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

Bio.GB.Type

Synopsis

Documentation

data GenBankSequence Source #

Type that represents contents of .gb file that is used to store information about genetic constructions.

Constructors

GenBankSequence 

Fields

Instances

Instances details
Eq GenBankSequence Source # 
Instance details

Defined in Bio.GB.Type

Show GenBankSequence Source # 
Instance details

Defined in Bio.GB.Type

Generic GenBankSequence Source # 
Instance details

Defined in Bio.GB.Type

Associated Types

type Rep GenBankSequence :: Type -> Type #

NFData GenBankSequence Source # 
Instance details

Defined in Bio.GB.Type

Methods

rnf :: GenBankSequence -> () #

type Rep GenBankSequence Source # 
Instance details

Defined in Bio.GB.Type

type Rep GenBankSequence = D1 ('MetaData "GenBankSequence" "Bio.GB.Type" "cobot-io-0.1.4.3-FtR1iZLExqtGkRGhoXEUKM" 'False) (C1 ('MetaCons "GenBankSequence" 'PrefixI 'True) (S1 ('MetaSel ('Just "meta") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Meta) :*: S1 ('MetaSel ('Just "gbSeq") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MarkedSequence Feature Char))))

data Meta Source #

Meta-information about sequence.

Constructors

Meta 

Fields

Instances

Instances details
Eq Meta Source # 
Instance details

Defined in Bio.GB.Type

Methods

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

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

Show Meta Source # 
Instance details

Defined in Bio.GB.Type

Methods

showsPrec :: Int -> Meta -> ShowS #

show :: Meta -> String #

showList :: [Meta] -> ShowS #

Generic Meta Source # 
Instance details

Defined in Bio.GB.Type

Associated Types

type Rep Meta :: Type -> Type #

Methods

from :: Meta -> Rep Meta x #

to :: Rep Meta x -> Meta #

NFData Meta Source # 
Instance details

Defined in Bio.GB.Type

Methods

rnf :: Meta -> () #

type Rep Meta Source # 
Instance details

Defined in Bio.GB.Type

data Form Source #

At this moment there are two known (to me) forms of seuqences that can be present in .gb file.

Constructors

Linear 
Circular 

Instances

Instances details
Eq Form Source # 
Instance details

Defined in Bio.GB.Type

Methods

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

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

Show Form Source # 
Instance details

Defined in Bio.GB.Type

Methods

showsPrec :: Int -> Form -> ShowS #

show :: Form -> String #

showList :: [Form] -> ShowS #

Generic Form Source # 
Instance details

Defined in Bio.GB.Type

Associated Types

type Rep Form :: Type -> Type #

Methods

from :: Form -> Rep Form x #

to :: Rep Form x -> Form #

NFData Form Source # 
Instance details

Defined in Bio.GB.Type

Methods

rnf :: Form -> () #

type Rep Form Source # 
Instance details

Defined in Bio.GB.Type

type Rep Form = D1 ('MetaData "Form" "Bio.GB.Type" "cobot-io-0.1.4.3-FtR1iZLExqtGkRGhoXEUKM" 'False) (C1 ('MetaCons "Linear" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Circular" 'PrefixI 'False) (U1 :: Type -> Type))

data Locus Source #

First line that should be present in every .gb file. Contains general info about sequence.

Constructors

Locus 

Fields

Instances

Instances details
Eq Locus Source # 
Instance details

Defined in Bio.GB.Type

Methods

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

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

Show Locus Source # 
Instance details

Defined in Bio.GB.Type

Methods

showsPrec :: Int -> Locus -> ShowS #

show :: Locus -> String #

showList :: [Locus] -> ShowS #

Generic Locus Source # 
Instance details

Defined in Bio.GB.Type

Associated Types

type Rep Locus :: Type -> Type #

Methods

from :: Locus -> Rep Locus x #

to :: Rep Locus x -> Locus #

NFData Locus Source # 
Instance details

Defined in Bio.GB.Type

Methods

rnf :: Locus -> () #

type Rep Locus Source # 
Instance details

Defined in Bio.GB.Type

data Version Source #

Id of sequence in GenBank database.

Constructors

Version 

Fields

Instances

Instances details
Eq Version Source # 
Instance details

Defined in Bio.GB.Type

Methods

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

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

Show Version Source # 
Instance details

Defined in Bio.GB.Type

Generic Version Source # 
Instance details

Defined in Bio.GB.Type

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

NFData Version Source # 
Instance details

Defined in Bio.GB.Type

Methods

rnf :: Version -> () #

type Rep Version Source # 
Instance details

Defined in Bio.GB.Type

type Rep Version = D1 ('MetaData "Version" "Bio.GB.Type" "cobot-io-0.1.4.3-FtR1iZLExqtGkRGhoXEUKM" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) (S1 ('MetaSel ('Just "versionT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "gbId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))

data Source Source #

Information about source of this sequence.

Constructors

Source 

Fields

  • sourceT :: Text

    free-format (as if all this format is not too much "free format") information including an abbreviated form of the organism name, sometimes followed by a molecule type

  • organism :: Maybe Text

    the formal scientific name for the source organism

Instances

Instances details
Eq Source Source # 
Instance details

Defined in Bio.GB.Type

Methods

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

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

Show Source Source # 
Instance details

Defined in Bio.GB.Type

Generic Source Source # 
Instance details

Defined in Bio.GB.Type

Associated Types

type Rep Source :: Type -> Type #

Methods

from :: Source -> Rep Source x #

to :: Rep Source x -> Source #

NFData Source Source # 
Instance details

Defined in Bio.GB.Type

Methods

rnf :: Source -> () #

type Rep Source Source # 
Instance details

Defined in Bio.GB.Type

type Rep Source = D1 ('MetaData "Source" "Bio.GB.Type" "cobot-io-0.1.4.3-FtR1iZLExqtGkRGhoXEUKM" 'False) (C1 ('MetaCons "Source" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "organism") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))

data Reference Source #

Publications by the authors of the sequence that discuss the data reported in the record.

Constructors

Reference 

Fields

Instances

Instances details
Eq Reference Source # 
Instance details

Defined in Bio.GB.Type

Show Reference Source # 
Instance details

Defined in Bio.GB.Type

Generic Reference Source # 
Instance details

Defined in Bio.GB.Type

Associated Types

type Rep Reference :: Type -> Type #

NFData Reference Source # 
Instance details

Defined in Bio.GB.Type

Methods

rnf :: Reference -> () #

type Rep Reference Source # 
Instance details

Defined in Bio.GB.Type

data Feature Source #

One single feature.

Constructors

Feature 

Fields

  • fName :: Text

    main information about feature

  • fProps :: [(Text, Text)]

    properties of feature (such as "label", "gene", "note" etc.)

Instances

Instances details
Eq Feature Source # 
Instance details

Defined in Bio.GB.Type

Methods

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

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

Ord Feature Source # 
Instance details

Defined in Bio.GB.Type

Show Feature Source # 
Instance details

Defined in Bio.GB.Type

Generic Feature Source # 
Instance details

Defined in Bio.GB.Type

Associated Types

type Rep Feature :: Type -> Type #

Methods

from :: Feature -> Rep Feature x #

to :: Rep Feature x -> Feature #

NFData Feature Source # 
Instance details

Defined in Bio.GB.Type

Methods

rnf :: Feature -> () #

IsMarking Feature Source # 
Instance details

Defined in Bio.GB.Type

type Rep Feature Source # 
Instance details

Defined in Bio.GB.Type

type Rep Feature = D1 ('MetaData "Feature" "Bio.GB.Type" "cobot-io-0.1.4.3-FtR1iZLExqtGkRGhoXEUKM" 'False) (C1 ('MetaCons "Feature" 'PrefixI 'True) (S1 ('MetaSel ('Just "fName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "fProps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, Text)])))