Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
TODO QuickCheck Arbitrary
for RNAss
.
Synopsis
- newtype RNAss = RNAss {
- _rnass :: ByteString
- rnass :: Iso' RNAss ByteString
- newtype RNAensembleStructure = RNAes {
- _rnaes :: ByteString
- rnaes :: Iso' RNAensembleStructure ByteString
- data RNAds = RNAds {
- _rnadsL :: !ByteString
- _rnadsR :: !ByteString
- rnadsR :: Lens' RNAds ByteString
- rnadsL :: Lens' RNAds ByteString
- rnads :: Prism' ByteString RNAds
- rnads2rnassPair :: Iso' RNAds (RNAss, RNAss)
- mkRNAds :: (Monad m, MonadError RNAStructureError m) => ByteString -> m RNAds
- data RNAStructureError = RNAStructureError {}
- verifyRNAss :: (Monad m, MonadError RNAStructureError m) => RNAss -> m RNAss
- data RNApset = RNApset {}
- rnapsetSLen :: Lens' RNApset Int
- rnapset :: Lens' RNApset (Set (Int, Int))
- rnassPairSet :: MonadError String m => RNAss -> m RNApset
- rnassSPForest :: MonadError String m => RNAss -> m (SPForest ByteString Char)
- compactifySPForest :: SPForest ByteString Char -> SPForest ByteString ByteString
- rnassPairSet' :: RNAss -> RNApset
- rnapsetRNAss :: RNApset -> RNAss
- pairDist :: RNApset -> RNApset -> Int
Documentation
Secondary structure using ()
for paired elements, and .
for unpaired
ones. It is assumed that the ()
match up. These structures from a Monoid.
Instances
Eq RNAss Source # | |
Data RNAss Source # | |
Defined in Biobase.Types.Structure 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 # 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 # | |
Read RNAss Source # | |
Show RNAss Source # | |
Generic RNAss Source # | |
Semigroup RNAss Source # | |
Monoid RNAss Source # | |
Arbitrary RNAss Source # | |
NFData RNAss Source # | |
Defined in Biobase.Types.Structure | |
type Rep RNAss Source # | |
Defined in Biobase.Types.Structure type Rep RNAss = D1 (MetaData "RNAss" "Biobase.Types.Structure" "BiobaseTypes-0.2.0.1-B9coIbijR6NEFcCxvqIOZp" True) (C1 (MetaCons "RNAss" PrefixI True) (S1 (MetaSel (Just "_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.
Instances
Cofolded structure.
RNAds | |
|
Instances
Eq RNAds Source # | |
Data RNAds Source # | |
Defined in Biobase.Types.Structure 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 # 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 # | |
Read RNAds Source # | |
Show RNAds Source # | |
Generic RNAds Source # | |
NFData RNAds Source # | |
Defined in Biobase.Types.Structure | |
type Rep RNAds Source # | |
Defined in Biobase.Types.Structure type Rep RNAds = D1 (MetaData "RNAds" "Biobase.Types.Structure" "BiobaseTypes-0.2.0.1-B9coIbijR6NEFcCxvqIOZp" False) (C1 (MetaCons "RNAds" PrefixI True) (S1 (MetaSel (Just "_rnadsL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString) :*: S1 (MetaSel (Just "_rnadsR") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString))) |
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.
Instances
Show RNAStructureError Source # | |
Defined in Biobase.Types.Structure showsPrec :: Int -> RNAStructureError -> ShowS # show :: RNAStructureError -> String # showList :: [RNAStructureError] -> ShowS # | |
Generic RNAStructureError Source # | |
Defined in Biobase.Types.Structure type Rep RNAStructureError :: Type -> Type # from :: RNAStructureError -> Rep RNAStructureError x # to :: Rep RNAStructureError x -> RNAStructureError # | |
NFData RNAStructureError Source # | |
Defined in Biobase.Types.Structure rnf :: RNAStructureError -> () # | |
type Rep RNAStructureError Source # | |
Defined in Biobase.Types.Structure type Rep RNAStructureError = D1 (MetaData "RNAStructureError" "Biobase.Types.Structure" "BiobaseTypes-0.2.0.1-B9coIbijR6NEFcCxvqIOZp" False) (C1 (MetaCons "RNAStructureError" PrefixI True) (S1 (MetaSel (Just "_rnaStructureError") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "_rnaOffender") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) |
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'
.
The set of nucleotide pairs, together with the sequence length.
Instances
Eq RNApset Source # | |
Ord RNApset Source # | |
Read RNApset Source # | |
Show RNApset Source # | |
Generic RNApset Source # | |
Arbitrary RNApset Source # | |
NFData RNApset Source # | |
Defined in Biobase.Types.Structure | |
type Rep RNApset Source # | |
Defined in Biobase.Types.Structure type Rep RNApset = D1 (MetaData "RNApset" "Biobase.Types.Structure" "BiobaseTypes-0.2.0.1-B9coIbijR6NEFcCxvqIOZp" False) (C1 (MetaCons "RNApset" PrefixI True) (S1 (MetaSel (Just "_rnapset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Set (Int, Int))) :*: S1 (MetaSel (Just "_rnapsetSLen") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 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.
rnassSPForest :: MonadError String m => RNAss -> m (SPForest ByteString Char) Source #
Genereate a simple structured/paired forest from a secondary structure string.
compactifySPForest :: SPForest ByteString Char -> SPForest ByteString ByteString Source #
Compactify such an SPForest. This means that all stems are now represented
by a single SPT
data constructor.
rnassPairSet' :: RNAss -> RNApset Source #
RNA pair set, but a transformation error calls error
.
rnapsetRNAss :: RNApset -> RNAss Source #
pairDist :: RNApset -> RNApset -> Int Source #
Calculates the number of different base pairs between two structures. This ignores the length of the underlying sequences.