Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- newtype SequenceIdentifier (which :: k) = SequenceIdentifier {}
- _SequenceIdentifier :: forall which which. Iso (SequenceIdentifier which) (SequenceIdentifier which) ByteString ByteString
- data RNA
- data DNA
- data XNA
- data AA
- newtype BioSequence (which :: k) = BioSequence {}
- _BioSequence :: forall which which. Iso (BioSequence which) (BioSequence which) ByteString ByteString
- mkRNAseq :: ByteString -> BioSequence RNA
- mkDNAseq :: ByteString -> BioSequence DNA
- mkXNAseq :: ByteString -> BioSequence XNA
- mkAAseq :: ByteString -> BioSequence AA
- data BioSequenceWindow w ty loc = BioSequenceWindow {
- _bswIdentifier :: !(SequenceIdentifier w)
- _bswPrefix :: !(BioSequence ty)
- _bswSequence :: !(BioSequence ty)
- _bswSuffix :: !(BioSequence ty)
- _bswLocation :: !loc
- bswSuffix :: forall w ty loc. Lens' (BioSequenceWindow w ty loc) (BioSequence ty)
- bswSequence :: forall w ty loc. Lens' (BioSequenceWindow w ty loc) (BioSequence ty)
- bswPrefix :: forall w ty loc. Lens' (BioSequenceWindow w ty loc) (BioSequence ty)
- bswLocation :: forall w ty loc loc. Lens (BioSequenceWindow w ty loc) (BioSequenceWindow w ty loc) loc loc
- bswIdentifier :: forall w ty loc w. Lens (BioSequenceWindow w ty loc) (BioSequenceWindow w ty loc) (SequenceIdentifier w) (SequenceIdentifier w)
- bswFullSequence :: Lens' (BioSequenceWindow w ty k) (BioSequence ty)
- attachPrefixes :: Monad m => Stream (Of (BioSequenceWindow w ty k)) m r -> Stream (Of (BioSequenceWindow w ty k)) m r
- attachSuffixes :: Monad m => Stream (Of (BioSequenceWindow w ty k)) m r -> Stream (Of (BioSequenceWindow w ty k)) m r
- rna2dna :: Char -> Char
- rnaComplement :: Char -> Char
- dna2rna :: Char -> Char
- dnaComplement :: Char -> Char
- class Transcribe f where
- type TranscribeTo f :: *
- transcribe :: Iso' f (TranscribeTo f)
- class Complement f where
- complement :: Iso' f f
- reverseComplement :: (Complement f, Reversing f) => Iso' f f
Sequence identifiers
newtype SequenceIdentifier (which :: k) Source #
Instances
_SequenceIdentifier :: forall which which. Iso (SequenceIdentifier which) (SequenceIdentifier which) ByteString ByteString Source #
Bio-Sequences
Instances
IsString (BioSequence RNA) Source # | |
Defined in Biobase.Types.BioSequence fromString :: String -> BioSequence RNA # | |
Arbitrary (BioSequence RNA) Source # | |
Defined in Biobase.Types.BioSequence arbitrary :: Gen (BioSequence RNA) # shrink :: BioSequence RNA -> [BioSequence RNA] # | |
Complement (BioSequence RNA) Source # | |
Defined in Biobase.Types.BioSequence complement :: Iso' (BioSequence RNA) (BioSequence RNA) Source # | |
Transcribe (BioSequence RNA) Source # | Transcribe a RNA sequence into an DNA sequence. This does not |
Defined in Biobase.Types.BioSequence type TranscribeTo (BioSequence RNA) :: Type Source # transcribe :: Iso' (BioSequence RNA) (TranscribeTo (BioSequence RNA)) Source # | |
type TranscribeTo (BioSequence RNA) Source # | |
Defined in Biobase.Types.BioSequence |
Instances
IsString (BioSequence DNA) Source # | |
Defined in Biobase.Types.BioSequence fromString :: String -> BioSequence DNA # | |
Arbitrary (BioSequence DNA) Source # | |
Defined in Biobase.Types.BioSequence arbitrary :: Gen (BioSequence DNA) # shrink :: BioSequence DNA -> [BioSequence DNA] # | |
Complement (BioSequence DNA) Source # | |
Defined in Biobase.Types.BioSequence complement :: Iso' (BioSequence DNA) (BioSequence DNA) Source # | |
Transcribe (BioSequence DNA) Source # | Transcribe a DNA sequence into an RNA sequence. This does not |
Defined in Biobase.Types.BioSequence type TranscribeTo (BioSequence DNA) :: Type Source # transcribe :: Iso' (BioSequence DNA) (TranscribeTo (BioSequence DNA)) Source # | |
type TranscribeTo (BioSequence DNA) Source # | |
Defined in Biobase.Types.BioSequence |
Instances
IsString (BioSequence XNA) Source # | |
Defined in Biobase.Types.BioSequence fromString :: String -> BioSequence XNA # | |
Arbitrary (BioSequence XNA) Source # | |
Defined in Biobase.Types.BioSequence arbitrary :: Gen (BioSequence XNA) # shrink :: BioSequence XNA -> [BioSequence XNA] # |
Instances
IsString (BioSequence AA) Source # | |
Defined in Biobase.Types.BioSequence fromString :: String -> BioSequence AA # | |
Arbitrary (BioSequence AA) Source # | |
Defined in Biobase.Types.BioSequence arbitrary :: Gen (BioSequence AA) # shrink :: BioSequence AA -> [BioSequence AA] # |
newtype BioSequence (which :: k) Source #
Instances
_BioSequence :: forall which which. Iso (BioSequence which) (BioSequence which) ByteString ByteString Source #
RNA
mkRNAseq :: ByteString -> BioSequence RNA Source #
TODO write that converts explicitly
DNA
mkDNAseq :: ByteString -> BioSequence DNA Source #
XNA
mkXNAseq :: ByteString -> BioSequence XNA Source #
Amino acid sequences
mkAAseq :: ByteString -> BioSequence AA Source #
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.
BioSequenceWindow | |
|
Instances
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 #
bswIdentifier :: forall w ty loc w. Lens (BioSequenceWindow w ty loc) (BioSequenceWindow w ty loc) (SequenceIdentifier w) (SequenceIdentifier w) 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
@
type TranscribeTo f :: * Source #
transcribe :: Iso' f (TranscribeTo f) Source #
Instances
Transcribe (BioSequence DNA) Source # | Transcribe a DNA sequence into an RNA sequence. This does not |
Defined in Biobase.Types.BioSequence type TranscribeTo (BioSequence DNA) :: Type Source # transcribe :: Iso' (BioSequence DNA) (TranscribeTo (BioSequence DNA)) Source # | |
Transcribe (BioSequence RNA) Source # | Transcribe a RNA sequence into an DNA sequence. This does not |
Defined in Biobase.Types.BioSequence type TranscribeTo (BioSequence RNA) :: Type Source # transcribe :: Iso' (BioSequence RNA) (TranscribeTo (BioSequence RNA)) Source # |
class Complement f where Source #
The complement of a biosequence.
complement :: Iso' f f Source #
Instances
Complement (BioSequence DNA) Source # | |
Defined in Biobase.Types.BioSequence complement :: Iso' (BioSequence DNA) (BioSequence DNA) Source # | |
Complement (BioSequence RNA) Source # | |
Defined in Biobase.Types.BioSequence complement :: Iso' (BioSequence RNA) (BioSequence RNA) Source # | |
Complement (BioSequence ty) => Complement (BioSequenceWindow w ty k3) Source # | |
Defined in Biobase.Types.BioSequence complement :: Iso' (BioSequenceWindow w ty k3) (BioSequenceWindow w ty k3) Source # |
reverseComplement :: (Complement f, Reversing f) => Iso' f f Source #