hPDB-1.2.0.9: Protein Databank file format library

Safe HaskellNone
LanguageHaskell98

Bio.PDB.Structure

Description

Module defines all components of high-level data type description of PDB model.

Synopsis

Documentation

type String = ByteString Source #

We use only strict ByteString as strings in PDB parser.

vdot :: Vector3 -> Vector3 -> Double Source #

Computes a dot product of two 3D vectors.

vnorm :: Vector3 -> Double Source #

2-norm of a vector (also called a magnitude or length.)

vproj :: Vector3 -> Vector3 -> Vector3 Source #

Finds a vector component of the first vector that is a projection onto direction of second vector.

vperpend :: Vector3 -> Vector3 -> Vector3 Source #

Returns a component of the vector v that is perpendicular to w.

vperpends :: Foldable t => Vector3 -> t Vector3 -> Vector3 Source #

Finds a component of the vector v that is perpendicular to all vectors in a list.

vdihedral :: Vector3 -> Vector3 -> Vector3 -> Double Source #

Compute dihedral between three bond vectors using spherical angle formula.

(*|) :: Double -> Vector3 -> Vector3 Source #

Scalar product. (asterisk - "*" - indicates side on which one can put a scalar.)

(|*) :: Vector3 -> Double -> Vector3 Source #

Scalar product. (asterisk - "*" - indicates side on which one can put a scalar.)

data Structure Source #

Structure holds all data parsed from a single PDB entry

Constructors

Structure 

Fields

Instances

Eq Structure Source # 
Show Structure Source # 
Generic Structure Source # 

Associated Types

type Rep Structure :: * -> * #

NFData Structure Source # 

Methods

rnf :: Structure -> () #

PDBWritable Structure Source # 

Methods

pdbEvents :: Structure -> [PDBEvent]

pdbEventS :: Structure -> PDBEventS

type Rep Structure Source # 
type Rep Structure = D1 (MetaData "Structure" "Bio.PDB.Structure" "hPDB_5rQudsWmTHnE3ug0qTu0P3" False) (C1 (MetaCons "Structure" PrefixI True) (S1 (MetaSel (Just Symbol "models") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (List Model))))

data Model Source #

PDB entry may contain multiple models, with slight differences in coordinates etc.

Constructors

Model 

Fields

Instances

Eq Model Source # 

Methods

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

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

Show Model Source # 

Methods

showsPrec :: Int -> Model -> ShowS #

show :: Model -> String #

showList :: [Model] -> ShowS #

Generic Model Source # 

Associated Types

type Rep Model :: * -> * #

Methods

from :: Model -> Rep Model x #

to :: Rep Model x -> Model #

NFData Model Source # 

Methods

rnf :: Model -> () #

PDBWritable Model Source # 

Methods

pdbEvents :: Model -> [PDBEvent]

pdbEventS :: Model -> PDBEventS

type Rep Model Source # 
type Rep Model = D1 (MetaData "Model" "Bio.PDB.Structure" "hPDB_5rQudsWmTHnE3ug0qTu0P3" False) (C1 (MetaCons "Model" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "modelId") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)) (S1 (MetaSel (Just Symbol "chains") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (List Chain)))))

data Chain Source #

Single linear polymer chain of protein, or nucleic acids

Constructors

Chain 

Fields

Instances

Eq Chain Source # 

Methods

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

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

Show Chain Source # 

Methods

showsPrec :: Int -> Chain -> ShowS #

show :: Chain -> String #

showList :: [Chain] -> ShowS #

Generic Chain Source # 

Associated Types

type Rep Chain :: * -> * #

Methods

from :: Chain -> Rep Chain x #

to :: Rep Chain x -> Chain #

NFData Chain Source # 

Methods

rnf :: Chain -> () #

PDBWritable Chain Source # 

Methods

pdbEvents :: Chain -> [PDBEvent]

pdbEventS :: Chain -> PDBEventS

type Rep Chain Source # 
type Rep Chain = D1 (MetaData "Chain" "Bio.PDB.Structure" "hPDB_5rQudsWmTHnE3ug0qTu0P3" False) (C1 (MetaCons "Chain" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "chainId") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Char)) (S1 (MetaSel (Just Symbol "residues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (List Residue)))))

data Residue Source #

Residue groups all atoms assigned to the same aminoacid or nucleic acid base within a polymer chain.

Constructors

Residue 

Fields

data Atom Source #

Single atom position | NOTE: disordered atoms are now reported as multiplicates

Constructors

Atom 

Instances

Eq Atom Source # 

Methods

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

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

Show Atom Source # 

Methods

showsPrec :: Int -> Atom -> ShowS #

show :: Atom -> String #

showList :: [Atom] -> ShowS #

Generic Atom Source # 

Associated Types

type Rep Atom :: * -> * #

Methods

from :: Atom -> Rep Atom x #

to :: Rep Atom x -> Atom #

NFData Atom Source # 

Methods

rnf :: Atom -> () #

PDBWritable Atom Source # 

Methods

pdbEvents :: Atom -> [PDBEvent]

pdbEventS :: Atom -> PDBEventS

type Rep Atom Source #