learning-hmm-0.3.2.2: Yet another library for hidden Markov models

Safe HaskellNone
LanguageHaskell2010

Learning.HMM

Synopsis

Documentation

data HMM s o Source

Parameter set of the hidden Markov model with discrete emission. The model schema is as follows.

      z_0 -> z_1 -> ... -> z_n
       |      |             |
       v      v             v
      x_0    x_1           x_n
  

Here, [z_0, z_1, ..., z_n] are hidden states and [x_0, x_1, ..., x_n] are observed outputs. z_0 is determined by the initialStateDist. For i = 1, ..., n, z_i is determined by the transitionDist conditioned by z_{i-1}. For i = 0, ..., n, x_i is determined by the emissionDist conditioned by z_i.

Constructors

HMM 

Fields

states :: [s]
 
outputs :: [o]
 
initialStateDist :: Categorical Double s

Categorical distribution of initial state

transitionDist :: s -> Categorical Double s

Categorical distribution of next state conditioned by the previous state

emissionDist :: s -> Categorical Double o

Categorical distribution of output conditioned by the hidden state

Instances

(Show s, Show o) => Show (HMM s o) 

init :: (Eq s, Eq o) => [s] -> [o] -> RVar (HMM s o) Source

init states outputs returns a random variable of models with the states and outputs, wherein parameters are sampled from uniform distributions.

withEmission :: (Eq s, Eq o) => HMM s o -> [o] -> HMM s o Source

model `withEmission` xs returns a model in which the emissionDist is updated by re-estimations using the observed outputs xs. The emissionDist is set to be normalized histograms each of which is calculated from segumentations of xs based on the Viterbi state path.

euclideanDistance :: (Eq s, Eq o) => HMM s o -> HMM s o -> Double Source

Return the Euclidean distance between two models that have the same states and outputs.

viterbi :: (Eq s, Eq o) => HMM s o -> [o] -> ([s], LogLikelihood) Source

viterbi model xs performs the Viterbi algorithm using the observed outputs xs, and returns the most likely state path and its log likelihood.

baumWelch :: (Eq s, Eq o) => HMM s o -> [o] -> [(HMM s o, LogLikelihood)] Source

baumWelch model xs iteratively performs the Baum-Welch algorithm using the observed outputs xs, and returns a list of updated models and their corresponding log likelihoods.

baumWelch' :: (Eq s, Eq o) => HMM s o -> [o] -> (HMM s o, LogLikelihood) Source

baumWelch' model xs performs the Baum-Welch algorithm using the observed outputs xs, and returns a model locally maximizing its log likelihood.

simulate :: HMM s o -> Int -> RVar ([s], [o]) Source

simulate model t generates a Markov process of length t using the model, and returns its state path and outputs.