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

Safe HaskellNone
LanguageHaskell2010

Learning.IOHMM

Synopsis

Documentation

data IOHMM i s o Source

Parameter set of the input-output hidden Markov model with discrete emission. This IOHMM assumes that the inputs affect only the transition probabilities. The model schema is as follows.

      x_0    x_1           x_n
              |             |
              v             v
      z_0 -> z_1 -> ... -> z_n
       |      |             |
       v      v             v
      y_0    y_1           y_n
  

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

Constructors

IOHMM 

Fields

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

Categorical distribution of initial state

transitionDist :: i -> s -> Categorical Double s

Categorical distribution of next state conditioned by the input and previous state

emissionDist :: s -> Categorical Double o

Categorical distribution of output conditioned by the hidden state

Instances

(Show i, Show s, Show o) => Show (IOHMM i s o) 

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

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

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

withEmission model xs ys returns a model in which the emissionDist is updated by re-estimations using the inputs xs and outputs ys. The emissionDist is set to be normalized histograms each of which is calculated from segumentations of ys based on the Viterbi state path. If the lengths of xs and ys are different, the longer one is cut by the length of the shorter one.

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

viterbi model xs ys performs the Viterbi algorithm using the inputs xs and outputs ys, and returns the most likely state path and its log likelihood. If the lengths of xs and ys are different, the longer one is cut by the length of the shorter one.

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

baumWelch model xs ys iteratively performs the Baum-Welch algorithm using the inputs xs and outputs ys, and returns a list of updated models and their corresponding log likelihoods. If the lengths of xs and ys are different, the longer one is cut by the length of the shorter one.

simulate :: IOHMM i s o -> [i] -> RVar ([s], [o]) Source

simulate model xs generates a Markov process coinciding with the inputs xs using the model, and returns its state path and observed outputs.