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

Bio.Uniprot.Type

Synopsis

Documentation

data Kingdom Source #

Which taxonomic kingdom an organism belongs to.

Constructors

Archea

A for archaea (=archaebacteria)

Bacteria

B for bacteria (=prokaryota or eubacteria)

Eukaryota

E for eukaryota (=eukarya)

Virus

V for viruses and phages (=viridae)

Other

O for others (such as artificial sequences)

Instances

Instances details
Bounded Kingdom Source # 
Instance details

Defined in Bio.Uniprot.Type

Enum Kingdom Source # 
Instance details

Defined in Bio.Uniprot.Type

Eq Kingdom Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord Kingdom Source # 
Instance details

Defined in Bio.Uniprot.Type

Show Kingdom Source # 
Instance details

Defined in Bio.Uniprot.Type

Generic Kingdom Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep Kingdom :: Type -> Type #

Methods

from :: Kingdom -> Rep Kingdom x #

to :: Rep Kingdom x -> Kingdom #

type Rep Kingdom Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep Kingdom = D1 ('MetaData "Kingdom" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) ((C1 ('MetaCons "Archea" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Bacteria" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Eukaryota" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Virus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Other" 'PrefixI 'False) (U1 :: Type -> Type))))

data Organism Source #

Controlled vocabulary of species

Constructors

Organism 

Fields

Instances

Instances details
Eq Organism Source # 
Instance details

Defined in Bio.Uniprot.Type

Ord Organism Source # 
Instance details

Defined in Bio.Uniprot.Type

Show Organism Source # 
Instance details

Defined in Bio.Uniprot.Type

Generic Organism Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep Organism :: Type -> Type #

Methods

from :: Organism -> Rep Organism x #

to :: Rep Organism x -> Organism #

type Rep Organism Source # 
Instance details

Defined in Bio.Uniprot.Type

data Status Source #

To distinguish the fully annotated entries in the Swiss-Prot section of the UniProt Knowledgebase from the computer-annotated entries in the TrEMBL section, the status of each entry is indicated in the first (ID) line of each entry

Constructors

Reviewed

Entries that have been manually reviewed and annotated by UniProtKB curators

Unreviewed

Computer-annotated entries that have not been reviewed by UniProtKB curators

Instances

Instances details
Bounded Status Source # 
Instance details

Defined in Bio.Uniprot.Type

Enum Status Source # 
Instance details

Defined in Bio.Uniprot.Type

Eq Status Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord Status Source # 
Instance details

Defined in Bio.Uniprot.Type

Show Status Source # 
Instance details

Defined in Bio.Uniprot.Type

Generic Status Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep Status :: Type -> Type #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

type Rep Status Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep Status = D1 ('MetaData "Status" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) (C1 ('MetaCons "Reviewed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unreviewed" 'PrefixI 'False) (U1 :: Type -> Type))

data ID Source #

IDentification

Constructors

ID 

Fields

  • entryName :: Text

    This name is a useful means of identifying a sequence, but it is not a stable identifier as is the accession number.

  • status :: Status

    The status of the entry

  • seqLength :: Int

    The length of the molecule, which is the total number of amino acids in the sequence. This number includes the positions reported to be present but which have not been determined (coded as X).

Instances

Instances details
Eq ID Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord ID Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: ID -> ID -> Ordering #

(<) :: ID -> ID -> Bool #

(<=) :: ID -> ID -> Bool #

(>) :: ID -> ID -> Bool #

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

max :: ID -> ID -> ID #

min :: ID -> ID -> ID #

Show ID Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> ID -> ShowS #

show :: ID -> String #

showList :: [ID] -> ShowS #

Generic ID Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep ID :: Type -> Type #

Methods

from :: ID -> Rep ID x #

to :: Rep ID x -> ID #

type Rep ID Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep ID = D1 ('MetaData "ID" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) (C1 ('MetaCons "ID" 'PrefixI 'True) (S1 ('MetaSel ('Just "entryName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status) :*: S1 ('MetaSel ('Just "seqLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

newtype AC Source #

ACcession numbers. The purpose of accession numbers is to provide a stable way of identifying entries from release to release. It is sometimes necessary for reasons of consistency to change the names of the entries, for example, to ensure that related entries have similar names. However, an accession number is always conserved, and therefore allows unambiguous citation of entries. Researchers who wish to cite entries in their publications should always cite the first accession number. This is commonly referred to as the 'primary accession number'. 'Secondary accession numbers' are sorted alphanumerically.

Constructors

AC 

Fields

Instances

Instances details
Eq AC Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord AC Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: AC -> AC -> Ordering #

(<) :: AC -> AC -> Bool #

(<=) :: AC -> AC -> Bool #

(>) :: AC -> AC -> Bool #

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

max :: AC -> AC -> AC #

min :: AC -> AC -> AC #

Show AC Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> AC -> ShowS #

show :: AC -> String #

showList :: [AC] -> ShowS #

Generic AC Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep AC :: Type -> Type #

Methods

from :: AC -> Rep AC x #

to :: Rep AC x -> AC #

type Rep AC Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep AC = D1 ('MetaData "AC" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'True) (C1 ('MetaCons "AC" 'PrefixI 'True) (S1 ('MetaSel ('Just "accessionNumbers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])))

data DT Source #

DaTe: the date of creation and last modification of the database entry.

Constructors

DT 

Fields

  • dbIntegrationDate :: Text

    Indicates when the entry first appeared in the database.

  • dbName :: Text

    Indicates in which section of UniProtKB, Swiss-Prot or TrEMBL, the entry can be found.

  • seqVersionDate :: Text

    Indicates when the sequence data was last modified.

  • seqVersion :: Int

    The sequence version number of an entry is incremented by one when the amino acid sequence shown in the sequence record is modified.

  • entryVersionDate :: Text

    Indicates when data other than the sequence was last modified.

  • entryVersion :: Int

    The entry version number is incremented by one whenever any data in the flat file representation of the entry is modified.

Instances

Instances details
Eq DT Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord DT Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: DT -> DT -> Ordering #

(<) :: DT -> DT -> Bool #

(<=) :: DT -> DT -> Bool #

(>) :: DT -> DT -> Bool #

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

max :: DT -> DT -> DT #

min :: DT -> DT -> DT #

Show DT Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> DT -> ShowS #

show :: DT -> String #

showList :: [DT] -> ShowS #

Generic DT Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep DT :: Type -> Type #

Methods

from :: DT -> Rep DT x #

to :: Rep DT x -> DT #

type Rep DT Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep DT = D1 ('MetaData "DT" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) (C1 ('MetaCons "DT" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dbIntegrationDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "dbName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "seqVersionDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "seqVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "entryVersionDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "entryVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))))

data Name Source #

Constructors

Name 

Fields

Instances

Instances details
Eq Name Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord Name Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Generic Name Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

type Rep Name Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep Name = D1 ('MetaData "Name" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) (C1 ('MetaCons "Name" 'PrefixI 'True) (S1 ('MetaSel ('Just "fullName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "shortName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "ecNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]))))

data AltName Source #

Instances

Instances details
Eq AltName Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord AltName Source # 
Instance details

Defined in Bio.Uniprot.Type

Show AltName Source # 
Instance details

Defined in Bio.Uniprot.Type

Generic AltName Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep AltName :: Type -> Type #

Methods

from :: AltName -> Rep AltName x #

to :: Rep AltName x -> AltName #

type Rep AltName Source # 
Instance details

Defined in Bio.Uniprot.Type

data Flag Source #

Constructors

Fragment

The complete sequence is not determined.

Fragments

The complete sequence is not determined.

Precursor

The sequence displayed does not correspond to the mature form of the protein.

Instances

Instances details
Bounded Flag Source # 
Instance details

Defined in Bio.Uniprot.Type

Enum Flag Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

succ :: Flag -> Flag #

pred :: Flag -> Flag #

toEnum :: Int -> Flag #

fromEnum :: Flag -> Int #

enumFrom :: Flag -> [Flag] #

enumFromThen :: Flag -> Flag -> [Flag] #

enumFromTo :: Flag -> Flag -> [Flag] #

enumFromThenTo :: Flag -> Flag -> Flag -> [Flag] #

Eq Flag Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord Flag Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: Flag -> Flag -> Ordering #

(<) :: Flag -> Flag -> Bool #

(<=) :: Flag -> Flag -> Bool #

(>) :: Flag -> Flag -> Bool #

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

max :: Flag -> Flag -> Flag #

min :: Flag -> Flag -> Flag #

Read Flag Source # 
Instance details

Defined in Bio.Uniprot.Type

Show Flag Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

Generic Flag Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep Flag :: Type -> Type #

Methods

from :: Flag -> Rep Flag x #

to :: Rep Flag x -> Flag #

type Rep Flag Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep Flag = D1 ('MetaData "Flag" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) (C1 ('MetaCons "Fragment" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Fragments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Precursor" 'PrefixI 'False) (U1 :: Type -> Type)))

data DE Source #

DEscription - general descriptive information about the sequence stored.

Constructors

DE 

Fields

  • recName :: Maybe Name

    The name recommended by the UniProt consortium.

  • altNames :: [AltName]

    A synonym of the recommended name.

  • subNames :: [Name]

    A name provided by the submitter of the underlying nucleotide sequence.

  • includes :: [DE]

    A protein is known to include multiple functional domains each of which is described by a different name.

  • contains :: [DE]

    The functional domains of an enzyme are cleaved, but the catalytic activity can only be observed, when the individual chains reorganize in a complex.

  • flags :: [Flag]

    Flags whether the entire is a precursor or/and a fragment.

Instances

Instances details
Eq DE Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord DE Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: DE -> DE -> Ordering #

(<) :: DE -> DE -> Bool #

(<=) :: DE -> DE -> Bool #

(>) :: DE -> DE -> Bool #

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

max :: DE -> DE -> DE #

min :: DE -> DE -> DE #

Show DE Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> DE -> ShowS #

show :: DE -> String #

showList :: [DE] -> ShowS #

Generic DE Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep DE :: Type -> Type #

Methods

from :: DE -> Rep DE x #

to :: Rep DE x -> DE #

type Rep DE Source # 
Instance details

Defined in Bio.Uniprot.Type

data GN Source #

Gene Name - the name(s) of the gene(s) that code for the stored protein sequence.

Constructors

GN 

Fields

  • geneName :: Maybe Text

    The name used to represent a gene.

  • synonyms :: [Text]

    Other (unofficial) names of a gene.

  • orderedLocusNames :: [Text]

    A name used to represent an ORF in a completely sequenced genome or chromosome.

  • orfNames :: [Text]

    A name temporarily attributed by a sequencing project to an open reading frame.

Instances

Instances details
Eq GN Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord GN Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: GN -> GN -> Ordering #

(<) :: GN -> GN -> Bool #

(<=) :: GN -> GN -> Bool #

(>) :: GN -> GN -> Bool #

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

max :: GN -> GN -> GN #

min :: GN -> GN -> GN #

Show GN Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> GN -> ShowS #

show :: GN -> String #

showList :: [GN] -> ShowS #

Generic GN Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep GN :: Type -> Type #

Methods

from :: GN -> Rep GN x #

to :: Rep GN x -> GN #

type Rep GN Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep GN = D1 ('MetaData "GN" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) (C1 ('MetaCons "GN" 'PrefixI 'True) ((S1 ('MetaSel ('Just "geneName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "synonyms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])) :*: (S1 ('MetaSel ('Just "orderedLocusNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "orfNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]))))

newtype OS Source #

Organism Species - the organism which was the source of the stored sequence.

Constructors

OS 

Fields

Instances

Instances details
Eq OS Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord OS Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: OS -> OS -> Ordering #

(<) :: OS -> OS -> Bool #

(<=) :: OS -> OS -> Bool #

(>) :: OS -> OS -> Bool #

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

max :: OS -> OS -> OS #

min :: OS -> OS -> OS #

Show OS Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> OS -> ShowS #

show :: OS -> String #

showList :: [OS] -> ShowS #

Generic OS Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep OS :: Type -> Type #

Methods

from :: OS -> Rep OS x #

to :: Rep OS x -> OS #

type Rep OS Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep OS = D1 ('MetaData "OS" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'True) (C1 ('MetaCons "OS" 'PrefixI 'True) (S1 ('MetaSel ('Just "specie") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Plastid Source #

A enum of possible plastid types, based on either taxonomic lineage or photosynthetic capacity.

Constructors

PlastidSimple

The term Plastid is used when the capacities of the organism are unclear; for example in the parasitic plants of the Cuscuta lineage, where sometimes young tissue is photosynthetic.

PlastidApicoplast

Apicoplasts are the plastids found in Apicocomplexa parasites such as Eimeria, Plasmodium and Toxoplasma; they are not photosynthetic.

PlastidChloroplast

Chloroplasts are the plastids found in all land plants and algae with the exception of the glaucocystophyte algae (see below). Chloroplasts in green tissue are photosynthetic; in other tissues they may not be photosynthetic and then may also have secondary information relating to subcellular location (e.g. amyloplasts, chromoplasts).

PlastidOrganellarChromatophore

Chloroplasts are the plastids found in all land plants and algae with the exception of the glaucocystophyte algae (see below). Chloroplasts in green tissue are photosynthetic; in other tissues they may not be photosynthetic and then may also have secondary information relating to subcellular location (e.g. amyloplasts, chromoplasts).

PlastidCyanelle

Cyanelles are the plastids found in the glaucocystophyte algae. They are also photosynthetic but their plastid has a vestigial cell wall between the 2 envelope membranes.

PlastidNonPhotosynthetic

Non-photosynthetic plastid is used when the plastid in question derives from a photosynthetic lineage but the plastid in question is missing essential genes. Some examples are Aneura mirabilis, Epifagus virginiana, Helicosporidium (a liverwort, higher plant and green alga respectively).

Instances

Instances details
Bounded Plastid Source # 
Instance details

Defined in Bio.Uniprot.Type

Enum Plastid Source # 
Instance details

Defined in Bio.Uniprot.Type

Eq Plastid Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord Plastid Source # 
Instance details

Defined in Bio.Uniprot.Type

Show Plastid Source # 
Instance details

Defined in Bio.Uniprot.Type

Generic Plastid Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep Plastid :: Type -> Type #

Methods

from :: Plastid -> Rep Plastid x #

to :: Rep Plastid x -> Plastid #

type Rep Plastid Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep Plastid = D1 ('MetaData "Plastid" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) ((C1 ('MetaCons "PlastidSimple" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PlastidApicoplast" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PlastidChloroplast" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PlastidOrganellarChromatophore" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PlastidCyanelle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PlastidNonPhotosynthetic" 'PrefixI 'False) (U1 :: Type -> Type))))

data OG Source #

OrGanelle - indicates if the gene coding for a protein originates from mitochondria, a plastid, a nucleomorph or a plasmid.

Constructors

Hydrogenosome

Hydrogenosomes are membrane-enclosed redox organelles found in some anaerobic unicellular eukaryotes which contain hydrogenase and produce hydrogen and ATP by glycolysis. They are thought to have evolved from mitochondria; most hydrogenosomes lack a genome, but some like (e.g. the anaerobic ciliate Nyctotherus ovalis) have retained a rudimentary genome.

Mitochondrion

Mitochondria are redox-active membrane-bound organelles found in the cytoplasm of most eukaryotic cells. They are the site of sthe reactions of oxidative phosphorylation, which results in the formation of ATP.

Nucleomorph

Nucleomorphs are reduced vestigal nuclei found in the plastids of cryptomonad and chlorachniophyte algae. The plastids originate from engulfed eukaryotic phototrophs.

Plasmid [Text]

Plasmid with a specific name. If an entry reports the sequence of a protein identical in a number of plasmids, the names of these plasmids will all be listed.

Plastid Plastid

Plastids are classified based on either their taxonomic lineage or in some cases on their photosynthetic capacity.

Instances

Instances details
Eq OG Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord OG Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: OG -> OG -> Ordering #

(<) :: OG -> OG -> Bool #

(<=) :: OG -> OG -> Bool #

(>) :: OG -> OG -> Bool #

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

max :: OG -> OG -> OG #

min :: OG -> OG -> OG #

Show OG Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> OG -> ShowS #

show :: OG -> String #

showList :: [OG] -> ShowS #

Generic OG Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep OG :: Type -> Type #

Methods

from :: OG -> Rep OG x #

to :: Rep OG x -> OG #

type Rep OG Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep OG = D1 ('MetaData "OG" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) ((C1 ('MetaCons "Hydrogenosome" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mitochondrion" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Nucleomorph" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Plasmid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])) :+: C1 ('MetaCons "Plastid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Plastid)))))

newtype OC Source #

Organism Classification - the taxonomic classification of the source organism.

Constructors

OC 

Fields

Instances

Instances details
Eq OC Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord OC Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: OC -> OC -> Ordering #

(<) :: OC -> OC -> Bool #

(<=) :: OC -> OC -> Bool #

(>) :: OC -> OC -> Bool #

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

max :: OC -> OC -> OC #

min :: OC -> OC -> OC #

Show OC Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> OC -> ShowS #

show :: OC -> String #

showList :: [OC] -> ShowS #

Generic OC Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep OC :: Type -> Type #

Methods

from :: OC -> Rep OC x #

to :: Rep OC x -> OC #

type Rep OC Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep OC = D1 ('MetaData "OC" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'True) (C1 ('MetaCons "OC" 'PrefixI 'True) (S1 ('MetaSel ('Just "nodes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])))

data OX Source #

Organism taxonomy cross-reference indicates the identifier of a specific organism in a taxonomic database.

Constructors

OX 

Fields

Instances

Instances details
Eq OX Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord OX Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: OX -> OX -> Ordering #

(<) :: OX -> OX -> Bool #

(<=) :: OX -> OX -> Bool #

(>) :: OX -> OX -> Bool #

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

max :: OX -> OX -> OX #

min :: OX -> OX -> OX #

Show OX Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> OX -> ShowS #

show :: OX -> String #

showList :: [OX] -> ShowS #

Generic OX Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep OX :: Type -> Type #

Methods

from :: OX -> Rep OX x #

to :: Rep OX x -> OX #

type Rep OX Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep OX = D1 ('MetaData "OX" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) (C1 ('MetaCons "OX" 'PrefixI 'True) (S1 ('MetaSel ('Just "databaseQualifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "taxonomicCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data OH Source #

Organism Host - indicates the host organism(s) that are susceptible to be infected by a virus. Appears only in viral entries.

Constructors

OH 

Fields

Instances

Instances details
Eq OH Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord OH Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: OH -> OH -> Ordering #

(<) :: OH -> OH -> Bool #

(<=) :: OH -> OH -> Bool #

(>) :: OH -> OH -> Bool #

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

max :: OH -> OH -> OH #

min :: OH -> OH -> OH #

Show OH Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> OH -> ShowS #

show :: OH -> String #

showList :: [OH] -> ShowS #

Generic OH Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep OH :: Type -> Type #

Methods

from :: OH -> Rep OH x #

to :: Rep OH x -> OH #

type Rep OH Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep OH = D1 ('MetaData "OH" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) (C1 ('MetaCons "OH" 'PrefixI 'True) (S1 ('MetaSel ('Just "taxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "hostName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Token Source #

Reference comment token.

Constructors

STRAIN 
PLASMID 
TRANSPOSON 
TISSUE 

Instances

Instances details
Bounded Token Source # 
Instance details

Defined in Bio.Uniprot.Type

Enum Token Source # 
Instance details

Defined in Bio.Uniprot.Type

Eq Token Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord Token Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: Token -> Token -> Ordering #

(<) :: Token -> Token -> Bool #

(<=) :: Token -> Token -> Bool #

(>) :: Token -> Token -> Bool #

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

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

Show Token Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Generic Token Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep Token :: Type -> Type #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

type Rep Token Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep Token = D1 ('MetaData "Token" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) ((C1 ('MetaCons "STRAIN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PLASMID" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TRANSPOSON" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TISSUE" 'PrefixI 'False) (U1 :: Type -> Type)))

data BibliographicDB Source #

Bibliographic database names.

Constructors

MEDLINE 
PubMed 
DOI 
AGRICOLA 

Instances

Instances details
Bounded BibliographicDB Source # 
Instance details

Defined in Bio.Uniprot.Type

Enum BibliographicDB Source # 
Instance details

Defined in Bio.Uniprot.Type

Eq BibliographicDB Source # 
Instance details

Defined in Bio.Uniprot.Type

Ord BibliographicDB Source # 
Instance details

Defined in Bio.Uniprot.Type

Show BibliographicDB Source # 
Instance details

Defined in Bio.Uniprot.Type

Generic BibliographicDB Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep BibliographicDB :: Type -> Type #

type Rep BibliographicDB Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep BibliographicDB = D1 ('MetaData "BibliographicDB" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) ((C1 ('MetaCons "MEDLINE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PubMed" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DOI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AGRICOLA" 'PrefixI 'False) (U1 :: Type -> Type)))

data RN Source #

Reference Number - a sequential number to each reference citation in an entry.

Constructors

RN 

Fields

Instances

Instances details
Eq RN Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord RN Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: RN -> RN -> Ordering #

(<) :: RN -> RN -> Bool #

(<=) :: RN -> RN -> Bool #

(>) :: RN -> RN -> Bool #

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

max :: RN -> RN -> RN #

min :: RN -> RN -> RN #

Show RN Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> RN -> ShowS #

show :: RN -> String #

showList :: [RN] -> ShowS #

Generic RN Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep RN :: Type -> Type #

Methods

from :: RN -> Rep RN x #

to :: Rep RN x -> RN #

type Rep RN Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep RN = D1 ('MetaData "RN" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) (C1 ('MetaCons "RN" 'PrefixI 'True) (S1 ('MetaSel ('Just "number") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "evidence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])))

data Reference Source #

Reference lines.

Constructors

Reference 

Fields

  • rn :: Int

    Reference Number - a sequential number to each reference citation in an entry.

  • rp :: Text

    Reference Position - the extent of the work relevant to the entry carried out by the authors.

  • rc :: [(Token, Text)]

    Reference Comment - comments relevant to the reference cited.

  • rx :: [(BibliographicDB, Text)]

    Reference cross-reference - the identifier assigned to a specific reference in a bibliographic database.

  • rg :: [Text]

    Reference Group - the consortium name associated with a given citation.

  • ra :: [Text]

    Reference Author - authors of the paper (or other work) cited.

  • rt :: Maybe Text

    Reference Title - the title of the paper (or other work) cited as exactly as possible given the limitations of the computer character set.

  • rl :: Text

    Reference Location - he conventional citation information for the reference.

Instances

Instances details
Eq Reference Source # 
Instance details

Defined in Bio.Uniprot.Type

Ord Reference Source # 
Instance details

Defined in Bio.Uniprot.Type

Show Reference Source # 
Instance details

Defined in Bio.Uniprot.Type

Generic Reference Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep Reference :: Type -> Type #

type Rep Reference Source # 
Instance details

Defined in Bio.Uniprot.Type

type Topic = Text Source #

The comment blocks are arranged according to what we designate as topics.

data CC Source #

Free text comments on the entry, and are used to convey any useful information.

Constructors

CC 

Fields

Instances

Instances details
Eq CC Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord CC Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: CC -> CC -> Ordering #

(<) :: CC -> CC -> Bool #

(<=) :: CC -> CC -> Bool #

(>) :: CC -> CC -> Bool #

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

max :: CC -> CC -> CC #

min :: CC -> CC -> CC #

Show CC Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> CC -> ShowS #

show :: CC -> String #

showList :: [CC] -> ShowS #

Generic CC Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep CC :: Type -> Type #

Methods

from :: CC -> Rep CC x #

to :: Rep CC x -> CC #

type Rep CC Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep CC = D1 ('MetaData "CC" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) (C1 ('MetaCons "CC" 'PrefixI 'True) (S1 ('MetaSel ('Just "topic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Topic) :*: S1 ('MetaSel ('Just "comment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data DR Source #

Database cross-Reference - pointers to information in external data resources that is related to UniProtKB entries.

Constructors

DR 

Fields

Instances

Instances details
Eq DR Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord DR Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: DR -> DR -> Ordering #

(<) :: DR -> DR -> Bool #

(<=) :: DR -> DR -> Bool #

(>) :: DR -> DR -> Bool #

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

max :: DR -> DR -> DR #

min :: DR -> DR -> DR #

Show DR Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> DR -> ShowS #

show :: DR -> String #

showList :: [DR] -> ShowS #

Generic DR Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep DR :: Type -> Type #

Methods

from :: DR -> Rep DR x #

to :: Rep DR x -> DR #

type Rep DR Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep DR = D1 ('MetaData "DR" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) (C1 ('MetaCons "DR" 'PrefixI 'True) (S1 ('MetaSel ('Just "resourceAbbr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "resourceId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "optionalInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]))))

data PE Source #

Protein existence - indication on the evidences that we currently have for the existence of a protein. Because most protein sequences are derived from translation of nucleotide sequences and are mere predictions, the PE line indicates what the evidences are of the existence of a protein.

Instances

Instances details
Eq PE Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord PE Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: PE -> PE -> Ordering #

(<) :: PE -> PE -> Bool #

(<=) :: PE -> PE -> Bool #

(>) :: PE -> PE -> Bool #

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

max :: PE -> PE -> PE #

min :: PE -> PE -> PE #

Show PE Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> PE -> ShowS #

show :: PE -> String #

showList :: [PE] -> ShowS #

Generic PE Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep PE :: Type -> Type #

Methods

from :: PE -> Rep PE x #

to :: Rep PE x -> PE #

type Rep PE Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep PE = D1 ('MetaData "PE" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) ((C1 ('MetaCons "EvidenceAtProteinLevel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EvidenceAtTranscriptLevel" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "InferredFromHomology" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Predicted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Uncertain" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype KW Source #

KeyWord - information that can be used to generate indexes of the sequence entries based on functional, structural, or other categories.

Constructors

KW 

Fields

Instances

Instances details
Eq KW Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord KW Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: KW -> KW -> Ordering #

(<) :: KW -> KW -> Bool #

(<=) :: KW -> KW -> Bool #

(>) :: KW -> KW -> Bool #

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

max :: KW -> KW -> KW #

min :: KW -> KW -> KW #

Show KW Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> KW -> ShowS #

show :: KW -> String #

showList :: [KW] -> ShowS #

Generic KW Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep KW :: Type -> Type #

Methods

from :: KW -> Rep KW x #

to :: Rep KW x -> KW #

type Rep KW Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep KW = D1 ('MetaData "KW" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'True) (C1 ('MetaCons "KW" 'PrefixI 'True) (S1 ('MetaSel ('Just "keywords") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])))

data Endpoint Source #

Instances

Instances details
Eq Endpoint Source # 
Instance details

Defined in Bio.Uniprot.Type

Ord Endpoint Source # 
Instance details

Defined in Bio.Uniprot.Type

Show Endpoint Source # 
Instance details

Defined in Bio.Uniprot.Type

Generic Endpoint Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep Endpoint :: Type -> Type #

Methods

from :: Endpoint -> Rep Endpoint x #

to :: Rep Endpoint x -> Endpoint #

type Rep Endpoint Source # 
Instance details

Defined in Bio.Uniprot.Type

data FT Source #

Feature Table - means for the annotation of the sequence data.

Constructors

FT 

Fields

Instances

Instances details
Eq FT Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord FT Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: FT -> FT -> Ordering #

(<) :: FT -> FT -> Bool #

(<=) :: FT -> FT -> Bool #

(>) :: FT -> FT -> Bool #

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

max :: FT -> FT -> FT #

min :: FT -> FT -> FT #

Show FT Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> FT -> ShowS #

show :: FT -> String #

showList :: [FT] -> ShowS #

Generic FT Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep FT :: Type -> Type #

Methods

from :: FT -> Rep FT x #

to :: Rep FT x -> FT #

type Rep FT Source # 
Instance details

Defined in Bio.Uniprot.Type

data SQ Source #

SeQuence header - sequence data and a quick summary of its content.

Constructors

SQ 

Fields

  • len :: Int

    Length of the sequence in amino acids.

  • molWeight :: Int

    Molecular weight rounded to the nearest mass unit (Dalton).

  • crc64 :: Text

    Sequence 64-bit CRC (Cyclic Redundancy Check) value.

  • sequ :: Text

    Sequence of the protein

Instances

Instances details
Eq SQ Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord SQ Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

compare :: SQ -> SQ -> Ordering #

(<) :: SQ -> SQ -> Bool #

(<=) :: SQ -> SQ -> Bool #

(>) :: SQ -> SQ -> Bool #

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

max :: SQ -> SQ -> SQ #

min :: SQ -> SQ -> SQ #

Show SQ Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

showsPrec :: Int -> SQ -> ShowS #

show :: SQ -> String #

showList :: [SQ] -> ShowS #

Generic SQ Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep SQ :: Type -> Type #

Methods

from :: SQ -> Rep SQ x #

to :: Rep SQ x -> SQ #

type Rep SQ Source # 
Instance details

Defined in Bio.Uniprot.Type

data Record Source #

Full UniProt record in UniProt-KB format.

Constructors

Record 

Fields

Instances

Instances details
Eq Record Source # 
Instance details

Defined in Bio.Uniprot.Type

Methods

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

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

Ord Record Source # 
Instance details

Defined in Bio.Uniprot.Type

Show Record Source # 
Instance details

Defined in Bio.Uniprot.Type

Generic Record Source # 
Instance details

Defined in Bio.Uniprot.Type

Associated Types

type Rep Record :: Type -> Type #

Methods

from :: Record -> Rep Record x #

to :: Rep Record x -> Record #

type Rep Record Source # 
Instance details

Defined in Bio.Uniprot.Type

type Rep Record = D1 ('MetaData "Record" "Bio.Uniprot.Type" "cobot-io-0.1.3.20-HPhNL0gUcHREQ55zp5Rm8s" 'False) (C1 ('MetaCons "Record" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ID) :*: S1 ('MetaSel ('Just "ac") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AC)) :*: (S1 ('MetaSel ('Just "dt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DT) :*: S1 ('MetaSel ('Just "de") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DE))) :*: ((S1 ('MetaSel ('Just "gn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GN]) :*: S1 ('MetaSel ('Just "os") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OS)) :*: (S1 ('MetaSel ('Just "og") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OG]) :*: S1 ('MetaSel ('Just "oc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OC)))) :*: (((S1 ('MetaSel ('Just "ox") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OX) :*: S1 ('MetaSel ('Just "oh") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OH])) :*: (S1 ('MetaSel ('Just "refs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Reference]) :*: S1 ('MetaSel ('Just "cc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CC]))) :*: ((S1 ('MetaSel ('Just "dr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DR]) :*: S1 ('MetaSel ('Just "pe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PE)) :*: (S1 ('MetaSel ('Just "kw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe KW)) :*: (S1 ('MetaSel ('Just "ft") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FT]) :*: S1 ('MetaSel ('Just "sq") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SQ)))))))