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

Bio.Structure

Synopsis

Documentation

data SecondaryStructure Source #

Protein secondary structure

Constructors

PiHelix

pi helix

Bend

bend

AlphaHelix

alpha helix

Extended

extended

ThreeTenHelix

3-10 helix

Bridge

brigde

Turn

turn

Coil

coil

Undefined

unknown structure

Instances

Instances details
Eq SecondaryStructure Source # 
Instance details

Defined in Bio.Structure

Show SecondaryStructure Source # 
Instance details

Defined in Bio.Structure

Generic SecondaryStructure Source # 
Instance details

Defined in Bio.Structure

Associated Types

type Rep SecondaryStructure :: Type -> Type #

NFData SecondaryStructure Source # 
Instance details

Defined in Bio.Structure

Methods

rnf :: SecondaryStructure -> () #

type Rep SecondaryStructure Source # 
Instance details

Defined in Bio.Structure

type Rep SecondaryStructure = D1 ('MetaData "SecondaryStructure" "Bio.Structure" "cobot-io-0.1.4.4-CqLQJQSI3e86Tkry2VYHOf" 'False) (((C1 ('MetaCons "PiHelix" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Bend" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AlphaHelix" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Extended" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ThreeTenHelix" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Bridge" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Turn" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Coil" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Undefined" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Atom Source #

Generic atom representation

Constructors

Atom 

Fields

Instances

Instances details
Eq Atom Source # 
Instance details

Defined in Bio.Structure

Methods

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

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

Ord Atom Source # 
Instance details

Defined in Bio.Structure

Methods

compare :: Atom -> Atom -> Ordering #

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

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

(>) :: Atom -> Atom -> Bool #

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

max :: Atom -> Atom -> Atom #

min :: Atom -> Atom -> Atom #

Show Atom Source # 
Instance details

Defined in Bio.Structure

Methods

showsPrec :: Int -> Atom -> ShowS #

show :: Atom -> String #

showList :: [Atom] -> ShowS #

Generic Atom Source # 
Instance details

Defined in Bio.Structure

Associated Types

type Rep Atom :: Type -> Type #

Methods

from :: Atom -> Rep Atom x #

to :: Rep Atom x -> Atom #

NFData Atom Source # 
Instance details

Defined in Bio.Structure

Methods

rnf :: Atom -> () #

type Rep Atom Source # 
Instance details

Defined in Bio.Structure

data Bond m Source #

Generic chemical bond

Constructors

Bond 

Fields

Instances

Instances details
Functor Bond Source # 
Instance details

Defined in Bio.Structure

Methods

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

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

Eq m => Eq (Bond m) Source # 
Instance details

Defined in Bio.Structure

Methods

(==) :: Bond m -> Bond m -> Bool #

(/=) :: Bond m -> Bond m -> Bool #

Ord (Bond LocalID) Source # 
Instance details

Defined in Bio.Structure

Ord (Bond GlobalID) Source # 
Instance details

Defined in Bio.Structure

Show m => Show (Bond m) Source # 
Instance details

Defined in Bio.Structure

Methods

showsPrec :: Int -> Bond m -> ShowS #

show :: Bond m -> String #

showList :: [Bond m] -> ShowS #

Generic (Bond m) Source # 
Instance details

Defined in Bio.Structure

Associated Types

type Rep (Bond m) :: Type -> Type #

Methods

from :: Bond m -> Rep (Bond m) x #

to :: Rep (Bond m) x -> Bond m #

NFData a => NFData (Bond a) Source # 
Instance details

Defined in Bio.Structure

Methods

rnf :: Bond a -> () #

type Rep (Bond m) Source # 
Instance details

Defined in Bio.Structure

type Rep (Bond m) = D1 ('MetaData "Bond" "Bio.Structure" "cobot-io-0.1.4.4-CqLQJQSI3e86Tkry2VYHOf" 'False) (C1 ('MetaCons "Bond" 'PrefixI 'True) (S1 ('MetaSel ('Just "bondStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m) :*: (S1 ('MetaSel ('Just "bondEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m) :*: S1 ('MetaSel ('Just "bondOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

data Residue Source #

A set of atoms, organized to a residues

Constructors

Residue 

Fields

Instances

Instances details
Eq Residue Source # 
Instance details

Defined in Bio.Structure

Methods

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

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

Show Residue Source # 
Instance details

Defined in Bio.Structure

Generic Residue Source # 
Instance details

Defined in Bio.Structure

Associated Types

type Rep Residue :: Type -> Type #

Methods

from :: Residue -> Rep Residue x #

to :: Rep Residue x -> Residue #

NFData Residue Source # 
Instance details

Defined in Bio.Structure

Methods

rnf :: Residue -> () #

type Rep Residue Source # 
Instance details

Defined in Bio.Structure

data Chain Source #

Chain organizes linear structure of residues

Constructors

Chain 

Fields

Instances

Instances details
Eq Chain Source # 
Instance details

Defined in Bio.Structure

Methods

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

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

Show Chain Source # 
Instance details

Defined in Bio.Structure

Methods

showsPrec :: Int -> Chain -> ShowS #

show :: Chain -> String #

showList :: [Chain] -> ShowS #

Generic Chain Source # 
Instance details

Defined in Bio.Structure

Associated Types

type Rep Chain :: Type -> Type #

Methods

from :: Chain -> Rep Chain x #

to :: Rep Chain x -> Chain #

NFData Chain Source # 
Instance details

Defined in Bio.Structure

Methods

rnf :: Chain -> () #

type Rep Chain Source # 
Instance details

Defined in Bio.Structure

type Rep Chain = D1 ('MetaData "Chain" "Bio.Structure" "cobot-io-0.1.4.4-CqLQJQSI3e86Tkry2VYHOf" 'False) (C1 ('MetaCons "Chain" 'PrefixI 'True) (S1 ('MetaSel ('Just "chainName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "chainResidues") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Residue))))

data Model Source #

Model represents a single experiment of structure determination

Constructors

Model 

Fields

Instances

Instances details
Eq Model Source # 
Instance details

Defined in Bio.Structure

Methods

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

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

Show Model Source # 
Instance details

Defined in Bio.Structure

Methods

showsPrec :: Int -> Model -> ShowS #

show :: Model -> String #

showList :: [Model] -> ShowS #

Generic Model Source # 
Instance details

Defined in Bio.Structure

Associated Types

type Rep Model :: Type -> Type #

Methods

from :: Model -> Rep Model x #

to :: Rep Model x -> Model #

NFData Model Source # 
Instance details

Defined in Bio.Structure

Methods

rnf :: Model -> () #

type Rep Model Source # 
Instance details

Defined in Bio.Structure

type Rep Model = D1 ('MetaData "Model" "Bio.Structure" "cobot-io-0.1.4.4-CqLQJQSI3e86Tkry2VYHOf" 'False) (C1 ('MetaCons "Model" 'PrefixI 'True) (S1 ('MetaSel ('Just "modelChains") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Chain)) :*: S1 ('MetaSel ('Just "modelBonds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector (Bond GlobalID)))))

class StructureModels a where Source #

Convert any format-specific data to an intermediate representation of structure

Methods

modelsOf :: a -> Vector Model Source #

Get an array of models

Instances

Instances details
StructureModels Mae Source # 
Instance details

Defined in Bio.MAE

StructureModels PDB Source # 
Instance details

Defined in Bio.PDB

StructureModels MMTF Source # 
Instance details

Defined in Bio.MMTF

class StructureSerializable a where Source #

Serialize an intermediate representation of sequence to some specific format

Methods

serializeModels :: Vector Model -> a Source #

Serialize an array of models to some format

Instances

Instances details
StructureSerializable PDB Source # 
Instance details

Defined in Bio.PDB

newtype LocalID Source #

Constructors

LocalID 

Fields

Instances

Instances details
Eq LocalID Source # 
Instance details

Defined in Bio.Structure

Methods

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

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

Ord LocalID Source # 
Instance details

Defined in Bio.Structure

Show LocalID Source # 
Instance details

Defined in Bio.Structure

Generic LocalID Source # 
Instance details

Defined in Bio.Structure

Associated Types

type Rep LocalID :: Type -> Type #

Methods

from :: LocalID -> Rep LocalID x #

to :: Rep LocalID x -> LocalID #

NFData LocalID Source # 
Instance details

Defined in Bio.Structure

Methods

rnf :: LocalID -> () #

Ord (Bond LocalID) Source # 
Instance details

Defined in Bio.Structure

type Rep LocalID Source # 
Instance details

Defined in Bio.Structure

type Rep LocalID = D1 ('MetaData "LocalID" "Bio.Structure" "cobot-io-0.1.4.4-CqLQJQSI3e86Tkry2VYHOf" 'True) (C1 ('MetaCons "LocalID" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLocalID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype GlobalID Source #

Constructors

GlobalID 

Fields

Instances

Instances details
Eq GlobalID Source # 
Instance details

Defined in Bio.Structure

Ord GlobalID Source # 
Instance details

Defined in Bio.Structure

Show GlobalID Source # 
Instance details

Defined in Bio.Structure

Generic GlobalID Source # 
Instance details

Defined in Bio.Structure

Associated Types

type Rep GlobalID :: Type -> Type #

Methods

from :: GlobalID -> Rep GlobalID x #

to :: Rep GlobalID x -> GlobalID #

NFData GlobalID Source # 
Instance details

Defined in Bio.Structure

Methods

rnf :: GlobalID -> () #

Ord (Bond GlobalID) Source # 
Instance details

Defined in Bio.Structure

type Rep GlobalID Source # 
Instance details

Defined in Bio.Structure

type Rep GlobalID = D1 ('MetaData "GlobalID" "Bio.Structure" "cobot-io-0.1.4.4-CqLQJQSI3e86Tkry2VYHOf" 'True) (C1 ('MetaCons "GlobalID" 'PrefixI 'True) (S1 ('MetaSel ('Just "getGlobalID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))