Copyright | (c) 2012-2021 Amy de Buitléir |
---|---|
License | BSD-style |
Maintainer | amy@nualeargais.ie |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
A module containing private SGM
internals. Most developers should
use SGM
instead. This module is subject to change without notice.
Synopsis
- exponential :: (Floating x, Integral t) => x -> x -> t -> x
- data SGM t x k p = SGM {
- toMap :: Map k (p, t)
- learningRate :: t -> x
- capacity :: Int
- difference :: p -> p -> x
- makeSimilar :: p -> x -> p -> p
- nextIndex :: k
- makeSGM :: Bounded k => (t -> x) -> Int -> (p -> p -> x) -> (p -> x -> p -> p) -> SGM t x k p
- isEmpty :: SGM t x k p -> Bool
- size :: SGM t x k p -> Int
- modelMap :: SGM t x k p -> Map k p
- counterMap :: SGM t x k p -> Map k t
- modelAt :: Ord k => SGM t x k p -> k -> p
- counterAt :: Ord k => SGM t x k p -> k -> t
- labels :: SGM t x k p -> [k]
- time :: Num t => SGM t x k p -> t
- addNode :: (Num t, Bounded k, Enum k, Ord k) => SGM t x k p -> p -> SGM t x k p
- addNodeAt :: (Num t, Bounded k, Enum k, Ord k) => SGM t x k p -> k -> p -> SGM t x k p
- incrementCounter :: (Num t, Ord k) => k -> SGM t x k p -> SGM t x k p
- trainNode :: (Num t, Ord k) => SGM t x k p -> k -> p -> SGM t x k p
- hasLabel :: Ord k => SGM t x k p -> k -> Bool
- imprint :: (Num t, Ord t, Fractional x, Num x, Ord x, Bounded k, Enum k, Ord k) => SGM t x k p -> k -> p -> SGM t x k p
- imprintBatch :: (Num t, Ord t, Fractional x, Num x, Ord x, Bounded k, Enum k, Ord k) => SGM t x k p -> [(k, p)] -> SGM t x k p
- modelDiffs :: (Eq k, Ord k) => SGM t x k p -> [((k, k), x)]
- labelPairs :: Eq k => SGM t x k p -> [(k, k)]
- labelPairs' :: Eq k => SGM t x k p -> k -> [(k, k)]
- twoMostSimilar :: (Ord x, Eq k, Ord k) => SGM t x k p -> (k, k, x)
- mergeModels :: (Num t, Ord t, Ord k) => SGM t x k p -> k -> k -> (k, SGM t x k p)
- atCapacity :: SGM t x k p -> Bool
- consolidate :: (Num t, Ord t, Ord x, Ord k) => SGM t x k p -> (k, SGM t x k p)
- consolidateAndAdd :: (Num t, Ord t, Ord x, Bounded k, Enum k, Ord k) => SGM t x k p -> p -> SGM t x k p
- setModel :: (Num t, Ord k) => SGM t x k p -> k -> p -> SGM t x k p
- 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))
- matchOrder :: (Ord a, Ord b) => (a, b) -> (a, b) -> Ordering
- trainAndClassify :: (Num t, Ord t, Fractional x, Num x, Ord x, Bounded k, Enum k, Ord k) => SGM t x k p -> p -> (k, x, Map k (p, x), SGM t x k p)
- 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)
- train :: (Num t, Ord t, Fractional x, Num x, Ord x, Bounded k, Enum k, Ord k) => SGM t x k p -> p -> SGM t x k p
- trainBatch :: (Num t, Ord t, Fractional x, Num x, Ord x, Bounded k, Enum k, Ord k) => SGM t x k p -> [p] -> SGM t x k p
- numModels :: SGM t x k p -> Int
- maxSize :: SGM t x k p -> Int
- filter :: (p -> Bool) -> SGM t x k p -> SGM t x k p
Documentation
exponential :: (Floating x, Integral t) => x -> x -> t -> x Source #
A typical learning function for classifiers.
returns the learning rate at time exponential
r0 d tt
.
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
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.
SGM | |
|
Instances
makeSGM :: Bounded k => (t -> x) -> Int -> (p -> p -> x) -> (p -> x -> p -> p) -> SGM t x k p Source #
creates a new SGM that does not (yet)
contain any models.
It will learn at the rate determined by the learning function makeSGM
lr n diff mslr
,
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.
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).
time :: Num t => SGM t x k p -> t Source #
The current "time" (number of times the SGM has been trained).
addNode :: (Num t, Bounded k, Enum k, Ord k) => SGM t x k p -> 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 match 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
, which automatically determines
the BMU and trains it.train
imprint :: (Num t, Ord t, Fractional x, Num x, Ord x, Bounded k, Enum k, Ord k) => SGM t x k p -> k -> p -> SGM t x k p Source #
imprintBatch :: (Num t, Ord t, Fractional x, Num x, Ord x, Bounded k, Enum k, Ord k) => SGM t x k p -> [(k, p)] -> SGM t x k p Source #
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?
atCapacity :: SGM t x k p -> Bool Source #
Returns True if the SOM is full; returns False if it can add one or more models.
consolidate :: (Num t, Ord t, Ord x, Ord k) => SGM t x k p -> (k, SGM t x k p) Source #
finds the two most similar models, and combines
them. This can be used to free up more space for learning. It
returns the index of the newly free node, and the updated SGM.consolidate
s
consolidateAndAdd :: (Num t, Ord t, Ord x, Bounded k, Enum k, Ord k) => SGM t x k p -> p -> SGM t x k p Source #
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.
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 #
identifies the model classify
s ps
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, Fractional x, Num x, Ord x, Bounded k, Enum k, Ord k) => SGM t x k p -> p -> (k, x, Map k (p, x), SGM t x k p) Source #
identifies the model in trainAndClassify
s ps
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.
train :: (Num t, Ord t, Fractional x, Num x, Ord x, Bounded k, Enum k, Ord k) => SGM t x k p -> p -> SGM t x k p Source #
identifies the model in train
s ps
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, Fractional x, Num x, Ord x, Bounded k, Enum k, Ord k) => SGM t x k p -> [p] -> SGM t x k p Source #
For each pattern p
in ps
,
identifies the
model in trainBatch
s pss
that most closely matches p
,
and updates it to be a somewhat better match.