{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Datamining.Clustering.SOMInternal where
import Prelude hiding (lookup)
import Control.DeepSeq (NFData)
import Data.Datamining.Clustering.Classifier (Classifier (..))
import qualified Data.Foldable as F (Foldable, foldr)
import Data.List (foldl', minimumBy)
import Data.Ord (comparing)
import GHC.Generics (Generic)
import qualified Math.Geometry.Grid as G (Grid (..))
import qualified Math.Geometry.GridMap as GM (GridMap (..))
decayingGaussian :: Floating x => x -> x -> x -> x -> x -> x -> x -> x
decayingGaussian r0 rf w0 wf tf t d = r * exp (-x/y)
where a = t / tf
r = r0 * ((rf/r0)**a)
w = w0 * ((wf/w0)**a)
x = (d*d)
y = (2*w*w)
stepFunction :: (Num d, Fractional x, Eq d) => x -> t -> d -> x
stepFunction r _ d = if d == 0 then r else 0.0
constantFunction :: x -> t -> d -> x
constantFunction r _ _ = r
data SOM t d gm x k p = SOM
{
gridMap :: gm p,
learningRate :: t -> d -> x,
difference :: p -> p -> x,
makeSimilar :: p -> x -> p -> p,
counter :: t
} deriving (Generic, NFData)
instance (F.Foldable gm) => F.Foldable (SOM t d gm x k) where
foldr f x g = F.foldr f x (gridMap g)
instance (G.Grid (gm p)) => G.Grid (SOM t d gm x k p) where
type Index (SOM t d gm x k p) = G.Index (gm p)
type Direction (SOM t d gm x k p) = G.Direction (gm p)
indices = G.indices . gridMap
distance = G.distance . gridMap
neighbours = G.neighbours . gridMap
contains = G.contains . gridMap
viewpoint = G.viewpoint . gridMap
directionTo = G.directionTo . gridMap
tileCount = G.tileCount . gridMap
null = G.null . gridMap
nonNull = G.nonNull . gridMap
instance (F.Foldable gm, GM.GridMap gm p, G.Grid (GM.BaseGrid gm p))
=> GM.GridMap (SOM t d gm x k) p where
type BaseGrid (SOM t d gm x k) p = GM.BaseGrid gm p
toGrid = GM.toGrid . gridMap
toMap = GM.toMap . gridMap
mapWithKey = error "Not implemented"
delete k = withGridMap (GM.delete k)
adjustWithKey f k = withGridMap (GM.adjustWithKey f k)
insertWithKey f k v = withGridMap (GM.insertWithKey f k v)
alter f k = withGridMap (GM.alter f k)
filterWithKey f = withGridMap (GM.filterWithKey f)
withGridMap :: (gm p -> gm p) -> SOM t d gm x k p -> SOM t d gm x k p
withGridMap f s = s { gridMap=gm' }
where gm = gridMap s
gm' = f gm
currentLearningFunction :: (Num t) => SOM t d gm x k p -> (d -> x)
currentLearningFunction s
= (learningRate s) (counter s)
toGridMap :: GM.GridMap gm p => SOM t d gm x k p -> gm p
toGridMap = gridMap
adjustNode
:: (G.Grid g, k ~ G.Index g, Num t) =>
g -> (t -> x) -> (p -> x -> p -> p) -> p -> k -> k -> p -> p
adjustNode g rateF adjustF target bmu k = adjustF target (rateF d)
where d = fromIntegral $ G.distance g bmu k
trainNeighbourhood
:: (G.Grid (gm p), GM.GridMap gm p,
G.Index (GM.BaseGrid gm p) ~ G.Index (gm p), Num t, Num x,
Num d) =>
SOM t d gm x k p -> G.Index (gm p) -> p -> SOM t d gm x k p
trainNeighbourhood s bmu target = s { gridMap=gm' }
where gm = gridMap s
gm' = GM.mapWithKey (adjustNode gm f1 f2 target bmu) gm
f1 = currentLearningFunction s
f2 = makeSimilar s
incrementCounter :: Num t => SOM t d gm x k p -> SOM t d gm x k p
incrementCounter s = s { counter=counter s + 1}
justTrain
:: (Ord x, G.Grid (gm p), GM.GridMap gm x, GM.GridMap gm p,
G.Index (GM.BaseGrid gm x) ~ G.Index (gm p),
G.Index (GM.BaseGrid gm p) ~ G.Index (gm p), Num t, Num x,
Num d) =>
SOM t d gm x k p -> p -> SOM t d gm x k p
justTrain s p = trainNeighbourhood s bmu p
where ds = GM.toList . GM.map (difference s p) $ gridMap s
bmu = f ds
f [] = error "SOM has no models"
f xs = fst $ minimumBy (comparing snd) xs
instance
(GM.GridMap gm p, k ~ G.Index (GM.BaseGrid gm p), G.Grid (gm p),
GM.GridMap gm x, k ~ G.Index (gm p), k ~ G.Index (GM.BaseGrid gm x),
Num t, Ord x, Num x, Num d)
=> Classifier (SOM t d gm) x k p where
toList = GM.toList . gridMap
numModels = G.tileCount . gridMap
models = GM.elems . gridMap
differences s p = GM.toList . GM.map (difference s p) $ gridMap s
trainBatch s = incrementCounter . foldl' justTrain s
reportAndTrain s p = (bmu, ds, incrementCounter s')
where ds = differences s p
bmu = fst $ minimumBy (comparing snd) ds
s' = trainNeighbourhood s bmu p