BiobaseTypes-0.2.0.1: Collection of types for bioinformatics

Safe HaskellNone
LanguageHaskell2010

Biobase.Types.BioSequence

Contents

Description

Abstraction over bio sequences encoded as one-ascii character as one symbol. We phantom-type the exact bio-sequence type and provide type classes that act on known types.

Unknown bio sequences should be tagged with Void.

TODO give (lens) usage examples

Synopsis

Sequence identifiers

newtype SequenceIdentifier (which :: k) Source #

Instances
Eq (SequenceIdentifier which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

(Typeable which, Typeable k) => Data (SequenceIdentifier which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SequenceIdentifier which -> c (SequenceIdentifier which) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SequenceIdentifier which) #

toConstr :: SequenceIdentifier which -> Constr #

dataTypeOf :: SequenceIdentifier which -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SequenceIdentifier which)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SequenceIdentifier which)) #

gmapT :: (forall b. Data b => b -> b) -> SequenceIdentifier which -> SequenceIdentifier which #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SequenceIdentifier which -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SequenceIdentifier which -> r #

gmapQ :: (forall d. Data d => d -> u) -> SequenceIdentifier which -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SequenceIdentifier which -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SequenceIdentifier which -> m (SequenceIdentifier which) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SequenceIdentifier which -> m (SequenceIdentifier which) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SequenceIdentifier which -> m (SequenceIdentifier which) #

Ord (SequenceIdentifier which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Read (SequenceIdentifier which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Show (SequenceIdentifier which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

IsString (SequenceIdentifier w) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Generic (SequenceIdentifier which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Associated Types

type Rep (SequenceIdentifier which) :: Type -> Type #

Methods

from :: SequenceIdentifier which -> Rep (SequenceIdentifier which) x #

to :: Rep (SequenceIdentifier which) x -> SequenceIdentifier which #

NFData (SequenceIdentifier w) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

rnf :: SequenceIdentifier w -> () #

Wrapped (SequenceIdentifier which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Associated Types

type Unwrapped (SequenceIdentifier which) :: Type #

SequenceIdentifier which1 ~ t => Rewrapped (SequenceIdentifier which2) t Source # 
Instance details

Defined in Biobase.Types.BioSequence

type Rep (SequenceIdentifier which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

type Rep (SequenceIdentifier which) = D1 (MetaData "SequenceIdentifier" "Biobase.Types.BioSequence" "BiobaseTypes-0.2.0.1-B9coIbijR6NEFcCxvqIOZp" True) (C1 (MetaCons "SequenceIdentifier" PrefixI True) (S1 (MetaSel (Just "_sequenceIdentifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))
type Unwrapped (SequenceIdentifier which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Bio-Sequences

data RNA Source #

Instances
IsString (BioSequence RNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Arbitrary (BioSequence RNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Complement (BioSequence RNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Transcribe (BioSequence RNA) Source #

Transcribe a RNA sequence into an DNA sequence. This does not reverse the sequence!

Instance details

Defined in Biobase.Types.BioSequence

Associated Types

type TranscribeTo (BioSequence RNA) :: Type Source #

type TranscribeTo (BioSequence RNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

data DNA Source #

Instances
IsString (BioSequence DNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Arbitrary (BioSequence DNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Complement (BioSequence DNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Transcribe (BioSequence DNA) Source #

Transcribe a DNA sequence into an RNA sequence. This does not reverse the sequence!

Instance details

Defined in Biobase.Types.BioSequence

Associated Types

type TranscribeTo (BioSequence DNA) :: Type Source #

type TranscribeTo (BioSequence DNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

newtype BioSequence (which :: k) Source #

Constructors

BioSequence 
Instances
Eq (BioSequence which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

(==) :: BioSequence which -> BioSequence which -> Bool #

(/=) :: BioSequence which -> BioSequence which -> Bool #

(Typeable which, Typeable k) => Data (BioSequence which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BioSequence which -> c (BioSequence which) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BioSequence which) #

toConstr :: BioSequence which -> Constr #

dataTypeOf :: BioSequence which -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (BioSequence which)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BioSequence which)) #

gmapT :: (forall b. Data b => b -> b) -> BioSequence which -> BioSequence which #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BioSequence which -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BioSequence which -> r #

gmapQ :: (forall d. Data d => d -> u) -> BioSequence which -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BioSequence which -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BioSequence which -> m (BioSequence which) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BioSequence which -> m (BioSequence which) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BioSequence which -> m (BioSequence which) #

Ord (BioSequence which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

compare :: BioSequence which -> BioSequence which -> Ordering #

(<) :: BioSequence which -> BioSequence which -> Bool #

(<=) :: BioSequence which -> BioSequence which -> Bool #

(>) :: BioSequence which -> BioSequence which -> Bool #

(>=) :: BioSequence which -> BioSequence which -> Bool #

max :: BioSequence which -> BioSequence which -> BioSequence which #

min :: BioSequence which -> BioSequence which -> BioSequence which #

Read (BioSequence which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Show (BioSequence which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

showsPrec :: Int -> BioSequence which -> ShowS #

show :: BioSequence which -> String #

showList :: [BioSequence which] -> ShowS #

IsString (BioSequence Void) Source # 
Instance details

Defined in Biobase.Types.BioSequence

IsString (BioSequence AA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

IsString (BioSequence XNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

IsString (BioSequence DNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

IsString (BioSequence RNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Generic (BioSequence which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Associated Types

type Rep (BioSequence which) :: Type -> Type #

Methods

from :: BioSequence which -> Rep (BioSequence which) x #

to :: Rep (BioSequence which) x -> BioSequence which #

Semigroup (BioSequence which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

(<>) :: BioSequence which -> BioSequence which -> BioSequence which #

sconcat :: NonEmpty (BioSequence which) -> BioSequence which #

stimes :: Integral b => b -> BioSequence which -> BioSequence which #

Arbitrary (BioSequence AA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Arbitrary (BioSequence XNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Arbitrary (BioSequence DNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Arbitrary (BioSequence RNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

NFData (BioSequence w) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

rnf :: BioSequence w -> () #

Ixed (BioSequence w) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Wrapped (BioSequence which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Associated Types

type Unwrapped (BioSequence which) :: Type #

Methods

_Wrapped' :: Iso' (BioSequence which) (Unwrapped (BioSequence which)) #

Reversing (BioSequence w) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Complement (BioSequence DNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Complement (BioSequence RNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Transcribe (BioSequence DNA) Source #

Transcribe a DNA sequence into an RNA sequence. This does not reverse the sequence!

Instance details

Defined in Biobase.Types.BioSequence

Associated Types

type TranscribeTo (BioSequence DNA) :: Type Source #

Transcribe (BioSequence RNA) Source #

Transcribe a RNA sequence into an DNA sequence. This does not reverse the sequence!

Instance details

Defined in Biobase.Types.BioSequence

Associated Types

type TranscribeTo (BioSequence RNA) :: Type Source #

BioSequence which1 ~ t => Rewrapped (BioSequence which2) t Source # 
Instance details

Defined in Biobase.Types.BioSequence

type Rep (BioSequence which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

type Rep (BioSequence which) = D1 (MetaData "BioSequence" "Biobase.Types.BioSequence" "BiobaseTypes-0.2.0.1-B9coIbijR6NEFcCxvqIOZp" True) (C1 (MetaCons "BioSequence" PrefixI True) (S1 (MetaSel (Just "_bioSequence") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))
type Index (BioSequence w) Source # 
Instance details

Defined in Biobase.Types.BioSequence

type Index (BioSequence w) = Int
type IxValue (BioSequence w) Source # 
Instance details

Defined in Biobase.Types.BioSequence

type Unwrapped (BioSequence which) Source # 
Instance details

Defined in Biobase.Types.BioSequence

type TranscribeTo (BioSequence DNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

type TranscribeTo (BioSequence RNA) Source # 
Instance details

Defined in Biobase.Types.BioSequence

_BioSequence :: forall which which. Iso (BioSequence which) (BioSequence which) ByteString ByteString Source #

RNA

mkRNAseq :: ByteString -> BioSequence RNA Source #

TODO write that converts explicitly

DNA

XNA

Amino acid sequences

A window into a longer sequence with prefix/suffix information.

data BioSequenceWindow w ty loc Source #

Phantom-typed over two types, the type w of the identifier, which can be descriptive (FirstInput) and the second type, identifying what kind of sequence types we are dealing with. Finally, the third type provides location information and should be location or streamed location.

Constructors

BioSequenceWindow 

Fields

Instances
Eq loc => Eq (BioSequenceWindow w ty loc) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

(==) :: BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc -> Bool #

(/=) :: BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc -> Bool #

(Typeable w, Typeable ty, Typeable k1, Typeable k2, Data loc) => Data (BioSequenceWindow w ty loc) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BioSequenceWindow w ty loc -> c (BioSequenceWindow w ty loc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BioSequenceWindow w ty loc) #

toConstr :: BioSequenceWindow w ty loc -> Constr #

dataTypeOf :: BioSequenceWindow w ty loc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (BioSequenceWindow w ty loc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BioSequenceWindow w ty loc)) #

gmapT :: (forall b. Data b => b -> b) -> BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BioSequenceWindow w ty loc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BioSequenceWindow w ty loc -> r #

gmapQ :: (forall d. Data d => d -> u) -> BioSequenceWindow w ty loc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BioSequenceWindow w ty loc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BioSequenceWindow w ty loc -> m (BioSequenceWindow w ty loc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BioSequenceWindow w ty loc -> m (BioSequenceWindow w ty loc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BioSequenceWindow w ty loc -> m (BioSequenceWindow w ty loc) #

Ord loc => Ord (BioSequenceWindow w ty loc) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

compare :: BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc -> Ordering #

(<) :: BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc -> Bool #

(<=) :: BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc -> Bool #

(>) :: BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc -> Bool #

(>=) :: BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc -> Bool #

max :: BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc #

min :: BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc #

Read loc => Read (BioSequenceWindow w ty loc) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Show loc => Show (BioSequenceWindow w ty loc) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

showsPrec :: Int -> BioSequenceWindow w ty loc -> ShowS #

show :: BioSequenceWindow w ty loc -> String #

showList :: [BioSequenceWindow w ty loc] -> ShowS #

Generic (BioSequenceWindow w ty loc) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Associated Types

type Rep (BioSequenceWindow w ty loc) :: Type -> Type #

Methods

from :: BioSequenceWindow w ty loc -> Rep (BioSequenceWindow w ty loc) x #

to :: Rep (BioSequenceWindow w ty loc) x -> BioSequenceWindow w ty loc #

Reversing loc => Reversing (BioSequenceWindow w ty loc) Source # 
Instance details

Defined in Biobase.Types.BioSequence

Methods

reversing :: BioSequenceWindow w ty loc -> BioSequenceWindow w ty loc #

Complement (BioSequence ty) => Complement (BioSequenceWindow w ty k3) Source # 
Instance details

Defined in Biobase.Types.BioSequence

type Rep (BioSequenceWindow w ty loc) Source # 
Instance details

Defined in Biobase.Types.BioSequence

type Rep (BioSequenceWindow w ty loc) = D1 (MetaData "BioSequenceWindow" "Biobase.Types.BioSequence" "BiobaseTypes-0.2.0.1-B9coIbijR6NEFcCxvqIOZp" False) (C1 (MetaCons "BioSequenceWindow" PrefixI True) ((S1 (MetaSel (Just "_bswIdentifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (SequenceIdentifier w)) :*: S1 (MetaSel (Just "_bswPrefix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (BioSequence ty))) :*: (S1 (MetaSel (Just "_bswSequence") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (BioSequence ty)) :*: (S1 (MetaSel (Just "_bswSuffix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (BioSequence ty)) :*: S1 (MetaSel (Just "_bswLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 loc)))))

bswSuffix :: forall w ty loc. Lens' (BioSequenceWindow w ty loc) (BioSequence ty) Source #

bswSequence :: forall w ty loc. Lens' (BioSequenceWindow w ty loc) (BioSequence ty) Source #

bswPrefix :: forall w ty loc. Lens' (BioSequenceWindow w ty loc) (BioSequence ty) Source #

bswLocation :: forall w ty loc loc. Lens (BioSequenceWindow w ty loc) (BioSequenceWindow w ty loc) loc loc Source #

bswFullSequence :: Lens' (BioSequenceWindow w ty k) (BioSequence ty) Source #

A lens into the full sequence information of a sequence window. One should *NOT* modify the length of the individual sequences.

attachPrefixes :: Monad m => Stream (Of (BioSequenceWindow w ty k)) m r -> Stream (Of (BioSequenceWindow w ty k)) m r Source #

For each element, attach the prefix as well.

1 2 3 4 -> 01 12 23 34

attachSuffixes :: Monad m => Stream (Of (BioSequenceWindow w ty k)) m r -> Stream (Of (BioSequenceWindow w ty k)) m r Source #

For each element, attach the suffix as well.

1 2 3 4 -> 12 23 34 40

DNA/RNA

rna2dna :: Char -> Char Source #

Simple case translation from U to T. with upper and lower-case awareness.

rnaComplement :: Char -> Char Source #

Single character RNA complement.

dna2rna :: Char -> Char Source #

Simple case translation from T to U with upper- and lower-case awareness.

dnaComplement :: Char -> Char Source #

Single character DNA complement.

class Transcribe f where Source #

Transcribes a DNA sequence into an RNA sequence. Note that transcribe is actually very generic. We just define its semantics to be that of biomolecular transcription.

transcribe makes the assumption that, given DNA -> RNA, we transcribe the coding strand. http://hyperphysics.phy-astr.gsu.edu/hbase/Organic/transcription.html

@ DNAseq ACGT ^. transcribe == RNAseq ACGU RNAseq ACGU ^. transcribe == DNAseq ACGT RNAseq ACGU ^. from transcribe :: DNAseq == DNAseq ACGT @

Associated Types

type TranscribeTo f :: * Source #

Instances
Transcribe (BioSequence DNA) Source #

Transcribe a DNA sequence into an RNA sequence. This does not reverse the sequence!

Instance details

Defined in Biobase.Types.BioSequence

Associated Types

type TranscribeTo (BioSequence DNA) :: Type Source #

Transcribe (BioSequence RNA) Source #

Transcribe a RNA sequence into an DNA sequence. This does not reverse the sequence!

Instance details

Defined in Biobase.Types.BioSequence

Associated Types

type TranscribeTo (BioSequence RNA) :: Type Source #

class Complement f where Source #

The complement of a biosequence.

Methods

complement :: Iso' f f Source #