Skip to content

Instantly share code, notes, and snippets.

@apskii
Last active August 29, 2015 14:07
Show Gist options
  • Save apskii/ca9f6807b9b3cc91ea02 to your computer and use it in GitHub Desktop.
Save apskii/ca9f6807b9b3cc91ea02 to your computer and use it in GitHub Desktop.
{-# LANGUAGE RankNTypes, TypeFamilies, RecordWildCards, GADTs, KindSignatures #-}
module Main where
import Data.List as L
import Data.Vector as V
import Data.Vector.Unboxed as U
import Data.Foldable as F
type family Observation c :: *
type instance Observation () = [Float]
data DataSet t label (box :: * -> *) =
forall elem . (Num elem) => DataSet {
observations :: t -> [Observation t],
measurements :: Observation t -> box elem,
label :: Observation t -> label,
distance :: box elem -> box elem -> elem
}
type VecDS t label = DataSet t label V.Vector
simpleDS :: VecDS () Int
simpleDS = DataSet observations measurements label distance
where
observations () = L.replicate 10 [0,0,0,0]
measurements xs = V.fromList xs
label _ = 111
distance xs ys = sqrt $ V.sum (V.zipWith (\x y -> (x+y)**2) xs ys)
kMeans :: Foldable box => DataSet t label box -> t -> [Observation t]
kMeans DataSet{..} x = undefined
where
labels = L.map label (observations x)
www = L.map measurements (observations x)
zzz = L.zipWith distance www www
wtf1 = L.foldl wtf2 0 (observations x)
wtf2 acc xs = acc + F.sum (measurements xs)
-- qq = V.fromList [1,2,3 :: Float]
-- l = distance qq qq
-- ^ if u really need this, make elem concrete,
-- make box concrete, or pass box constructor and use it in qq
data AbstractDataSet t = forall label box . AbstractDataSet (DataSet t label box)
abstractDS = AbstractDataSet simpleDS
polyFnForDataSetsWithDifferentInternalsButSameT :: [AbstractDataSet t] -> t -> [[Observation t]]
polyFnForDataSetsWithDifferentInternalsButSameT dss t =
L.map (\(AbstractDataSet ds) -> observations ds t) dss
main :: IO ()
main = print "hello world"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment