Copyright | (c) Amy de Buitléir 2012-2018 |
---|---|
License | BSD-style |
Maintainer | amy@nualeargais.ie |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
A Kohonen Self-organising Map (SOM). A SOM maps input patterns onto a regular grid (usually two-dimensional) where each node in the grid is a model of the input data, and does so using a method which ensures that any topological relationships within the input data are also represented in the grid. This implementation supports the use of non-numeric patterns.
In layman's terms, a SOM can be useful when you you want to discover the underlying structure of some data. A tutorial is available at https://github.com/mhwombat/som/wiki.
NOTES:
- Version 5.0 fixed a bug in the
function. If you usedecayingGaussian
(which uses this function), your SOM should now learn more quickly.defaultSOM
- The
gaussian
function has been removed because it is not as useful for SOMs as I originally thought. It was originally designed to be used as a factor in a learning function. However, in most cases the user will want to introduce a time decay into the exponent, rather than simply multiply by a factor.
References:
- Kohonen, T. (1982). Self-organized formation of topologically correct feature maps. Biological Cybernetics, 43 (1), 59–69.
Synopsis
- 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
- toGridMap :: GridMap gm p => SOM t d gm x k p -> gm p
- decayingGaussian :: Floating x => x -> x -> x -> x -> x -> x -> x -> x
- stepFunction :: (Num d, Fractional x, Eq d) => x -> t -> d -> x
- constantFunction :: x -> t -> d -> x
- trainNeighbourhood :: (Grid (gm p), GridMap gm p, Index (BaseGrid gm p) ~ Index (gm p), Num t, Num x, Num d) => SOM t d gm x k p -> Index (gm p) -> p -> SOM t d gm x k p
Construction
data SOM t d gm x k p Source #
A Self-Organising Map (SOM).
Although SOM
implements GridMap
, most users will only need the
interface provided by Data.Datamining.Clustering.Classifier
. If
you chose to use the GridMap
functions, please note:
- The functions
adjust
, andadjustWithKey
do not increment the counter. You can do so manually withincrementCounter
. - The functions
map
andmapWithKey
are not implemented (they just return anerror
). It would be problematic to implement them because the input SOM and the output SOM would have to have the sameMetric
type.
SOM | |
|
Instances
(GridMap gm p, k ~ Index (BaseGrid gm p), Grid (gm p), GridMap gm x, k ~ Index (gm p), k ~ Index (BaseGrid gm x), Num t, Ord x, Num x, Num d) => Classifier (SOM t d gm) x k p Source # | |
Defined in Data.Datamining.Clustering.SOMInternal toList :: SOM t d gm x k p -> [(k, p)] Source # numModels :: SOM t d gm x k p -> Int Source # models :: SOM t d gm x k p -> [p] Source # differences :: SOM t d gm x k p -> p -> [(k, x)] Source # classify :: SOM t d gm x k p -> p -> k Source # train :: SOM t d gm x k p -> p -> SOM t d gm x k p Source # trainBatch :: SOM t d gm x k p -> [p] -> SOM t d gm x k p Source # classifyAndTrain :: SOM t d gm x k p -> p -> (k, SOM t d gm x k p) Source # diffAndTrain :: SOM t d gm x k p -> p -> ([(k, x)], SOM t d gm x k p) Source # reportAndTrain :: SOM t d gm x k p -> p -> (k, [(k, x)], SOM t d gm x k p) Source # | |
Foldable gm => Foldable (SOM t d gm x k) Source # | |
Defined in Data.Datamining.Clustering.SOMInternal fold :: Monoid m => SOM t d gm x k m -> m # foldMap :: Monoid m => (a -> m) -> SOM t d gm x k a -> m # foldr :: (a -> b -> b) -> b -> SOM t d gm x k a -> b # foldr' :: (a -> b -> b) -> b -> SOM t d gm x k a -> b # foldl :: (b -> a -> b) -> b -> SOM t d gm x k a -> b # foldl' :: (b -> a -> b) -> b -> SOM t d gm x k a -> b # foldr1 :: (a -> a -> a) -> SOM t d gm x k a -> a # foldl1 :: (a -> a -> a) -> SOM t d gm x k a -> a # toList :: SOM t d gm x k a -> [a] # null :: SOM t d gm x k a -> Bool # length :: SOM t d gm x k a -> Int # elem :: Eq a => a -> SOM t d gm x k a -> Bool # maximum :: Ord a => SOM t d gm x k a -> a # minimum :: Ord a => SOM t d gm x k a -> a # | |
(Foldable gm, GridMap gm p, Grid (BaseGrid gm p)) => GridMap (SOM t d gm x k) p Source # | |
Defined in Data.Datamining.Clustering.SOMInternal (!) :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), Ord k0) => SOM t d gm x k p -> k0 -> p # toMap :: k0 ~ Index (BaseGrid (SOM t d gm x k) p) => SOM t d gm x k p -> Map k0 p # toGrid :: SOM t d gm x k p -> BaseGrid (SOM t d gm x k) p # toList :: k0 ~ Index (BaseGrid (SOM t d gm x k) p) => SOM t d gm x k p -> [(k0, p)] # lookup :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), Ord k0) => k0 -> SOM t d gm x k p -> Maybe p # insert :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), Ord k0) => k0 -> p -> SOM t d gm x k p -> SOM t d gm x k p # insertWith :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), Ord k0) => (p -> p -> p) -> k0 -> p -> SOM t d gm x k p -> SOM t d gm x k p # insertWithKey :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), Ord k0) => (k0 -> p -> p -> p) -> k0 -> p -> SOM t d gm x k p -> SOM t d gm x k p # insertLookupWithKey :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), Ord k0) => (k0 -> p -> p -> p) -> k0 -> p -> SOM t d gm x k p -> (Maybe p, SOM t d gm x k p) # delete :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), Ord k0) => k0 -> SOM t d gm x k p -> SOM t d gm x k p # adjust :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), Ord k0) => (p -> p) -> k0 -> SOM t d gm x k p -> SOM t d gm x k p # adjustWithKey :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), Ord k0) => (k0 -> p -> p) -> k0 -> SOM t d gm x k p -> SOM t d gm x k p # alter :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), Ord k0) => (Maybe p -> Maybe p) -> k0 -> SOM t d gm x k p -> SOM t d gm x k p # findWithDefault :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), Ord k0) => p -> k0 -> SOM t d gm x k p -> p # keys :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), Ord k0) => SOM t d gm x k p -> [k0] # elems :: SOM t d gm x k p -> [p] # map :: (GridMap (SOM t d gm x k) v2, Index (BaseGrid (SOM t d gm x k) p) ~ Index (BaseGrid (SOM t d gm x k) v2)) => (p -> v2) -> SOM t d gm x k p -> SOM t d gm x k v2 # mapWithKey :: (k0 ~ Index (BaseGrid (SOM t d gm x k) p), k0 ~ Index (BaseGrid (SOM t d gm x k) v2), GridMap (SOM t d gm x k) v2) => (k0 -> p -> v2) -> SOM t d gm x k p -> SOM t d gm x k v2 # filter :: (p -> Bool) -> SOM t d gm x k p -> SOM t d gm x k p # filterWithKey :: k0 ~ Index (BaseGrid (SOM t d gm x k) p) => (k0 -> p -> Bool) -> SOM t d gm x k p -> SOM t d gm x k p # | |
Generic (SOM t d gm x k p) Source # | |
(NFData t, NFData (gm p)) => NFData (SOM t d gm x k p) Source # | |
Defined in Data.Datamining.Clustering.SOMInternal | |
Grid (gm p) => Grid (SOM t d gm x k p) Source # | |
Defined in Data.Datamining.Clustering.SOMInternal indices :: SOM t d gm x k p -> [Index (SOM t d gm x k p)] # distance :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> Index (SOM t d gm x k p) -> Int # minDistance :: SOM t d gm x k p -> [Index (SOM t d gm x k p)] -> Index (SOM t d gm x k p) -> Int # neighbours :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> [Index (SOM t d gm x k p)] # neighboursOfSet :: SOM t d gm x k p -> [Index (SOM t d gm x k p)] -> [Index (SOM t d gm x k p)] # neighbour :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> Direction (SOM t d gm x k p) -> Maybe (Index (SOM t d gm x k p)) # numNeighbours :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> Int # contains :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> Bool # tileCount :: SOM t d gm x k p -> Int # null :: SOM t d gm x k p -> Bool # nonNull :: SOM t d gm x k p -> Bool # edges :: SOM t d gm x k p -> [(Index (SOM t d gm x k p), Index (SOM t d gm x k p))] # viewpoint :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> [(Index (SOM t d gm x k p), Int)] # isAdjacent :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> Index (SOM t d gm x k p) -> Bool # adjacentTilesToward :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> Index (SOM t d gm x k p) -> [Index (SOM t d gm x k p)] # minimalPaths :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> Index (SOM t d gm x k p) -> [[Index (SOM t d gm x k p)]] # directionTo :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> Index (SOM t d gm x k p) -> [Direction (SOM t d gm x k p)] # defaultMinDistance :: SOM t d gm x k p -> [Index (SOM t d gm x k p)] -> Index (SOM t d gm x k p) -> Int # defaultNeighbours :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> [Index (SOM t d gm x k p)] # defaultNeighboursOfSet :: SOM t d gm x k p -> [Index (SOM t d gm x k p)] -> [Index (SOM t d gm x k p)] # defaultNeighbour :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> Direction (SOM t d gm x k p) -> Maybe (Index (SOM t d gm x k p)) # defaultTileCount :: SOM t d gm x k p -> Int # defaultEdges :: SOM t d gm x k p -> [(Index (SOM t d gm x k p), Index (SOM t d gm x k p))] # defaultIsAdjacent :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> Index (SOM t d gm x k p) -> Bool # defaultAdjacentTilesToward :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> Index (SOM t d gm x k p) -> [Index (SOM t d gm x k p)] # defaultMinimalPaths :: SOM t d gm x k p -> Index (SOM t d gm x k p) -> Index (SOM t d gm x k p) -> [[Index (SOM t d gm x k p)]] # | |
type BaseGrid (SOM t d gm x k) p Source # | |
Defined in Data.Datamining.Clustering.SOMInternal | |
type Rep (SOM t d gm x k p) Source # | |
Defined in Data.Datamining.Clustering.SOMInternal type Rep (SOM t d gm x k p) = D1 (MetaData "SOM" "Data.Datamining.Clustering.SOMInternal" "som-10.1.8-4U7idyllz4eEJA79g8KqEw" False) (C1 (MetaCons "SOM" PrefixI True) ((S1 (MetaSel (Just "gridMap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (gm p)) :*: S1 (MetaSel (Just "learningRate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (t -> d -> x))) :*: (S1 (MetaSel (Just "difference") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (p -> p -> x)) :*: (S1 (MetaSel (Just "makeSimilar") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (p -> x -> p -> p)) :*: S1 (MetaSel (Just "counter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 t))))) | |
type Direction (SOM t d gm x k p) Source # | |
Defined in Data.Datamining.Clustering.SOMInternal | |
type Index (SOM t d gm x k p) Source # | |
Defined in Data.Datamining.Clustering.SOMInternal |
Deconstruction
toGridMap :: GridMap gm p => SOM t d gm x k p -> gm p Source #
Extracts the grid and current models from the SOM.
A synonym for
.gridMap
Learning functions
decayingGaussian :: Floating x => x -> x -> x -> x -> x -> x -> x -> x Source #
A typical learning function for classifiers.
returns a bell curve-shaped
function. At time zero, the maximum learning rate (applied to the
BMU) is decayingGaussian
r0 rf w0 wf tfr0
, and the neighbourhood width is w0
. Over time the
bell curve shrinks and the learning rate tapers off, until at time
tf
, the maximum learning rate (applied to the BMU) is rf
,
and the neighbourhood width is wf
. Normally the parameters
should be chosen such that:
- 0 < rf << r0 < 1
- 0 < wf << w0
- 0 < tf
where << means "is much smaller than" (not the Haskell <<
operator!)
stepFunction :: (Num d, Fractional x, Eq d) => x -> t -> d -> x Source #
A learning function that only updates the BMU and has a constant learning rate.
constantFunction :: x -> t -> d -> x Source #
A learning function that updates all nodes with the same, constant learning rate. This can be useful for testing.
Advanced control
trainNeighbourhood :: (Grid (gm p), GridMap gm p, Index (BaseGrid gm p) ~ Index (gm p), Num t, Num x, Num d) => SOM t d gm x k p -> Index (gm p) -> p -> SOM t d gm x k p Source #
Trains the specified node and the neighbourood around it to better
match a target.
Most users should use
, which automatically determines
the BMU and trains it and its neighbourhood.train