Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data T distr sh prob = Cons {
- initial :: Vector sh prob
- transition :: SquareMatrix sh prob
- distribution :: distr
- type Discrete symbol sh prob = T (Discrete symbol sh prob) sh prob
- type DiscreteTrained symbol sh prob = Trained (DiscreteTrained symbol sh prob) sh prob
- type Gaussian emiSh stateSh a = T (Gaussian emiSh stateSh a) stateSh a
- type GaussianTrained emiSh stateSh a = Trained (GaussianTrained emiSh stateSh a) stateSh a
- uniform :: (Info distr, StateShape distr ~ sh, C sh, Probability distr ~ prob) => distr -> T distr sh prob
- generate :: (RandomGen g, Ord prob, Random prob, Generate distr, StateShape distr ~ sh, Indexed sh, Index sh ~ state, Probability distr ~ prob, Emission distr ~ emission) => T distr sh prob -> g -> [emission]
- generateLabeled :: (RandomGen g, Ord prob, Random prob, Generate distr, StateShape distr ~ sh, Indexed sh, Index sh ~ state, Probability distr ~ prob, Emission distr ~ emission) => T distr sh prob -> g -> [(state, emission)]
- probabilitySequence :: (Traversable f, EmissionProb distr, StateShape distr ~ sh, Indexed sh, Index sh ~ state, Probability distr ~ prob, Emission distr ~ emission) => T distr sh prob -> f (state, emission) -> f prob
- logLikelihood :: (EmissionProb distr, StateShape distr ~ sh, Eq sh, Floating prob, Probability distr ~ prob, Emission distr ~ emission, Traversable f) => T distr sh prob -> T f emission -> prob
- reveal :: (EmissionProb distr, StateShape distr ~ sh, InvIndexed sh, Eq sh, Index sh ~ state, Probability distr ~ prob, Emission distr ~ emission, Traversable f, Reverse f) => T distr sh prob -> T f emission -> T f state
- data Trained distr sh prob = Trained {
- trainedInitial :: Vector sh prob
- trainedTransition :: SquareMatrix sh prob
- trainedDistribution :: distr
- trainSupervised :: (StateShape distr ~ sh, Index sh ~ state, Estimate tdistr distr, Probability distr ~ prob, Emission distr ~ emission) => sh -> T [] (state, emission) -> Trained tdistr sh prob
- trainUnsupervised :: (Estimate tdistr distr, StateShape distr ~ sh, Eq sh, Probability distr ~ prob, Emission distr ~ emission) => T distr sh prob -> T [] emission -> Trained tdistr sh prob
- mergeTrained :: (C sh, Eq sh, Estimate tdistr distr, Probability distr ~ prob) => Trained tdistr sh prob -> Trained tdistr sh prob -> Trained tdistr sh prob
- finishTraining :: (C sh, Eq sh, Estimate tdistr distr, Probability distr ~ prob) => Trained tdistr sh prob -> T distr sh prob
- trainMany :: (C sh, Eq sh, Estimate tdistr distr, Probability distr ~ prob, Foldable f) => (trainingData -> Trained tdistr sh prob) -> T f trainingData -> T distr sh prob
- deviation :: (C sh, Eq sh, Real prob, Ord prob) => T distr sh prob -> T distr sh prob -> prob
- toCSV :: (ToCSV distr, Indexed sh, Real prob, Show prob) => T distr sh prob -> String
- fromCSV :: (FromCSV distr, StateShape distr ~ stateSh, Indexed stateSh, Index stateSh ~ state, Real prob, Read prob) => (Int -> stateSh) -> String -> Exceptional String (T distr stateSh prob)
Documentation
A Hidden Markov model consists of a number of (hidden) states
and a set of emissions.
There is a vector for the initial probability of each state
and a matrix containing the probability for switching
from one state to another one.
The distribution
field points to probability distributions
that associate every state with emissions of different probability.
Famous distribution instances are discrete and Gaussian distributions.
See Math.HiddenMarkovModel.Distribution for details.
The transition matrix is transposed with respect to popular HMM descriptions. But I think this is the natural orientation, because this way you can write "transition matrix times probability column vector".
The type has two type parameters,
although the one for the distribution would be enough.
However, replacing prob
by Distr.Probability distr
would prohibit the derived Show and Read instances.
Cons | |
|
Instances
(C sh, Storable prob, Show sh, Show prob, Show distr) => Show (T distr sh prob) Source # | |
(NFData distr, NFData sh, NFData prob, Storable prob) => NFData (T distr sh prob) Source # | |
Defined in Math.HiddenMarkovModel.Private | |
(Real prob, FormatArray sh, Format distr) => Format (T distr sh prob) Source # | |
type DiscreteTrained symbol sh prob = Trained (DiscreteTrained symbol sh prob) sh prob Source #
type GaussianTrained emiSh stateSh a = Trained (GaussianTrained emiSh stateSh a) stateSh a Source #
uniform :: (Info distr, StateShape distr ~ sh, C sh, Probability distr ~ prob) => distr -> T distr sh prob Source #
Create a model with uniform probabilities
for initial vector and transition matrix
given a distribution for the emissions.
You can use this as a starting point for trainUnsupervised
.
generate :: (RandomGen g, Ord prob, Random prob, Generate distr, StateShape distr ~ sh, Indexed sh, Index sh ~ state, Probability distr ~ prob, Emission distr ~ emission) => T distr sh prob -> g -> [emission] Source #
generateLabeled :: (RandomGen g, Ord prob, Random prob, Generate distr, StateShape distr ~ sh, Indexed sh, Index sh ~ state, Probability distr ~ prob, Emission distr ~ emission) => T distr sh prob -> g -> [(state, emission)] Source #
probabilitySequence :: (Traversable f, EmissionProb distr, StateShape distr ~ sh, Indexed sh, Index sh ~ state, Probability distr ~ prob, Emission distr ~ emission) => T distr sh prob -> f (state, emission) -> f prob Source #
logLikelihood :: (EmissionProb distr, StateShape distr ~ sh, Eq sh, Floating prob, Probability distr ~ prob, Emission distr ~ emission, Traversable f) => T distr sh prob -> T f emission -> prob Source #
Logarithm of the likelihood to observe the given sequence. We return the logarithm because the likelihood can be so small that it may be rounded to zero in the choosen number type.
reveal :: (EmissionProb distr, StateShape distr ~ sh, InvIndexed sh, Eq sh, Index sh ~ state, Probability distr ~ prob, Emission distr ~ emission, Traversable f, Reverse f) => T distr sh prob -> T f emission -> T f state Source #
Reveal the state sequence that led most likely to the observed sequence of emissions. It is found using the Viterbi algorithm.
data Trained distr sh prob Source #
A trained model is a temporary form of a Hidden Markov model
that we need during the training on multiple training sequences.
It allows to collect knowledge over many sequences with mergeTrained
,
even with mixed supervised and unsupervised training.
You finish the training by converting the trained model
back to a plain modul using finishTraining
.
You can create a trained model in three ways:
- supervised training using an emission sequence with associated states,
- unsupervised training using an emission sequence and an existing Hidden Markov Model,
- derive it from state sequence patterns, cf. Math.HiddenMarkovModel.Pattern.
Trained | |
|
Instances
(C sh, Storable prob, Show sh, Show prob, Show distr) => Show (Trained distr sh prob) Source # | |
(C sh, Eq sh, Estimate tdistr distr, Probability distr ~ prob) => Semigroup (Trained tdistr sh prob) Source # | |
(NFData distr, NFData sh, NFData prob, Storable prob) => NFData (Trained distr sh prob) Source # | |
Defined in Math.HiddenMarkovModel.Private |
trainSupervised :: (StateShape distr ~ sh, Index sh ~ state, Estimate tdistr distr, Probability distr ~ prob, Emission distr ~ emission) => sh -> T [] (state, emission) -> Trained tdistr sh prob Source #
Contribute a manually labeled emission sequence to a HMM training.
trainUnsupervised :: (Estimate tdistr distr, StateShape distr ~ sh, Eq sh, Probability distr ~ prob, Emission distr ~ emission) => T distr sh prob -> T [] emission -> Trained tdistr sh prob Source #
Consider a superposition of all possible state sequences weighted by the likelihood to produce the observed emission sequence. Now train the model with respect to all of these sequences with respect to the weights. This is done by the Baum-Welch algorithm.
mergeTrained :: (C sh, Eq sh, Estimate tdistr distr, Probability distr ~ prob) => Trained tdistr sh prob -> Trained tdistr sh prob -> Trained tdistr sh prob Source #
finishTraining :: (C sh, Eq sh, Estimate tdistr distr, Probability distr ~ prob) => Trained tdistr sh prob -> T distr sh prob Source #
trainMany :: (C sh, Eq sh, Estimate tdistr distr, Probability distr ~ prob, Foldable f) => (trainingData -> Trained tdistr sh prob) -> T f trainingData -> T distr sh prob Source #
deviation :: (C sh, Eq sh, Real prob, Ord prob) => T distr sh prob -> T distr sh prob -> prob Source #
Compute maximum deviation between initial and transition probabilities. You can use this as abort criterion for unsupervised training. We omit computation of differences between the emission probabilities. This simplifies matters a lot and should suffice for defining an abort criterion.