Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data family T typ sh prob
- data family Trained typ sh prob
- type family Emission typ prob
- class Show typ where
- class NFData typ where
- class Format typ where
- class Info typ where
- statesShape :: C sh => T typ sh prob -> sh
- statesShapeTrained :: C sh => Trained typ sh prob -> sh
- class Generate typ where
- class EmissionProb typ where
- class EmissionProb typ => Estimate typ where
- accumulateEmissions :: (Indexed sh, Real prob, Index sh ~ state) => sh -> T [] (state, Emission typ prob) -> Trained typ sh prob
- trainVector :: (C sh, Eq sh, Real prob) => Emission typ prob -> Vector sh prob -> Trained typ sh prob
- combine :: (C sh, Eq sh, Real prob) => Trained typ sh prob -> Trained typ sh prob -> Trained typ sh prob
- normalize :: (C sh, Eq sh, Real prob) => Trained typ sh prob -> T typ sh prob
- accumulateEmissionVectors :: (Estimate typ, C sh, Eq sh, Real prob) => T [] (Emission typ prob, Vector sh prob) -> Trained typ sh prob
- data Discrete symbol
- discreteFromList :: (Ord symbol, C sh, Eq sh, Real prob) => T [] (symbol, Vector sh prob) -> T (Discrete symbol) sh prob
- data Gaussian emiSh
- gaussian :: (C emiSh, C stateSh, Real prob) => Array stateSh (Vector emiSh prob, Hermitian emiSh prob) -> T (Gaussian emiSh) stateSh prob
- gaussianTrained :: (C emiSh, Eq emiSh, C stateSh, Real prob) => Array stateSh (prob, Vector emiSh prob, Hermitian emiSh prob) -> Trained (Gaussian emiSh) stateSh prob
- class ToCSV typ where
- class FromCSV typ where
- type CSVParser = StateT CSVResult (Exceptional String)
- class Ord symbol => CSVSymbol symbol where
- cellFromSymbol :: symbol -> String
- symbolFromCell :: String -> Maybe symbol
Documentation
data family T typ sh prob Source #
Instances
(Show typ, C sh, Show sh, Show prob, Storable prob) => Show (T typ sh prob) Source # | |
(NFData typ, NFData sh, NFData prob, C sh) => NFData (T typ sh prob) Source # | |
Defined in Math.HiddenMarkovModel.Distribution | |
(Format typ, C sh, Real prob) => Format (T typ sh prob) Source # | |
newtype T (Gaussian emiSh) stateSh a Source # | |
newtype T (Discrete symbol) sh prob Source # | |
data family Trained typ sh prob Source #
Instances
(Show typ, C sh, Show sh, Show prob, Storable prob) => Show (Trained typ sh prob) Source # | |
(Estimate typ, C sh, Eq sh, Real prob) => Semigroup (Trained typ sh prob) Source # | |
(NFData typ, NFData sh, NFData prob, C sh) => NFData (Trained typ sh prob) Source # | |
Defined in Math.HiddenMarkovModel.Distribution | |
newtype Trained (Gaussian emiSh) stateSh a Source # | |
Defined in Math.HiddenMarkovModel.Distribution | |
newtype Trained (Discrete symbol) sh prob Source # | |
Defined in Math.HiddenMarkovModel.Distribution |
showsPrec :: (C sh, Show sh, Show prob, Storable prob) => Int -> T typ sh prob -> ShowS Source #
showsPrecTrained :: (C sh, Show sh, Show prob, Storable prob) => Int -> Trained typ sh prob -> ShowS Source #
class NFData typ where Source #
rnf :: (NFData sh, NFData prob, C sh) => T typ sh prob -> () Source #
rnfTrained :: (NFData sh, NFData prob, C sh) => Trained typ sh prob -> () Source #
statesShape :: C sh => T typ sh prob -> sh Source #
statesShapeTrained :: C sh => Trained typ sh prob -> sh Source #
class Generate typ where Source #
generate :: (Indexed sh, Real prob, Random prob, RandomGen g) => T typ sh prob -> Index sh -> State g (Emission typ prob) Source #
class EmissionProb typ where Source #
mapStatesShape :: (C sh0, C sh1) => (sh0 -> sh1) -> T typ sh0 prob -> T typ sh1 prob Source #
emissionProb :: (C sh, Real prob) => T typ sh prob -> Emission typ prob -> Vector sh prob Source #
emissionStateProb :: (Indexed sh, Real prob) => T typ sh prob -> Emission typ prob -> Index sh -> prob Source #
Instances
(C emiSh, Eq emiSh) => EmissionProb (Gaussian emiSh) Source # | |
Defined in Math.HiddenMarkovModel.Distribution mapStatesShape :: (C sh0, C sh1) => (sh0 -> sh1) -> T (Gaussian emiSh) sh0 prob -> T (Gaussian emiSh) sh1 prob Source # emissionProb :: (C sh, Real prob) => T (Gaussian emiSh) sh prob -> Emission (Gaussian emiSh) prob -> Vector sh prob Source # emissionStateProb :: (Indexed sh, Real prob) => T (Gaussian emiSh) sh prob -> Emission (Gaussian emiSh) prob -> Index sh -> prob Source # | |
Ord symbol => EmissionProb (Discrete symbol) Source # | |
Defined in Math.HiddenMarkovModel.Distribution mapStatesShape :: (C sh0, C sh1) => (sh0 -> sh1) -> T (Discrete symbol) sh0 prob -> T (Discrete symbol) sh1 prob Source # emissionProb :: (C sh, Real prob) => T (Discrete symbol) sh prob -> Emission (Discrete symbol) prob -> Vector sh prob Source # emissionStateProb :: (Indexed sh, Real prob) => T (Discrete symbol) sh prob -> Emission (Discrete symbol) prob -> Index sh -> prob Source # |
class EmissionProb typ => Estimate typ where Source #
accumulateEmissions :: (Indexed sh, Real prob, Index sh ~ state) => sh -> T [] (state, Emission typ prob) -> Trained typ sh prob Source #
trainVector :: (C sh, Eq sh, Real prob) => Emission typ prob -> Vector sh prob -> Trained typ sh prob Source #
combine :: (C sh, Eq sh, Real prob) => Trained typ sh prob -> Trained typ sh prob -> Trained typ sh prob Source #
normalize :: (C sh, Eq sh, Real prob) => Trained typ sh prob -> T typ sh prob Source #
Instances
(C emiSh, Eq emiSh) => Estimate (Gaussian emiSh) Source # | |
Defined in Math.HiddenMarkovModel.Distribution accumulateEmissions :: (Indexed sh, Real prob, Index sh ~ state) => sh -> T [] (state, Emission (Gaussian emiSh) prob) -> Trained (Gaussian emiSh) sh prob Source # trainVector :: (C sh, Eq sh, Real prob) => Emission (Gaussian emiSh) prob -> Vector sh prob -> Trained (Gaussian emiSh) sh prob Source # combine :: (C sh, Eq sh, Real prob) => Trained (Gaussian emiSh) sh prob -> Trained (Gaussian emiSh) sh prob -> Trained (Gaussian emiSh) sh prob Source # normalize :: (C sh, Eq sh, Real prob) => Trained (Gaussian emiSh) sh prob -> T (Gaussian emiSh) sh prob Source # | |
Ord symbol => Estimate (Discrete symbol) Source # | |
Defined in Math.HiddenMarkovModel.Distribution accumulateEmissions :: (Indexed sh, Real prob, Index sh ~ state) => sh -> T [] (state, Emission (Discrete symbol) prob) -> Trained (Discrete symbol) sh prob Source # trainVector :: (C sh, Eq sh, Real prob) => Emission (Discrete symbol) prob -> Vector sh prob -> Trained (Discrete symbol) sh prob Source # combine :: (C sh, Eq sh, Real prob) => Trained (Discrete symbol) sh prob -> Trained (Discrete symbol) sh prob -> Trained (Discrete symbol) sh prob Source # normalize :: (C sh, Eq sh, Real prob) => Trained (Discrete symbol) sh prob -> T (Discrete symbol) sh prob Source # |
accumulateEmissionVectors :: (Estimate typ, C sh, Eq sh, Real prob) => T [] (Emission typ prob, Vector sh prob) -> Trained typ sh prob Source #
Instances
CSVSymbol symbol => FromCSV (Discrete symbol) Source # | |
CSVSymbol symbol => ToCSV (Discrete symbol) Source # | |
Ord symbol => Estimate (Discrete symbol) Source # | |
Defined in Math.HiddenMarkovModel.Distribution accumulateEmissions :: (Indexed sh, Real prob, Index sh ~ state) => sh -> T [] (state, Emission (Discrete symbol) prob) -> Trained (Discrete symbol) sh prob Source # trainVector :: (C sh, Eq sh, Real prob) => Emission (Discrete symbol) prob -> Vector sh prob -> Trained (Discrete symbol) sh prob Source # combine :: (C sh, Eq sh, Real prob) => Trained (Discrete symbol) sh prob -> Trained (Discrete symbol) sh prob -> Trained (Discrete symbol) sh prob Source # normalize :: (C sh, Eq sh, Real prob) => Trained (Discrete symbol) sh prob -> T (Discrete symbol) sh prob Source # | |
Ord symbol => EmissionProb (Discrete symbol) Source # | |
Defined in Math.HiddenMarkovModel.Distribution mapStatesShape :: (C sh0, C sh1) => (sh0 -> sh1) -> T (Discrete symbol) sh0 prob -> T (Discrete symbol) sh1 prob Source # emissionProb :: (C sh, Real prob) => T (Discrete symbol) sh prob -> Emission (Discrete symbol) prob -> Vector sh prob Source # emissionStateProb :: (Indexed sh, Real prob) => T (Discrete symbol) sh prob -> Emission (Discrete symbol) prob -> Index sh -> prob Source # | |
Ord symbol => Generate (Discrete symbol) Source # | |
Ord symbol => Info (Discrete symbol) Source # | |
Defined in Math.HiddenMarkovModel.Distribution | |
(Show symbol, Ord symbol) => Format (Discrete symbol) Source # | |
NFData symbol => NFData (Discrete symbol) Source # | |
(Show symbol, Ord symbol) => Show (Discrete symbol) Source # | |
newtype Trained (Discrete symbol) sh prob Source # | |
Defined in Math.HiddenMarkovModel.Distribution | |
newtype T (Discrete symbol) sh prob Source # | |
type Emission (Discrete symbol) prob Source # | |
Defined in Math.HiddenMarkovModel.Distribution |
discreteFromList :: (Ord symbol, C sh, Eq sh, Real prob) => T [] (symbol, Vector sh prob) -> T (Discrete symbol) sh prob Source #
Instances
emiSh ~ ShapeInt => FromCSV (Gaussian emiSh) Source # | |
Indexed emiSh => ToCSV (Gaussian emiSh) Source # | |
(C emiSh, Eq emiSh) => Estimate (Gaussian emiSh) Source # | |
Defined in Math.HiddenMarkovModel.Distribution accumulateEmissions :: (Indexed sh, Real prob, Index sh ~ state) => sh -> T [] (state, Emission (Gaussian emiSh) prob) -> Trained (Gaussian emiSh) sh prob Source # trainVector :: (C sh, Eq sh, Real prob) => Emission (Gaussian emiSh) prob -> Vector sh prob -> Trained (Gaussian emiSh) sh prob Source # combine :: (C sh, Eq sh, Real prob) => Trained (Gaussian emiSh) sh prob -> Trained (Gaussian emiSh) sh prob -> Trained (Gaussian emiSh) sh prob Source # normalize :: (C sh, Eq sh, Real prob) => Trained (Gaussian emiSh) sh prob -> T (Gaussian emiSh) sh prob Source # | |
(C emiSh, Eq emiSh) => EmissionProb (Gaussian emiSh) Source # | |
Defined in Math.HiddenMarkovModel.Distribution mapStatesShape :: (C sh0, C sh1) => (sh0 -> sh1) -> T (Gaussian emiSh) sh0 prob -> T (Gaussian emiSh) sh1 prob Source # emissionProb :: (C sh, Real prob) => T (Gaussian emiSh) sh prob -> Emission (Gaussian emiSh) prob -> Vector sh prob Source # emissionStateProb :: (Indexed sh, Real prob) => T (Gaussian emiSh) sh prob -> Emission (Gaussian emiSh) prob -> Index sh -> prob Source # | |
(C emiSh, Eq emiSh) => Generate (Gaussian emiSh) Source # | |
Info (Gaussian emiSh) Source # | |
Defined in Math.HiddenMarkovModel.Distribution | |
FormatArray emiSh => Format (Gaussian emiSh) Source # | |
NFData emiSh => NFData (Gaussian emiSh) Source # | |
(C emiSh, Show emiSh) => Show (Gaussian emiSh) Source # | |
newtype Trained (Gaussian emiSh) stateSh a Source # | |
Defined in Math.HiddenMarkovModel.Distribution | |
newtype T (Gaussian emiSh) stateSh a Source # | |
type Emission (Gaussian emiSh) a Source # | |
Defined in Math.HiddenMarkovModel.Distribution |
gaussian :: (C emiSh, C stateSh, Real prob) => Array stateSh (Vector emiSh prob, Hermitian emiSh prob) -> T (Gaussian emiSh) stateSh prob Source #
gaussianTrained :: (C emiSh, Eq emiSh, C stateSh, Real prob) => Array stateSh (prob, Vector emiSh prob, Hermitian emiSh prob) -> Trained (Gaussian emiSh) stateSh prob Source #
input array must be non-empty
class Ord symbol => CSVSymbol symbol where Source #
cellFromSymbol :: symbol -> String Source #
symbolFromCell :: String -> Maybe symbol Source #
Instances
CSVSymbol Char Source # | |
Defined in Math.HiddenMarkovModel.Distribution | |
CSVSymbol Int Source # | |
Defined in Math.HiddenMarkovModel.Distribution | |
CSVSymbol Color Source # | Using |