Biobase.Infernal.CM
Contents
- data CM n s = CM {}
- data Node n = Node {}
- data State s = State {}
- data CMType
- data Emission
- = EmitS {
- eNuc :: Nucleotide
- escore :: Double
- | EmitP {
- eNucL :: Nucleotide
- eNucR :: Nucleotide
- escore :: Double
- = EmitS {
- data Transition
- data NodeType
- data StateType
- cmMakeLocal :: Double -> Double -> CM n s -> CM n s
- cmMakeLocalBegin :: Double -> CM n s -> CM n s
- cmMakeLocalEnd :: Double -> CM n s -> CM n s
- cmScore2Prob :: CM n s -> CM n s
- cmProb2Score :: CM n s -> CM n s
- cmNormalizeProbabilities :: CM n s -> CM n s
- statesScore2Prob :: CM n s -> Array Int (State s) -> Array Int (State s)
- localBeginScore2Prob :: Array Int Double -> Array Int Double
- localEndScore2Prob :: Array Int Double -> Array Int Double
- statesProb2Score :: CM n s -> Array Int (State s) -> Array Int (State s)
- localBeginProb2Score :: Array Int Double -> Array Int Double
- localEndProb2Score :: Array Int Double -> Array Int Double
- nodeMainState :: CM n s -> Node n -> State s
- localBeginPossible :: CM n s -> Node n -> Bool
- localEndPossible :: CM n s -> Node n -> Bool
- stateScore2Prob :: CM n s -> State s -> State s
- stateProb2Score :: CM n s -> State s -> State s
- transitionTargets :: [Transition] -> [Int]
- nodeMainStateAssocs :: [(NodeType, StateType)]
Data types for Covariance Models
A complete covariance model. Each node and each state can be tagged with additional data. Typically, say after parsing, the tag will be ().
Constructors
CM | |
Describes one node
Constructors
Node | |
One state
Constructors
State | |
CMType is important if we want to set localBegin / localEnd!
can emit either one nucleotide or a pair
Constructors
EmitS | |
Fields
| |
EmitP | |
Fields
|
data Transition Source
branches are transition without attached probability becaue both branches are always taken
Instances
the different node types
the different state types
make a local model out of a global one
cmMakeLocal :: Double -> Double -> CM n s -> CM n sSource
generate a local model with local begin prob and local end prob
cmMakeLocalBegin :: Double -> CM n s -> CM n sSource
cmMakeLocalEnd :: Double -> CM n s -> CM n sSource
Transform between score and probability mode
cmScore2Prob :: CM n s -> CM n sSource
given a CM in score mode, change it to probability mode
cmProb2Score :: CM n s -> CM n sSource
Given a CM in prob mode, change to score mode
cmNormalizeProbabilities :: CM n s -> CM n sSource
normalize all PROBabilities in a CM
Helper Functions
nodeMainState :: CM n s -> Node n -> State sSource
extract the main state for each node (eg MP state for MATP node)
localBeginPossible :: CM n s -> Node n -> BoolSource
Checks for each node, if it can be target of a local begin.
localEndPossible :: CM n s -> Node n -> BoolSource
Checks for each node if it can lead to a local end.
stateScore2Prob :: CM n s -> State s -> State sSource
transform scores into probabilities, given a nullmodel for x
back into scores
Transform a state, setting probabilities instead of scores. Requires CM knowledge for background model.
stateProb2Score :: CM n s -> State s -> State sSource
Transform a state, setting scores instead of probabilities.
transitionTargets :: [Transition] -> [Int]Source