BiobaseTypes-0.1.3.0: Collection of types for bioinformatics

Safe HaskellNone
LanguageHaskell2010

Biobase.Types.Structure

Description

Wrappers for structural data. Encoded as bytestrings. This differs from BiobaseXNA, where specialized encodings are used. These structures are supposedly "short", they need to fit into a strict bytestring.

TODO Consider where to move each type. There are merge possibilities between BiobaseXNA and BiobaseTypes.

Synopsis

Documentation

newtype RNAss Source #

Secondary structure using () for paired elements, and . for unpaired ones. It is assumed that the () match up. These structures from a Monoid.

Constructors

RNAss 

Fields

Instances

Eq RNAss Source # 

Methods

(==) :: RNAss -> RNAss -> Bool #

(/=) :: RNAss -> RNAss -> Bool #

Data RNAss Source # 

Methods

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

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

toConstr :: RNAss -> Constr #

dataTypeOf :: RNAss -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RNAss Source # 

Methods

compare :: RNAss -> RNAss -> Ordering #

(<) :: RNAss -> RNAss -> Bool #

(<=) :: RNAss -> RNAss -> Bool #

(>) :: RNAss -> RNAss -> Bool #

(>=) :: RNAss -> RNAss -> Bool #

max :: RNAss -> RNAss -> RNAss #

min :: RNAss -> RNAss -> RNAss #

Read RNAss Source # 
Show RNAss Source # 

Methods

showsPrec :: Int -> RNAss -> ShowS #

show :: RNAss -> String #

showList :: [RNAss] -> ShowS #

Generic RNAss Source # 

Associated Types

type Rep RNAss :: * -> * #

Methods

from :: RNAss -> Rep RNAss x #

to :: Rep RNAss x -> RNAss #

Monoid RNAss Source # 

Methods

mempty :: RNAss #

mappend :: RNAss -> RNAss -> RNAss #

mconcat :: [RNAss] -> RNAss #

NFData RNAss Source # 

Methods

rnf :: RNAss -> () #

type Rep RNAss Source # 
type Rep RNAss = D1 (MetaData "RNAss" "Biobase.Types.Structure" "BiobaseTypes-0.1.3.0-7EMqsaldKh99G4UiC4Kzi1" True) (C1 (MetaCons "RNAss" PrefixI True) (S1 (MetaSel (Just Symbol "_rnass") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

newtype RNAensembleStructure Source #

Ensemble structure encoding. *Very* different type ctor name chosen! The structure of this string makes verification much more complicated.

TODO describe encoding used by RNAfold for the ensemble string.

Constructors

RNAes 

Fields

Instances

Eq RNAensembleStructure Source # 
Data RNAensembleStructure Source # 

Methods

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

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

toConstr :: RNAensembleStructure -> Constr #

dataTypeOf :: RNAensembleStructure -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RNAensembleStructure Source # 
Read RNAensembleStructure Source # 
Show RNAensembleStructure Source # 
Generic RNAensembleStructure Source # 
NFData RNAensembleStructure Source # 

Methods

rnf :: RNAensembleStructure -> () #

type Rep RNAensembleStructure Source # 
type Rep RNAensembleStructure = D1 (MetaData "RNAensembleStructure" "Biobase.Types.Structure" "BiobaseTypes-0.1.3.0-7EMqsaldKh99G4UiC4Kzi1" True) (C1 (MetaCons "RNAes" PrefixI True) (S1 (MetaSel (Just Symbol "_rnaes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

data RNAds Source #

Cofolded structure.

Constructors

RNAds 

Instances

Eq RNAds Source # 

Methods

(==) :: RNAds -> RNAds -> Bool #

(/=) :: RNAds -> RNAds -> Bool #

Data RNAds Source # 

Methods

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

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

toConstr :: RNAds -> Constr #

dataTypeOf :: RNAds -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RNAds Source # 

Methods

compare :: RNAds -> RNAds -> Ordering #

(<) :: RNAds -> RNAds -> Bool #

(<=) :: RNAds -> RNAds -> Bool #

(>) :: RNAds -> RNAds -> Bool #

(>=) :: RNAds -> RNAds -> Bool #

max :: RNAds -> RNAds -> RNAds #

min :: RNAds -> RNAds -> RNAds #

Read RNAds Source # 
Show RNAds Source # 

Methods

showsPrec :: Int -> RNAds -> ShowS #

show :: RNAds -> String #

showList :: [RNAds] -> ShowS #

Generic RNAds Source # 

Associated Types

type Rep RNAds :: * -> * #

Methods

from :: RNAds -> Rep RNAds x #

to :: Rep RNAds x -> RNAds #

NFData RNAds Source # 

Methods

rnf :: RNAds -> () #

type Rep RNAds Source # 
type Rep RNAds = D1 (MetaData "RNAds" "Biobase.Types.Structure" "BiobaseTypes-0.1.3.0-7EMqsaldKh99G4UiC4Kzi1" False) (C1 (MetaCons "RNAds" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rnadsL") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 ByteString)) (S1 (MetaSel (Just Symbol "_rnadsR") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 ByteString))))

rnads :: Prism' ByteString RNAds Source #

A Prism that turns ByteStrings with a single & into RNAds.

rnads2rnassPair :: Iso' RNAds (RNAss, RNAss) Source #

Isomorphism from RNAds to (RNAss,RNAss). The RNAss are only legal if taken both: rnassFromDimer . both.

mkRNAds :: (Monad m, MonadError RNAStructureError m) => ByteString -> m RNAds Source #

Try to create a dimeric structure.

data RNAStructureError Source #

Capture what might be wrong with the RNAss.

verifyRNAss :: (Monad m, MonadError RNAStructureError m) => RNAss -> m RNAss Source #

Verifies that the given RNAss is properly formatted. Otherwise, error out.

TODO Implement! Check with BiobaseXNA and the stack effort in there. This might influence if the verification goes into BiobaseXNA and happens via an Iso'.

newtype RNApset Source #

Constructors

RNApset 

Fields

Instances

Eq RNApset Source # 

Methods

(==) :: RNApset -> RNApset -> Bool #

(/=) :: RNApset -> RNApset -> Bool #

Ord RNApset Source # 
Read RNApset Source # 
Show RNApset Source # 
Generic RNApset Source # 

Associated Types

type Rep RNApset :: * -> * #

Methods

from :: RNApset -> Rep RNApset x #

to :: Rep RNApset x -> RNApset #

NFData RNApset Source # 

Methods

rnf :: RNApset -> () #

type Rep RNApset Source # 
type Rep RNApset = D1 (MetaData "RNApset" "Biobase.Types.Structure" "BiobaseTypes-0.1.3.0-7EMqsaldKh99G4UiC4Kzi1" True) (C1 (MetaCons "RNApset" PrefixI True) (S1 (MetaSel (Just Symbol "_rnapset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (Int, Int)))))

rnassPairSet :: MonadError String m => RNAss -> m RNApset Source #

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

rnassPairSet' :: RNAss -> RNApset Source #

RNA pair set, but a transformation error calls error.

pairDist :: RNApset -> RNApset -> Int Source #

Calculates the number of different base pairs betwwen two structures.