hPDB-1.0: Protein Databank file format library

Safe HaskellNone

Bio.PDB

Synopsis

Documentation

parse :: FilePath -> IO (Maybe Structure)Source

Parse a .pdb file and return Structure.

write :: Structure -> FilePath -> IO ()Source

Write structure to a .pdb file.

data Model Source

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

Constructors

Model 

Fields

modelId :: !Int
 
chains :: List Chain
 

data Chain Source

Single linear polymer chain of protein, or nucleic acids

Constructors

Chain 

Fields

chainId :: !Char
 
residues :: 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

resName :: !String
 
resSeq :: !Int
 
atoms :: List Atom
 
insCode :: !Char
 

data Atom Source

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

Constructors

Atom 

class Iterable a b where

Class for iterating all nested components b of type a.

Methods

itmapM :: Monad m => (b -> m b) -> a -> m a

itmap :: (b -> b) -> a -> a

itfoldM :: Monad m => (c -> b -> m c) -> c -> a -> m c

itfoldr :: (b -> c -> c) -> c -> a -> c

itfoldl :: (c -> b -> c) -> c -> a -> c

itfoldl' :: (c -> b -> c) -> c -> a -> c

itlength :: b -> a -> Int

numAtoms :: Iterable a Atom => a -> IntSource

Number of all atoms within the structure.

numResidues :: Iterable a Residue => a -> IntSource

Number of all residues within the structure.

numChains :: Iterable a Chain => a -> IntSource

Number of all chains within the structure.

numModels :: Iterable a Model => a -> IntSource

Number of all models within the structure.

firstModel :: Iterable a Model => a -> Maybe ModelSource

Takes a first model.

resname2fastacode :: String -> CharSource

Dictionary mapping three-letter PDB residue code to a single-letter FASTA code.

fastacode2resname :: Char -> StringSource

Dictionary mapping single-letter FASTA standard aminoacid code to a PDB residue name

(*|) :: Double -> Vector3 -> Vector3Source

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

(|*) :: Vector3 -> Double -> Vector3Source

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

vnorm :: Vector3 -> DoubleSource

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

type Element = ByteStringSource

Type alias for Element names.

assignElement :: Atom -> ElementSource

Given a PDB Atom extract or guess its Element name.

atomicNumber :: Element -> IntSource

Atomic number of a given element

atomicMass :: Element -> DoubleSource

Atomic mass of a given element in g/mol

covalentRadius :: (Eq a1, Fractional a, Show a1, IsString a1) => a1 -> aSource

Covalent radius of an element with a given name.

vanDerWaalsRadius :: Element -> DoubleSource

Van der Waals radius of the given element