hopfield-0.1.0.1: Hopfield Networks, Boltzmann Machines and Clusters

Safe HaskellNone

Hopfield.Boltzmann.RestrictedBoltzmannMachine

Description

Base Restricted Boltzmann machine. http:en.wikipedia.orgwikiRestricted_Boltzmann_machine

Synopsis

Documentation

learningRate :: DoubleSource

determines the rate in which the weights are changed in the training phase. http:en.wikipedia.orgwikiRestricted_Boltzmann_machine#Training_algorithm

data Mode Source

Constructors

Hidden 
Visible 

Instances

Eq Mode 
Show Mode 

data Phase Source

Constructors

Training 
Matching 

Instances

Eq Phase 
Show Phase 

data BoltzmannData Source

Constructors

BoltzmannData 

Fields

weightsB :: Weights

the weights of the network

patternsB :: [Pattern]

the patterns which were used to train it

nr_hiddenB :: Int

number of neurons in the hidden layer

pattern_to_binaryB :: [(Pattern, [Int])]

the binary representation of the pattern index the pattern_to_binary field will not replace the patternsB field as it does not contain duplicated patterns, which might be required for statistical analysis in clustering and super attractors

Instances

getDimension :: Mode -> Weights -> IntSource

Retrieves the dimension of the weights matrix corresponding to the given mode. For hidden, it is the width of the matrix, and for visible it is the height.

buildBoltzmannData :: MonadRandom m => [Pattern] -> m BoltzmannDataSource

buildBoltzmannData patterns trains a boltzmann network with patterns. The number of hidden neurons is set to the number of visible neurons.

buildBoltzmannData' :: MonadRandom m => [Pattern] -> Int -> m BoltzmannDataSource

buildBoltzmannData' patterns nr_hidden: Takes a list of patterns and builds a Boltzmann network (by training) in which these patterns are stable states. The result of this function can be used to run a pattern against the network, by using matchPatternBoltzmann.

updateNeuron' :: Double -> Phase -> Mode -> Weights -> Pattern -> Int -> IntSource

updateNeuron :: MonadRandom m => Phase -> Mode -> Weights -> Pattern -> Int -> m IntSource

updateNeuron mode ws pat index , given a vector pat of type mode updates the neuron with number index in the layer with opposite type.

getCounterPattern :: MonadRandom m => Phase -> Mode -> Weights -> Pattern -> m PatternSource

getCounterPattern mode ws pat, given a vector pat of type mode computes the values of all the neurons in the layer of the opposite type.

updateWeights :: MonadRandom m => Weights -> Pattern -> m WeightsSource

One step which updates the weights in the CD-n training process. The weights are changed according to one of the training patterns. http:en.wikipedia.orgwikiRestricted_Boltzmann_machine#Training_algorithm

trainBoltzmann :: MonadRandom m => [Pattern] -> Int -> m (Weights, [(Pattern, [Int])])Source

The training function for the Boltzmann Machine. We are using the contrastive divergence algorithm CD-1 TODO see if making the vis (we could extend to CD-n, but In practice, CD-1 has been shown to work surprisingly well. trainBoltzmann pats nr_hidden where pats are the training patterns and nr_hidden is the number of neurons to be created in the hidden layer. http:en.wikipedia.orgwikiRestricted_Boltzmann_machine#Training_algorithm

activation :: Double -> DoubleSource

The activation function for the network (the logistic sigmoid). http:en.wikipedia.orgwikiSigmoid_function

validPattern :: Phase -> Mode -> Weights -> Pattern -> Maybe StringSource

validPattern mode weights pattern Returns an error string in a Just if the pattern is not compatible with weights and Nothing otherwise. mode gives the type of the pattern, which is checked (Visible or Hidden).

validWeights :: Weights -> Maybe StringSource

updateBoltzmann :: MonadRandom m => Weights -> Pattern -> m PatternSource

Updates a pattern using the Boltzmann machine

matchPatternBoltzmann :: MonadRandom m => BoltzmannData -> Pattern -> m IntSource

Matches a pattern against the a given network