som-10.1.3: Self-Organising Maps

Copyright(c) Amy de Buitléir 2012-2018
LicenseBSD-style
Maintaineramy@nualeargais.ie
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Datamining.Clustering.SGM2Internal

Description

A module containing private SGM internals. Most developers should use SGM instead. This module is subject to change without notice.

Synopsis

Documentation

exponential :: (Floating a, Integral t) => a -> a -> t -> a Source #

A typical learning function for classifiers. exponential r0 d t returns the learning rate at time t. When t = 0, the learning rate is r0. Over time the learning rate decays exponentially; the decay rate is d. Normally the parameters are chosen such that:

  • 0 < r0 < 1
  • 0 < d

data SGM t x k p Source #

A Simplified Self-Organising Map (SGM). t is the type of the counter. x is the type of the learning rate and the difference metric. k is the type of the model indices. p is the type of the input patterns and models.

Constructors

SGM 

Fields

  • toMap :: Map k (p, t)

    Maps patterns and match counts to nodes.

  • learningRate :: t -> x

    A function which determines the learning rate for a node. The input parameter indicates how many patterns (or pattern batches) have previously been presented to the classifier. Typically this is used to make the learning rate decay over time. The output is the learning rate for that node (the amount by which the node's model should be updated to match the target). The learning rate should be between zero and one.

  • capacity :: Int

    The maximum number of models this SGM can hold.

  • difference :: p -> p -> x

    A function which compares two patterns and returns a non-negative number representing how different the patterns are. A result of 0 indicates that the patterns are identical.

  • makeSimilar :: p -> x -> p -> p

    A function which updates models. For example, if this function is f, then f target amount pattern returns a modified copy of pattern that is more similar to target than pattern is. The magnitude of the adjustment is controlled by the amount parameter, which should be a number between 0 and 1. Larger values for amount permit greater adjustments. If amount=1, the result should be identical to the target. If amount=0, the result should be the unmodified pattern.

  • nextIndex :: k

    Index for the next node to add to the SGM.

Instances
Generic (SGM t x k p) Source # 
Instance details

Defined in Data.Datamining.Clustering.SGM2Internal

Associated Types

type Rep (SGM t x k p) :: Type -> Type #

Methods

from :: SGM t x k p -> Rep (SGM t x k p) x0 #

to :: Rep (SGM t x k p) x0 -> SGM t x k p #

(NFData k, NFData p, NFData t) => NFData (SGM t x k p) Source # 
Instance details

Defined in Data.Datamining.Clustering.SGM2Internal

Methods

rnf :: SGM t x k p -> () #

type Rep (SGM t x k p) Source # 
Instance details

Defined in Data.Datamining.Clustering.SGM2Internal

type Rep (SGM t x k p) = D1 (MetaData "SGM" "Data.Datamining.Clustering.SGM2Internal" "som-10.1.3-KJQv6JTiMLLFaeo4CM2vOK" False) (C1 (MetaCons "SGM" PrefixI True) ((S1 (MetaSel (Just "toMap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map k (p, t))) :*: (S1 (MetaSel (Just "learningRate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (t -> x)) :*: S1 (MetaSel (Just "capacity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :*: (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 "nextIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 k)))))

makeSGM :: Bounded k => (t -> x) -> Int -> (p -> p -> x) -> (p -> x -> p -> p) -> SGM t x k p Source #

makeSGM lr n diff ms creates a new SGM that does not (yet) contain any models. It will learn at the rate determined by the learning function lr, and will be able to hold up to n models. It will create a new model based on a pattern presented to it when the SGM is not at capacity, or a less useful model can be replaced. It will use the function diff to measure the similarity between an input pattern and a model. It will use the function ms to adjust models as needed to make them more similar to input patterns.

isEmpty :: SGM t x k p -> Bool Source #

Returns true if the SGM has no models, false otherwise.

size :: SGM t x k p -> Int Source #

Returns the number of models the SGM currently contains.

modelMap :: SGM t x k p -> Map k p Source #

Returns a map from node ID to model.

counterMap :: SGM t x k p -> Map k t Source #

Returns a map from node ID to counter (number of times the node's model has been the closest match to an input pattern).

modelAt :: Ord k => SGM t x k p -> k -> p Source #

Returns the model at a specified node.

counterAt :: Ord k => SGM t x k p -> k -> t Source #

Returns the match counter for a specified node.

labels :: SGM t x k p -> [k] Source #

Returns the current labels.

time :: Num t => SGM t x k p -> t Source #

The current "time" (number of times the SGM has been trained).

addNode :: (Num t, Enum k, Ord k) => p -> SGM t x k p -> SGM t x k p Source #

Adds a new node to the SGM.

incrementCounter :: (Num t, Ord k) => k -> SGM t x k p -> SGM t x k p Source #

Increments the counter.

trainNode :: (Num t, Ord k) => SGM t x k p -> k -> p -> SGM t x k p Source #

Trains the specified node to better match a target. Most users should use train, which automatically determines the BMU and trains it.

modelDiffs :: (Eq k, Ord k) => SGM t x k p -> [((k, k), x)] Source #

Calculates the difference between all pairs of non-identical labels in the SGM.

labelPairs :: Eq k => SGM t x k p -> [(k, k)] Source #

Generates all pairs of non-identical labels in the SGM.

labelPairs' :: Eq k => SGM t x k p -> k -> [(k, k)] Source #

Pairs a node label with all labels except itself.

twoMostSimilar :: (Ord x, Eq k, Ord k) => SGM t x k p -> (k, k, x) Source #

Returns the labels of the two most similar models, and the difference between them.

mergeModels :: (Num t, Ord t, Ord k) => SGM t x k p -> k -> k -> (k, SGM t x k p) Source #

Deletes the least used (least matched) model in a pair, and returns its label (now available) and the updated SGM. TODO: Modify the other model to make it slightly more similar to the one that was deleted?

setModel :: (Num t, Ord k) => SGM t x k p -> k -> p -> SGM t x k p Source #

Set the model for a node. Useful when merging two models and replacing one.

mergeAddModel :: (Num t, Ord t, Ord k) => SGM t x k p -> k -> k -> p -> SGM t x k p Source #

Add a new node, making room for it by merging two existing nodes.

classify :: (Num t, Ord t, Num x, Ord x, Enum k, Ord k) => SGM t x k p -> p -> (k, x, Map k (p, x)) Source #

classify s p identifies the model s that most closely matches the pattern p. It will not make any changes to the classifier. (I.e., it will not change the models or match counts.) Returns the ID of the node with the best matching model, the difference between the best matching model and the pattern, and the SGM labels paired with the model and the difference between the input and the corresponding model. The final paired list is sorted in decreasing order of similarity.

matchOrder :: (Ord a, Ord b) => (a, b) -> (a, b) -> Ordering Source #

Order models by ascending difference from the input pattern, then by creation order (label number).

trainAndClassify :: (Num t, Ord t, Num x, Ord x, Enum k, Ord k) => SGM t x k p -> p -> (k, x, Map k (p, x), SGM t x k p) Source #

trainAndClassify s p identifies the model in s that most closely matches p, and updates it to be a somewhat better match. If necessary, it will create a new node and model. Returns the ID of the node with the best matching model, the difference between the pattern and the best matching model in the original SGM (before training or adding a new model), the differences between the pattern and each model in the updated SGM, and the updated SGM.

trainAndClassify' :: (Num t, Ord t, Num x, Ord x, Enum k, Ord k) => SGM t x k p -> p -> (k, x, Map k (p, x), SGM t x k p) Source #

Internal method. NOTE: This function will adjust the model and update the match for the BMU.

addModelTrainAndClassify :: (Num t, Ord t, Num x, Ord x, Enum k, Ord k) => SGM t x k p -> p -> (k, x, Map k (p, x), SGM t x k p) Source #

Internal method.

train :: (Num t, Ord t, Num x, Ord x, Enum k, Ord k) => SGM t x k p -> p -> SGM t x k p Source #

train s p identifies the model in s that most closely matches p, and updates it to be a somewhat better match. If necessary, it will create a new node and model.

trainBatch :: (Num t, Ord t, Num x, Ord x, Enum k, Ord k) => SGM t x k p -> [p] -> SGM t x k p Source #

For each pattern p in ps, trainBatch s ps identifies the model in s that most closely matches p, and updates it to be a somewhat better match.