BiobaseXNA-0.9.3.0: Efficient RNA/DNA representations

Safe HaskellNone
LanguageHaskell2010

Biobase.Secondary.Diagrams

Contents

Description

Types for RNA secondary structure. Types vary from the simplest array (D1Secondary) to rather complex ones.

Synopsis

Documentation

newtype D1Secondary Source #

RNA secondary structure with 1-diagrams. Each nucleotide is paired with at most one other nucleotide. A nucleotide with index k in [0..len-1] is paired if unD1S VU.! k >=0 0 Unpaired status is -1.

Constructors

D1S 

Fields

Instances

Eq D1Secondary Source # 
Read D1Secondary Source # 
Show D1Secondary Source # 
Generic D1Secondary Source # 

Associated Types

type Rep D1Secondary :: * -> * #

FromJSON D1Secondary Source # 
ToJSON D1Secondary Source # 
Binary D1Secondary Source # 
Serialize D1Secondary Source # 
MkD2Secondary D1Secondary Source #

Conversion between D1S and D2S is lossy in D2S -> D1S

TODO fromD2S makes me wanna rewrite everything...

type Rep D1Secondary Source # 
type Rep D1Secondary = D1 (MetaData "D1Secondary" "Biobase.Secondary.Diagrams" "BiobaseXNA-0.9.3.0-8oUGCIbMbYx8TN6nAPRU1W" True) (C1 (MetaCons "D1S" PrefixI True) (S1 (MetaSel (Just Symbol "unD1S") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector Int))))

newtype D2Secondary Source #

Constructors

D2S 

Instances

Eq D2Secondary Source # 
Read D2Secondary Source # 
Show D2Secondary Source # 
Generic D2Secondary Source # 

Associated Types

type Rep D2Secondary :: * -> * #

FromJSON D2Secondary Source # 
ToJSON D2Secondary Source # 
Binary D2Secondary Source # 
Serialize D2Secondary Source # 
MkD1Secondary D2Secondary Source #

Conversion between D1S and D2S is lossy in D2S -> D1S

type Rep D2Secondary Source # 
type Rep D2Secondary = D1 (MetaData "D2Secondary" "Biobase.Secondary.Diagrams" "BiobaseXNA-0.9.3.0-8oUGCIbMbYx8TN6nAPRU1W" True) (C1 (MetaCons "D2S" PrefixI True) (S1 (MetaSel (Just Symbol "unD2S") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector ((Int, Edge, CTisomerism), (Int, Edge, CTisomerism))))))

class MkD1Secondary a where Source #

Conversion to and from 1-diagrams.

Minimal complete definition

mkD1S, fromD1S

Instances

MkD1Secondary String Source #

A "fast" instance for getting the pair list of vienna-structures.

MkD1Secondary D2Secondary Source #

Conversion between D1S and D2S is lossy in D2S -> D1S

MkD1Secondary (Vector Char) Source # 
MkD1Secondary (Int, [PairIdx]) Source #

(Length,List of Pairs)

MkD1Secondary ([String], Vector Char) Source #

Generate Secondary given that we have an unboxed vector of characters

MkD1Secondary ([String], String) Source #

A second primitive generator, requiring dictionary and String. This one generates pairs that are then used by the above instance. The dict is a list of possible brackets: ["()"] being the minimal set.

class MkD2Secondary a where Source #

Conversion to and from 2-diagrams.

Minimal complete definition

mkD2S, fromD2S

Instances

MkD2Secondary D1Secondary Source #

Conversion between D1S and D2S is lossy in D2S -> D1S

TODO fromD2S makes me wanna rewrite everything...

MkD2Secondary (Int, [ExtPairIdx]) Source # 

Tree-based representation

data SSTree idx a Source #

A secondary-structure tree. Has no notion of pseudoknots.

Constructors

SSTree idx a [SSTree idx a] 
SSExtern Int a [SSTree idx a] 

Instances

(Eq idx, Eq a) => Eq (SSTree idx a) Source # 

Methods

(==) :: SSTree idx a -> SSTree idx a -> Bool #

(/=) :: SSTree idx a -> SSTree idx a -> Bool #

(Read idx, Read a) => Read (SSTree idx a) Source # 

Methods

readsPrec :: Int -> ReadS (SSTree idx a) #

readList :: ReadS [SSTree idx a] #

readPrec :: ReadPrec (SSTree idx a) #

readListPrec :: ReadPrec [SSTree idx a] #

(Show idx, Show a) => Show (SSTree idx a) Source # 

Methods

showsPrec :: Int -> SSTree idx a -> ShowS #

show :: SSTree idx a -> String #

showList :: [SSTree idx a] -> ShowS #

Generic (SSTree idx a) Source # 

Associated Types

type Rep (SSTree idx a) :: * -> * #

Methods

from :: SSTree idx a -> Rep (SSTree idx a) x #

to :: Rep (SSTree idx a) x -> SSTree idx a #

type Rep (SSTree idx a) Source # 

d1sTree :: D1Secondary -> SSTree PairIdx () Source #

Create a tree from (pseudoknot-free [not checked]) 1-diagrams.

d2sTree :: D2Secondary -> SSTree ExtPairIdx () Source #

Create a tree from (pseudoknot-free [not checked]) 2-diagrams.

d2Compare :: (Ord t3, Ord t2) => ((t2, t3), t) -> ((t2, t3), t1) -> Ordering Source #

d2Grouping :: (Ord a1, Ord a) => ((a, a1), t) -> ((a, a1), t1) -> Bool Source #

Instances for D1S

Instances for D2S

Older instances (should still work)

High-level parsing functionality for secondary structures

isCanonicalStructure :: String -> Bool Source #

Completely canonical structure.

TODO Check size of hairpins and interior loops?

isConstraintStructure :: String -> Bool Source #

Is constraint type structure, i.e. there can also be symbols present that denote up- or downstream pairing.

structures :: Iso' String [String] Source #

Take a structural string and split it into its constituents.

If we decide to NOT depend on lens explicitly, another way to write this is:

structures :: forall p f . (Profunctor p, Functor f) => p [String] (f [String]) -> p String (f String)
structures = dimap (splitOn "&") (fmap (concat . intersperse "&"))

foldStructure :: Prism' String String Source #

A fold structure is a single structure

cofoldStructure :: Prism' String (String, String) Source #

A cofold structure has exactly two structures split by & (which the prism removes).

Helper functions

unsafeDotBracket2pairlist :: [String] -> String -> [(Int, Int)] Source #

Secondary structure parser which allows pseudoknots, if they use different kinds of brackets.

dotBracket2pairlist :: [String] -> String -> Either String [(Int, Int)] Source #

Secondary structure parser with a notion of errors. We either return a Right structure, including flags, or a Left error.

viennaStringDistance :: Bool -> Bool -> String -> String -> (String, Int) Source #

Calculates the distance between two vienna strings.