cobot-io-0.1.4.3: Biological data file formats and IO
Safe HaskellNone
LanguageHaskell2010

Bio.FASTA.Type

Synopsis

Documentation

type Fasta a = [FastaItem a] Source #

Type alias for FASTA file. satisfies the following format : >(s|t)*[^nr]+(s|t)*(n|r)*((w|s)(n|r)*)*

data FastaItem a Source #

One record in FASTA file.

Constructors

FastaItem 

Fields

Instances

Instances details
Functor FastaItem Source # 
Instance details

Defined in Bio.FASTA.Type

Methods

fmap :: (a -> b) -> FastaItem a -> FastaItem b #

(<$) :: a -> FastaItem b -> FastaItem a #

Eq a => Eq (FastaItem a) Source # 
Instance details

Defined in Bio.FASTA.Type

Methods

(==) :: FastaItem a -> FastaItem a -> Bool #

(/=) :: FastaItem a -> FastaItem a -> Bool #

Show a => Show (FastaItem a) Source # 
Instance details

Defined in Bio.FASTA.Type

class ParsableFastaToken a where Source #

Methods

parseToken :: (Char -> Bool) -> Parser a Source #

Instances

Instances details
ParsableFastaToken Char Source # 
Instance details

Defined in Bio.FASTA.Parser

Methods

parseToken :: (Char -> Bool) -> Parser Char Source #

ParsableFastaToken ModItem Source # 
Instance details

Defined in Bio.FASTA.Parser

data Modification Source #

Instances

Instances details
Eq Modification Source # 
Instance details

Defined in Bio.FASTA.Type

Ord Modification Source # 
Instance details

Defined in Bio.FASTA.Type

Show Modification Source # 
Instance details

Defined in Bio.FASTA.Type

Generic Modification Source # 
Instance details

Defined in Bio.FASTA.Type

Associated Types

type Rep Modification :: Type -> Type #

type Rep Modification Source # 
Instance details

Defined in Bio.FASTA.Type

type Rep Modification = D1 ('MetaData "Modification" "Bio.FASTA.Type" "cobot-io-0.1.4.3-FtR1iZLExqtGkRGhoXEUKM" 'False) ((((((C1 ('MetaCons "Mod_A_Star" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_C_Star" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Mod_G_Star" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_T_Star" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_rA" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Mod_rC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_rG" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_rU" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Mod_Plus_A" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_Plus_C" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_Plus_G" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Mod_Plus_T" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_rAf" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Mod_rCf" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_rGf" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_rUf" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Mod_mA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_mC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_mG" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Mod_mU" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_mA_Star" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_mC_Star" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Mod_mG_Star" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_mU_Star" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Mod_dU" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_5Bio" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_iBio" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Mod_56FAM" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_36FAM" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_5HEX" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Mod_5TMR" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_3BHQ1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_3BHQ2" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Mod_5NH2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_3NH2" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Mod_5PO4" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_3PO4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_3BioTEG" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Mod_C12" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_NHSdT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_5Mal" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Mod_5thio" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_3thio" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_3azide" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Mod_3alkine" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_5CholTEG" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Mod_3CholTEG" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_5C10" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_5Alk" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Mod_GC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_GT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_AT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Mod_TG" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_AC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_CC" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Mod_AA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_TC" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Mod_TT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_CG" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_GG" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Mod_AG" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_GA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_CA" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Mod_CT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_TA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_AAA" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Mod_AAC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_ACT" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Mod_ATC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_ATG" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_CAG" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Mod_AGA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_CAT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_CCG" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Mod_CGT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_CTG" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_GAA" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Mod_GAC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_GCT" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Mod_GGT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_GTT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_TAC" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Mod_TCT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_TGC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod_TGG" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Mod_TTC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mod_TTT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unknown" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))))))

data ModItem Source #

Constructors

Mod Modification 
Letter Char 

Instances

Instances details
Eq ModItem Source # 
Instance details

Defined in Bio.FASTA.Type

Methods

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

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

Show ModItem Source # 
Instance details

Defined in Bio.FASTA.Type

Generic ModItem Source # 
Instance details

Defined in Bio.FASTA.Type

Associated Types

type Rep ModItem :: Type -> Type #

Methods

from :: ModItem -> Rep ModItem x #

to :: Rep ModItem x -> ModItem #

ParsableFastaToken ModItem Source # 
Instance details

Defined in Bio.FASTA.Parser

WritableFastaToken ModItem Source # 
Instance details

Defined in Bio.FASTA.Writer

type Rep ModItem Source # 
Instance details

Defined in Bio.FASTA.Type

type Rep ModItem = D1 ('MetaData "ModItem" "Bio.FASTA.Type" "cobot-io-0.1.4.3-FtR1iZLExqtGkRGhoXEUKM" 'False) (C1 ('MetaCons "Mod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Modification)) :+: C1 ('MetaCons "Letter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char)))