Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data ShapeLevel
- data RNAshape = RNAshape {}
- rnashapelevel :: Lens' RNAshape ShapeLevel
- rnashape :: Lens' RNAshape ByteString
- shapeForest :: ShapeLevel -> SPForest ByteString ByteString -> SPForest Char Char
- rnass2shape :: ShapeLevel -> RNAss -> RNAshape
- test :: ShapeLevel -> RNAshape
- shapeForestshape :: ShapeLevel -> SPForest Char Char -> RNAshape
- generateShape :: ShapeLevel -> RNAss -> RNAshape
- data RNAshapepset = RNAshapepset {
- _rnashapepsetlevel :: ShapeLevel
- _rnashapepset :: Set (Int, Int)
- rnashapepsetlevel :: Lens' RNAshapepset ShapeLevel
- rnashapepset :: Lens' RNAshapepset (Set (Int, Int))
- rnashapePairSet :: MonadError String m => RNAshape -> m RNAshapepset
- rnassPairSet' :: RNAshape -> RNAshapepset
- shapePairDist :: RNAshapepset -> RNAshapepset -> Int
Documentation
data ShapeLevel Source #
Shape levels are hardcoded according to their specification.
TODO Allow compile-time check on accepted shape levels?
Instances
The type of RNA shapes. Keeps the type
RNAshape | |
|
Instances
Eq RNAshape Source # | |
Data RNAshape Source # | |
Defined in Biobase.Types.Shape 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 # | |
Defined in Biobase.Types.Shape | |
Read RNAshape Source # | |
Show RNAshape Source # | |
Generic RNAshape Source # | |
NFData RNAshape Source # | |
Defined in Biobase.Types.Shape | |
type Rep RNAshape Source # | |
Defined in Biobase.Types.Shape type Rep RNAshape = D1 (MetaData "RNAshape" "Biobase.Types.Shape" "BiobaseTypes-0.2.0.1-B9coIbijR6NEFcCxvqIOZp" 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
rnass2shape :: ShapeLevel -> RNAss -> RNAshape Source #
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
.
shapeForestshape :: ShapeLevel -> SPForest Char Char -> RNAshape Source #
generateShape :: ShapeLevel -> RNAss -> RNAshape Source #
Distance measures on the shape string itself.
data RNAshapepset Source #
Wrapper for string-positional shapes. Intentionally chosen long name.
Instances
rnashapepset :: Lens' RNAshapepset (Set (Int, Int)) Source #
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