BiobaseXNA-0.11.0.0: Efficient RNA/DNA/Protein Primary/Secondary Structure

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".

Since we often want to make "pairedness" explicit, we have a newtype for this as well.

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

Synopsis

Newtype for efficient basepair encoding.

newtype Basepair Source #

Encode a base pair as a single Int.

Constructors

BP 

Fields

Instances
Eq Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Ord Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Ix Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Generic Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Associated Types

type Rep Basepair :: Type -> Type #

Methods

from :: Basepair -> Rep Basepair x #

to :: Rep Basepair x -> Basepair #

Index Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Associated Types

data LimitType Basepair :: Type #

IndexStream Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

ToJSON Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

FromJSON Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Binary Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Methods

put :: Basepair -> Put #

get :: Get Basepair #

putList :: [Basepair] -> Put #

Serialize Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Unbox Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Vector Vector Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

MVector MVector Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

BasepairConvert Basepair ViennaPair Source # 
Instance details

Defined in Biobase.Secondary.Convert

BasepairConvert ViennaPair Basepair Source # 
Instance details

Defined in Biobase.Secondary.Convert

BasepairConvert Basepair (Letter RNA n, Letter RNA n) Source # 
Instance details

Defined in Biobase.Secondary.Convert

IndexStream z => IndexStream (z :. Basepair) Source # 
Instance details

Defined in Biobase.Secondary.Basepair

BasepairConvert (Letter RNA n, Letter RNA n) Basepair Source # 
Instance details

Defined in Biobase.Secondary.Convert

type Rep Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

type Rep Basepair = D1 (MetaData "Basepair" "Biobase.Secondary.Basepair" "BiobaseXNA-0.11.0.0-6sSV7wA2ZNJ62zYFxZDZpd" True) (C1 (MetaCons "BP" PrefixI True) (S1 (MetaSel (Just "getBP") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
newtype LimitType Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

newtype Vector Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

newtype MVector s Basepair Source # 
Instance details

Defined in Biobase.Secondary.Basepair

pattern AA :: Basepair Source #

pattern AC :: Basepair Source #

pattern AG :: Basepair Source #

pattern AU :: Basepair Source #

pattern CA :: Basepair Source #

pattern CC :: Basepair Source #

pattern CG :: Basepair Source #

pattern CU :: Basepair Source #

pattern GA :: Basepair Source #

pattern GC :: Basepair Source #

pattern GG :: Basepair Source #

pattern GU :: Basepair Source #

pattern UA :: Basepair Source #

pattern UC :: Basepair Source #

pattern UG :: Basepair Source #

pattern UU :: Basepair Source #

pattern NS :: Basepair Source #

pattern NoBP :: Basepair Source #

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 # 
Instance details

Defined in Biobase.Secondary.Basepair

Enum Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

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 # 
Instance details

Defined in Biobase.Secondary.Basepair

Methods

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

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

Ord Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

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.

Instance details

Defined in Biobase.Secondary.Basepair

Show Edge Source #

Human-readable Show instance.

Instance details

Defined in Biobase.Secondary.Basepair

Methods

showsPrec :: Int -> Edge -> ShowS #

show :: Edge -> String #

showList :: [Edge] -> ShowS #

Ix Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

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 # 
Instance details

Defined in Biobase.Secondary.Basepair

Associated Types

type Rep Edge :: Type -> Type #

Methods

from :: Edge -> Rep Edge x #

to :: Rep Edge x -> Edge #

ToJSON Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

FromJSON Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Binary Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Methods

put :: Edge -> Put #

get :: Get Edge #

putList :: [Edge] -> Put #

Serialize Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Methods

put :: Putter Edge #

get :: Get Edge #

Unbox Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Vector Vector Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

MVector MVector Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

RemovePseudoKnots [ExtPairIdx] Source # 
Instance details

Defined in Biobase.Secondary.Pseudoknots

RemovePseudoKnots (Vector ExtPairIdx) Source #

Remove pseudoknotted pairs from extended RNA secondary structures.

Instance details

Defined in Biobase.Secondary.Pseudoknots

MkD2Secondary (Int, [ExtPairIdx]) Source # 
Instance details

Defined in Biobase.Secondary.Diagrams

IsostericityLookup (ExtPair n) Source #

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

TODO inClass missing

Instance details

Defined in Biobase.Secondary.Isostericity

type Rep Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

type Rep Edge = D1 (MetaData "Edge" "Biobase.Secondary.Basepair" "BiobaseXNA-0.11.0.0-6sSV7wA2ZNJ62zYFxZDZpd" True) (C1 (MetaCons "Edge" PrefixI True) (S1 (MetaSel (Just "unEdge") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
newtype Vector Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

newtype MVector s Edge Source # 
Instance details

Defined in Biobase.Secondary.Basepair

newtype MVector s Edge = MV_Edge (MVector s Int)

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 # 
Instance details

Defined in Biobase.Secondary.Basepair

Enum CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Eq CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Ord CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Read CTisomerism Source #

Human-readable Read instance.

Instance details

Defined in Biobase.Secondary.Basepair

Show CTisomerism Source #

Human-readable Show instance.

Instance details

Defined in Biobase.Secondary.Basepair

Ix CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Generic CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Associated Types

type Rep CTisomerism :: Type -> Type #

ToJSON CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

FromJSON CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Binary CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Serialize CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Unbox CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

Vector Vector CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

MVector MVector CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

RemovePseudoKnots [ExtPairIdx] Source # 
Instance details

Defined in Biobase.Secondary.Pseudoknots

RemovePseudoKnots (Vector ExtPairIdx) Source #

Remove pseudoknotted pairs from extended RNA secondary structures.

Instance details

Defined in Biobase.Secondary.Pseudoknots

MkD2Secondary (Int, [ExtPairIdx]) Source # 
Instance details

Defined in Biobase.Secondary.Diagrams

IsostericityLookup (ExtPair n) Source #

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

TODO inClass missing

Instance details

Defined in Biobase.Secondary.Isostericity

type Rep CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

type Rep CTisomerism = D1 (MetaData "CTisomerism" "Biobase.Secondary.Basepair" "BiobaseXNA-0.11.0.0-6sSV7wA2ZNJ62zYFxZDZpd" True) (C1 (MetaCons "CT" PrefixI True) (S1 (MetaSel (Just "unCT") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
newtype Vector CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

newtype MVector s CTisomerism Source # 
Instance details

Defined in Biobase.Secondary.Basepair

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 n = (Letter RNA n, Letter RNA n) 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 n = (Pair n, 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 #