MutationOrder-0.0.0.2: Most likely order of mutation events in RNA

Safe HaskellNone
LanguageHaskell2010

BioInf.MutationOrder

Description

Run all steps of the HoxCluster algorithms in order.

This will produce the following:

  1. run the minimal distance algorithm, give the minimal distance score and return all co-optimal paths
  2. run the end-probability algorithm and return the probability that each node is the begin/end of a chain
  3. run the edge probability algorithm and give the probability for each from :-> to edge
  4. with the edge probabilities, run the maximal probability path algorithm, return that probability and all co-optimal paths

TODO -Pretty should yield a structure to be given to the eps or svg generator. This allows more flexibility. Does diagrams offer serialization?

TODO All this should be wrapped and available as a function. not just providing output files.

Synopsis

Documentation

mfeDelta :: ScaleFunction Source #

Scale function for normal mfe delta energies

centroidDelta :: ScaleFunction Source #

Scale function for normal centroid delta energies

squaredPositive :: ScaleFunction -> ScaleFunction Source #

Square positive "contributions", making bad moves more unlikely

scaleTemperature :: Double -> ScaleFunction -> ScaleFunction Source #

Scale by temperature (for probability stuff)

scaleByFunction :: (t3 -> t2) -> (t1 -> t -> t3) -> t1 -> t -> t2 Source #

stupidReader :: FilePath -> IO ByteString Source #

Basepair distance

Stupid fasta reader

withDumpFile Source #

Arguments

:: Handle 
-> FilePath

The path we store the serialized and compressed dump in

-> ByteString

ancestral / origin sequence

-> ByteString

destination sequence

-> Landscape

the element which is to be serialized in the dump, or which would be the data in the dump

-> IO Landscape

the data we put in, but maybe taken from the dump file

withDumpFile is like idIO :: a -> IO a in that it returns the data we give to the function. However, in case the dump file exists, we read it and return its contents, instead of recalculating. If it does not exist, we dump the data in addition to returning it. This forces the Landscape.

data FillWeight :: * #

Fill weight for our grid. If the fill weight is logarithmic, then the line length is 1 / (1 + log value) otherwise it is value.

Constructors

FWlog 
FWlinear 
FWfill 

Instances

Eq FillWeight 
Data FillWeight 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FillWeight -> c FillWeight #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FillWeight #

toConstr :: FillWeight -> Constr #

dataTypeOf :: FillWeight -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FillWeight) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FillWeight) #

gmapT :: (forall b. Data b => b -> b) -> FillWeight -> FillWeight #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FillWeight -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FillWeight -> r #

gmapQ :: (forall d. Data d => d -> u) -> FillWeight -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FillWeight -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FillWeight -> m FillWeight #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FillWeight -> m FillWeight #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FillWeight -> m FillWeight #

Show FillWeight 

data FillStyle :: * #

Instances

Eq FillStyle 
Data FillStyle 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FillStyle -> c FillStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FillStyle #

toConstr :: FillStyle -> Constr #

dataTypeOf :: FillStyle -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FillStyle) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FillStyle) #

gmapT :: (forall b. Data b => b -> b) -> FillStyle -> FillStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FillStyle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FillStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> FillStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FillStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FillStyle -> m FillStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FillStyle -> m FillStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FillStyle -> m FillStyle #

Show FillStyle 

type ScaleFunction = RNA -> RNA -> Double Source #

Given the RNA we come from and the RNA we mutate into, derive the gain or loss by a scaling function.