BiobaseXNA-0.9.3.1: Efficient RNA/DNA representations

Safe HaskellNone
LanguageHaskell2010

Biobase.Secondary.Basepair

Contents

Description

Secondary structure: define basepairs as Int-tuples, the three edges, a nucleotide can use for pairing and the cis/trans isomerism. Both edges and cis/trans come with a tag for "unknown".

TODO set ext-annotations to be (isomerism,edge,edge) and have a asString instance to read "cWW" "tSH" and other notation.

Synopsis

Newtypes for extended secondary structures

Encode which of three edges is engaged in base pairing

newtype Edge Source #

Each nucleotide in a pair may be paired using one of three edges: watson-crick, sugar, or hoogsteen.

Constructors

Edge 

Fields

Instances

Bounded Edge Source # 
Enum Edge Source # 

Methods

succ :: Edge -> Edge #

pred :: Edge -> Edge #

toEnum :: Int -> Edge #

fromEnum :: Edge -> Int #

enumFrom :: Edge -> [Edge] #

enumFromThen :: Edge -> Edge -> [Edge] #

enumFromTo :: Edge -> Edge -> [Edge] #

enumFromThenTo :: Edge -> Edge -> Edge -> [Edge] #

Eq Edge Source # 

Methods

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

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

Ord Edge Source # 

Methods

compare :: Edge -> Edge -> Ordering #

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

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

(>) :: Edge -> Edge -> Bool #

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

max :: Edge -> Edge -> Edge #

min :: Edge -> Edge -> Edge #

Read Edge Source #

Human-readable Read instance.

Show Edge Source #

Human-readable Show instance.

Methods

showsPrec :: Int -> Edge -> ShowS #

show :: Edge -> String #

showList :: [Edge] -> ShowS #

Ix Edge Source # 

Methods

range :: (Edge, Edge) -> [Edge] #

index :: (Edge, Edge) -> Edge -> Int #

unsafeIndex :: (Edge, Edge) -> Edge -> Int

inRange :: (Edge, Edge) -> Edge -> Bool #

rangeSize :: (Edge, Edge) -> Int #

unsafeRangeSize :: (Edge, Edge) -> Int

Generic Edge Source # 

Associated Types

type Rep Edge :: * -> * #

Methods

from :: Edge -> Rep Edge x #

to :: Rep Edge x -> Edge #

ToJSON Edge Source # 
FromJSON Edge Source # 
Binary Edge Source # 

Methods

put :: Edge -> Put #

get :: Get Edge #

putList :: [Edge] -> Put #

Serialize Edge Source # 

Methods

put :: Putter Edge #

get :: Get Edge #

Unbox Edge Source # 
IsostericityLookup ExtPair Source #

For extended basepairs, we take the default mapping and go from there.

TODO inClass missing

Vector Vector Edge Source # 
MVector MVector Edge Source # 
RemovePseudoKnots [ExtPairIdx] Source # 
RemovePseudoKnots (Vector ExtPairIdx) Source #

Remove pseudoknotted pairs from extended RNA secondary structures.

MkD2Secondary (Int, [ExtPairIdx]) Source # 
BaseSelect ((a, a), ExtPairAnnotation) a Source #

extended pairtype annotation given

Methods

baseL :: ((a, a), ExtPairAnnotation) -> a Source #

baseR :: ((a, a), ExtPairAnnotation) -> a Source #

baseP :: ((a, a), ExtPairAnnotation) -> (a, a) Source #

baseT :: ((a, a), ExtPairAnnotation) -> ExtPairAnnotation Source #

updL :: a -> ((a, a), ExtPairAnnotation) -> ((a, a), ExtPairAnnotation) Source #

updR :: a -> ((a, a), ExtPairAnnotation) -> ((a, a), ExtPairAnnotation) Source #

updP :: (a, a) -> ((a, a), ExtPairAnnotation) -> ((a, a), ExtPairAnnotation) Source #

updT :: ExtPairAnnotation -> ((a, a), ExtPairAnnotation) -> ((a, a), ExtPairAnnotation) Source #

type Rep Edge Source # 
type Rep Edge = D1 (MetaData "Edge" "Biobase.Secondary.Basepair" "BiobaseXNA-0.9.3.1-GowCVjd9NVABe39cHSIsJW" True) (C1 (MetaCons "Edge" PrefixI True) (S1 (MetaSel (Just Symbol "unEdge") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector Edge Source # 
data MVector s Edge Source # 

pattern W :: Edge Source #

pattern S :: Edge Source #

pattern H :: Edge Source #

Is the base pair in cis or trans configuration

newtype CTisomerism Source #

Nucleotides in a pairing may be in the cis(==?) or trans(==?) state.

Constructors

CT 

Fields

Instances

Bounded CTisomerism Source # 
Enum CTisomerism Source # 
Eq CTisomerism Source # 
Ord CTisomerism Source # 
Read CTisomerism Source #

Human-readable Read instance.

Show CTisomerism Source #

Human-readable Show instance.

Ix CTisomerism Source # 
Generic CTisomerism Source # 

Associated Types

type Rep CTisomerism :: * -> * #

ToJSON CTisomerism Source # 
FromJSON CTisomerism Source # 
Binary CTisomerism Source # 
Serialize CTisomerism Source # 
Unbox CTisomerism Source # 
IsostericityLookup ExtPair Source #

For extended basepairs, we take the default mapping and go from there.

TODO inClass missing

Vector Vector CTisomerism Source # 
MVector MVector CTisomerism Source # 
RemovePseudoKnots [ExtPairIdx] Source # 
RemovePseudoKnots (Vector ExtPairIdx) Source #

Remove pseudoknotted pairs from extended RNA secondary structures.

MkD2Secondary (Int, [ExtPairIdx]) Source # 
BaseSelect ((a, a), ExtPairAnnotation) a Source #

extended pairtype annotation given

Methods

baseL :: ((a, a), ExtPairAnnotation) -> a Source #

baseR :: ((a, a), ExtPairAnnotation) -> a Source #

baseP :: ((a, a), ExtPairAnnotation) -> (a, a) Source #

baseT :: ((a, a), ExtPairAnnotation) -> ExtPairAnnotation Source #

updL :: a -> ((a, a), ExtPairAnnotation) -> ((a, a), ExtPairAnnotation) Source #

updR :: a -> ((a, a), ExtPairAnnotation) -> ((a, a), ExtPairAnnotation) Source #

updP :: (a, a) -> ((a, a), ExtPairAnnotation) -> ((a, a), ExtPairAnnotation) Source #

updT :: ExtPairAnnotation -> ((a, a), ExtPairAnnotation) -> ((a, a), ExtPairAnnotation) Source #

type Rep CTisomerism Source # 
type Rep CTisomerism = D1 (MetaData "CTisomerism" "Biobase.Secondary.Basepair" "BiobaseXNA-0.9.3.1-GowCVjd9NVABe39cHSIsJW" True) (C1 (MetaCons "CT" PrefixI True) (S1 (MetaSel (Just Symbol "unCT") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector CTisomerism Source # 
data MVector s CTisomerism Source # 

pattern Cis :: CTisomerism Source #

pattern Trn :: CTisomerism Source #

Types

type PairIdx = (Int, Int) Source #

A basepair is simply a pair of Ints which are 0-indexing a sequence.

type Pair = (Letter RNA, Letter RNA) Source #

A pair as a tuple containing Nucs.

type ExtPairAnnotation = (CTisomerism, Edge, Edge) Source #

Annotation for a basepair.

type ExtPairIdx = (PairIdx, ExtPairAnnotation) Source #

An extended basepair is a basepair, annotated with edge and CTisomerism.

type ExtPair = (Pair, ExtPairAnnotation) Source #

An extended basepair, with nucleotides an annotation.

little helpers

pattern CHH :: (CTisomerism, Edge, Edge) Source #

pattern CHS :: (CTisomerism, Edge, Edge) Source #

pattern CHW :: (CTisomerism, Edge, Edge) Source #

pattern CSH :: (CTisomerism, Edge, Edge) Source #

pattern CSS :: (CTisomerism, Edge, Edge) Source #

pattern CSW :: (CTisomerism, Edge, Edge) Source #

pattern CWH :: (CTisomerism, Edge, Edge) Source #

pattern CWS :: (CTisomerism, Edge, Edge) Source #

pattern CWW :: (CTisomerism, Edge, Edge) Source #

pattern THH :: (CTisomerism, Edge, Edge) Source #

pattern THS :: (CTisomerism, Edge, Edge) Source #

pattern THW :: (CTisomerism, Edge, Edge) Source #

pattern TSH :: (CTisomerism, Edge, Edge) Source #

pattern TSS :: (CTisomerism, Edge, Edge) Source #

pattern TSW :: (CTisomerism, Edge, Edge) Source #

pattern TWH :: (CTisomerism, Edge, Edge) Source #

pattern TWS :: (CTisomerism, Edge, Edge) Source #

pattern TWW :: (CTisomerism, Edge, Edge) Source #

tuple-like selection

class BaseSelect a b | a -> b where Source #

Selection of nucleotides and/or type classes independent of which type we are looking at.

Minimal complete definition

baseL, baseR, baseP, baseT, updL, updR, updP, updT

Methods

baseL :: a -> b Source #

select first index or nucleotide

baseR :: a -> b Source #

select second index or nucleotide

baseP :: a -> (b, b) Source #

select both nucleotides as pair

baseT :: a -> ExtPairAnnotation Source #

select basepair type if existing or return default cWW

updL :: b -> a -> a Source #

update first index or nucleotide

updR :: b -> a -> a Source #

update second index or nucleotide

updP :: (b, b) -> a -> a Source #

update complete pair

updT :: ExtPairAnnotation -> a -> a Source #

update basepair type, error if not possible due to type a

Instances

BaseSelect ((a, a), ExtPairAnnotation) a Source #

extended pairtype annotation given

Methods

baseL :: ((a, a), ExtPairAnnotation) -> a Source #

baseR :: ((a, a), ExtPairAnnotation) -> a Source #

baseP :: ((a, a), ExtPairAnnotation) -> (a, a) Source #

baseT :: ((a, a), ExtPairAnnotation) -> ExtPairAnnotation Source #

updL :: a -> ((a, a), ExtPairAnnotation) -> ((a, a), ExtPairAnnotation) Source #

updR :: a -> ((a, a), ExtPairAnnotation) -> ((a, a), ExtPairAnnotation) Source #

updP :: (a, a) -> ((a, a), ExtPairAnnotation) -> ((a, a), ExtPairAnnotation) Source #

updT :: ExtPairAnnotation -> ((a, a), ExtPairAnnotation) -> ((a, a), ExtPairAnnotation) Source #

BaseSelect (a, a) a Source #

simple cis/wc-wc basepairs

Methods

baseL :: (a, a) -> a Source #

baseR :: (a, a) -> a Source #

baseP :: (a, a) -> (a, a) Source #

baseT :: (a, a) -> ExtPairAnnotation Source #

updL :: a -> (a, a) -> (a, a) Source #

updR :: a -> (a, a) -> (a, a) Source #

updP :: (a, a) -> (a, a) -> (a, a) Source #

updT :: ExtPairAnnotation -> (a, a) -> (a, a) Source #