BiobaseTypes-0.1.4.0: Collection of types for bioinformatics

Safe HaskellNone
LanguageHaskell2010

Biobase.Types.Shape

Contents

Description

Shape abstractions of structures.

Shapes do not preserve sizes of structures (say unpaired regions or stem length). As such, distance measures provided here are to be used carefully!

TODO consider how to handle the different shape levels. One option would be to phantom-type everything.

Synopsis

Documentation

data ShapeLevel Source #

Shape levels are hardcoded according to their specification.

TODO Allow compile-time check on accepted shape levels?

Constructors

SL1 
SL2 
SL3 
SL4 
SL5 
Instances
Eq ShapeLevel Source # 
Instance details

Defined in Biobase.Types.Shape

Data ShapeLevel Source # 
Instance details

Defined in Biobase.Types.Shape

Methods

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

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

toConstr :: ShapeLevel -> Constr #

dataTypeOf :: ShapeLevel -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ShapeLevel Source # 
Instance details

Defined in Biobase.Types.Shape

Read ShapeLevel Source # 
Instance details

Defined in Biobase.Types.Shape

Show ShapeLevel Source # 
Instance details

Defined in Biobase.Types.Shape

Generic ShapeLevel Source # 
Instance details

Defined in Biobase.Types.Shape

Associated Types

type Rep ShapeLevel :: Type -> Type #

NFData ShapeLevel Source # 
Instance details

Defined in Biobase.Types.Shape

Methods

rnf :: ShapeLevel -> () #

type Rep ShapeLevel Source # 
Instance details

Defined in Biobase.Types.Shape

type Rep ShapeLevel = D1 (MetaData "ShapeLevel" "Biobase.Types.Shape" "BiobaseTypes-0.1.4.0-2SJmLmHyrafG90Dl3d2I5j" False) ((C1 (MetaCons "SL1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SL2" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SL3" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SL4" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SL5" PrefixI False) (U1 :: Type -> Type))))

data RNAshape Source #

The type of RNA shapes. Keeps the type

Constructors

RNAshape 

Fields

Instances
Eq RNAshape Source # 
Instance details

Defined in Biobase.Types.Shape

Data RNAshape Source # 
Instance details

Defined in Biobase.Types.Shape

Methods

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

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

toConstr :: RNAshape -> Constr #

dataTypeOf :: RNAshape -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RNAshape Source # 
Instance details

Defined in Biobase.Types.Shape

Read RNAshape Source # 
Instance details

Defined in Biobase.Types.Shape

Show RNAshape Source # 
Instance details

Defined in Biobase.Types.Shape

Generic RNAshape Source # 
Instance details

Defined in Biobase.Types.Shape

Associated Types

type Rep RNAshape :: Type -> Type #

Methods

from :: RNAshape -> Rep RNAshape x #

to :: Rep RNAshape x -> RNAshape #

NFData RNAshape Source # 
Instance details

Defined in Biobase.Types.Shape

Methods

rnf :: RNAshape -> () #

type Rep RNAshape Source # 
Instance details

Defined in Biobase.Types.Shape

type Rep RNAshape = D1 (MetaData "RNAshape" "Biobase.Types.Shape" "BiobaseTypes-0.1.4.0-2SJmLmHyrafG90Dl3d2I5j" False) (C1 (MetaCons "RNAshape" PrefixI True) (S1 (MetaSel (Just "_rnashapelevel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ShapeLevel) :*: S1 (MetaSel (Just "_rnashape") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString)))

shapeForest :: ShapeLevel -> SPForest ByteString ByteString -> SPForest Char Char Source #

Given a compactified SPForest, creates a shape forest of the given level.

TODO needs newtyping

test :: ShapeLevel -> RNAshape Source #

turn into unit test. also reverse of the input should give reverse shape! this then gives a quickcheck test, reversing the input should reverse the shape

TODO requires generating secondary structures via Arbitrary.

Distance measures on the shape string itself.

data RNAshapepset Source #

Wrapper for string-positional shapes. Intentionally chosen long name.

Instances
Eq RNAshapepset Source # 
Instance details

Defined in Biobase.Types.Shape

Ord RNAshapepset Source # 
Instance details

Defined in Biobase.Types.Shape

Read RNAshapepset Source # 
Instance details

Defined in Biobase.Types.Shape

Show RNAshapepset Source # 
Instance details

Defined in Biobase.Types.Shape

Generic RNAshapepset Source # 
Instance details

Defined in Biobase.Types.Shape

Associated Types

type Rep RNAshapepset :: Type -> Type #

NFData RNAshapepset Source # 
Instance details

Defined in Biobase.Types.Shape

Methods

rnf :: RNAshapepset -> () #

type Rep RNAshapepset Source # 
Instance details

Defined in Biobase.Types.Shape

type Rep RNAshapepset = D1 (MetaData "RNAshapepset" "Biobase.Types.Shape" "BiobaseTypes-0.1.4.0-2SJmLmHyrafG90Dl3d2I5j" False) (C1 (MetaCons "RNAshapepset" PrefixI True) (S1 (MetaSel (Just "_rnashapepsetlevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShapeLevel) :*: S1 (MetaSel (Just "_rnashapepset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (Int, Int)))))

rnashapePairSet :: MonadError String m => RNAshape -> m RNAshapepset Source #

Transform an RNAss into a set of base pairs (i,j). The pairs are 0-based.

rnassPairSet' :: RNAshape -> RNAshapepset Source #

RNA pair set, but a transformation error calls error.

shapePairDist :: RNAshapepset -> RNAshapepset -> Int Source #

Calculates the number of different base pairs betwwen two structures.

TODO error out on different shape levels