cobot-io-0.1.2.0: Biological data file formats and IO

Safe HaskellNone
LanguageHaskell2010

Bio.MMTF.Type

Synopsis

Documentation

type IArray a = Array Int a Source #

All arrays are int-indexed

data M44 Source #

Transformation matrix

Instances
Eq M44 Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

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

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

Show M44 Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

showsPrec :: Int -> M44 -> ShowS #

show :: M44 -> String #

showList :: [M44] -> ShowS #

Generic M44 Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep M44 :: Type -> Type #

Methods

from :: M44 -> Rep M44 x #

to :: Rep M44 x -> M44 #

NFData M44 Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: M44 -> () #

type Rep M44 Source # 
Instance details

Defined in Bio.MMTF.Type

type Rep M44 = D1 (MetaData "M44" "Bio.MMTF.Type" "cobot-io-0.1.2.0-Edw5pXm2rhDLW8sGnHkG2U" False) (C1 (MetaCons "M44" PrefixI False) ((((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))) :*: ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)))) :*: (((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))) :*: ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))))))

data UnitCell Source #

Unit cell data

Constructors

UnitCell 

Fields

Instances
Eq UnitCell Source # 
Instance details

Defined in Bio.MMTF.Type

Show UnitCell Source # 
Instance details

Defined in Bio.MMTF.Type

Generic UnitCell Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep UnitCell :: Type -> Type #

Methods

from :: UnitCell -> Rep UnitCell x #

to :: Rep UnitCell x -> UnitCell #

NFData UnitCell Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: UnitCell -> () #

type Rep UnitCell Source # 
Instance details

Defined in Bio.MMTF.Type

data Transform Source #

Transform data

Constructors

Transform 

Fields

Instances
Eq Transform Source # 
Instance details

Defined in Bio.MMTF.Type

Show Transform Source # 
Instance details

Defined in Bio.MMTF.Type

Generic Transform Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep Transform :: Type -> Type #

NFData Transform Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: Transform -> () #

type Rep Transform Source # 
Instance details

Defined in Bio.MMTF.Type

type Rep Transform = D1 (MetaData "Transform" "Bio.MMTF.Type" "cobot-io-0.1.2.0-Edw5pXm2rhDLW8sGnHkG2U" False) (C1 (MetaCons "Transform" PrefixI True) (S1 (MetaSel (Just "chainIndexList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray Int32)) :*: S1 (MetaSel (Just "matrix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 M44)))

data Assembly Source #

Assembly data

Constructors

Assembly 

Fields

Instances
Eq Assembly Source # 
Instance details

Defined in Bio.MMTF.Type

Show Assembly Source # 
Instance details

Defined in Bio.MMTF.Type

Generic Assembly Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep Assembly :: Type -> Type #

Methods

from :: Assembly -> Rep Assembly x #

to :: Rep Assembly x -> Assembly #

NFData Assembly Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: Assembly -> () #

type Rep Assembly Source # 
Instance details

Defined in Bio.MMTF.Type

type Rep Assembly = D1 (MetaData "Assembly" "Bio.MMTF.Type" "cobot-io-0.1.2.0-Edw5pXm2rhDLW8sGnHkG2U" False) (C1 (MetaCons "Assembly" PrefixI True) (S1 (MetaSel (Just "transformList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray Transform)) :*: S1 (MetaSel (Just "assemblyName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

data Entity Source #

Entity data

Constructors

Entity 

Fields

Instances
Eq Entity Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

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

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

Show Entity Source # 
Instance details

Defined in Bio.MMTF.Type

Generic Entity Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep Entity :: Type -> Type #

Methods

from :: Entity -> Rep Entity x #

to :: Rep Entity x -> Entity #

NFData Entity Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: Entity -> () #

type Rep Entity Source # 
Instance details

Defined in Bio.MMTF.Type

type Rep Entity = D1 (MetaData "Entity" "Bio.MMTF.Type" "cobot-io-0.1.2.0-Edw5pXm2rhDLW8sGnHkG2U" False) (C1 (MetaCons "Entity" PrefixI True) ((S1 (MetaSel (Just "entityChainIndexList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray Int32)) :*: S1 (MetaSel (Just "entityDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "entityType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "entitySequence") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data GroupType Source #

Group type data

Constructors

GroupType 

Fields

Instances
Eq GroupType Source # 
Instance details

Defined in Bio.MMTF.Type

Show GroupType Source # 
Instance details

Defined in Bio.MMTF.Type

Generic GroupType Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep GroupType :: Type -> Type #

NFData GroupType Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: GroupType -> () #

type Rep GroupType Source # 
Instance details

Defined in Bio.MMTF.Type

data FormatData Source #

MMTF format data

Constructors

FormatData 

Fields

  • mmtfVersion :: !Text

    The version number of the specification the file adheres to

  • mmtfProducer :: !Text

    The name and version of the software used to produce the file

Instances
Eq FormatData Source # 
Instance details

Defined in Bio.MMTF.Type

Show FormatData Source # 
Instance details

Defined in Bio.MMTF.Type

Generic FormatData Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep FormatData :: Type -> Type #

NFData FormatData Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: FormatData -> () #

type Rep FormatData Source # 
Instance details

Defined in Bio.MMTF.Type

type Rep FormatData = D1 (MetaData "FormatData" "Bio.MMTF.Type" "cobot-io-0.1.2.0-Edw5pXm2rhDLW8sGnHkG2U" False) (C1 (MetaCons "FormatData" PrefixI True) (S1 (MetaSel (Just "mmtfVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "mmtfProducer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

data StructureData Source #

Structure data

Constructors

StructureData 

Fields

Instances
Eq StructureData Source # 
Instance details

Defined in Bio.MMTF.Type

Show StructureData Source # 
Instance details

Defined in Bio.MMTF.Type

Generic StructureData Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep StructureData :: Type -> Type #

NFData StructureData Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: StructureData -> () #

type Rep StructureData Source # 
Instance details

Defined in Bio.MMTF.Type

type Rep StructureData = D1 (MetaData "StructureData" "Bio.MMTF.Type" "cobot-io-0.1.2.0-Edw5pXm2rhDLW8sGnHkG2U" False) (C1 (MetaCons "StructureData" PrefixI True) ((((S1 (MetaSel (Just "title") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "structureId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "depositionDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "releaseDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "numBonds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int32)))) :*: ((S1 (MetaSel (Just "numAtoms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int32) :*: S1 (MetaSel (Just "numGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int32)) :*: (S1 (MetaSel (Just "numChains") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int32) :*: (S1 (MetaSel (Just "numModels") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int32) :*: S1 (MetaSel (Just "spaceGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))) :*: (((S1 (MetaSel (Just "unitCell") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UnitCell)) :*: S1 (MetaSel (Just "ncsOperatorList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray M44))) :*: (S1 (MetaSel (Just "bioAssemblyList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray Assembly)) :*: (S1 (MetaSel (Just "entityList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray Entity)) :*: S1 (MetaSel (Just "resolution") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Float))))) :*: ((S1 (MetaSel (Just "rFree") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Float)) :*: S1 (MetaSel (Just "rWork") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Float))) :*: (S1 (MetaSel (Just "experimentalMethods") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray Text)) :*: (S1 (MetaSel (Just "bondAtomList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray (Int32, Int32))) :*: S1 (MetaSel (Just "bondOrderList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray Int8))))))))

data ModelData Source #

Models data

Constructors

ModelData 

Fields

Instances
Eq ModelData Source # 
Instance details

Defined in Bio.MMTF.Type

Show ModelData Source # 
Instance details

Defined in Bio.MMTF.Type

Generic ModelData Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep ModelData :: Type -> Type #

NFData ModelData Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: ModelData -> () #

type Rep ModelData Source # 
Instance details

Defined in Bio.MMTF.Type

type Rep ModelData = D1 (MetaData "ModelData" "Bio.MMTF.Type" "cobot-io-0.1.2.0-Edw5pXm2rhDLW8sGnHkG2U" False) (C1 (MetaCons "ModelData" PrefixI True) (S1 (MetaSel (Just "chainsPerModel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray Int32))))

data ChainData Source #

Chains data

Constructors

ChainData 

Fields

Instances
Eq ChainData Source # 
Instance details

Defined in Bio.MMTF.Type

Show ChainData Source # 
Instance details

Defined in Bio.MMTF.Type

Generic ChainData Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep ChainData :: Type -> Type #

NFData ChainData Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: ChainData -> () #

type Rep ChainData Source # 
Instance details

Defined in Bio.MMTF.Type

type Rep ChainData = D1 (MetaData "ChainData" "Bio.MMTF.Type" "cobot-io-0.1.2.0-Edw5pXm2rhDLW8sGnHkG2U" False) (C1 (MetaCons "ChainData" PrefixI True) (S1 (MetaSel (Just "groupsPerChain") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray Int32)) :*: (S1 (MetaSel (Just "chainIdList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray Text)) :*: S1 (MetaSel (Just "chainNameList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IArray Text)))))

data GroupData Source #

Groups data

Constructors

GroupData 

Fields

Instances
Eq GroupData Source # 
Instance details

Defined in Bio.MMTF.Type

Show GroupData Source # 
Instance details

Defined in Bio.MMTF.Type

Generic GroupData Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep GroupData :: Type -> Type #

NFData GroupData Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: GroupData -> () #

type Rep GroupData Source # 
Instance details

Defined in Bio.MMTF.Type

data AtomData Source #

Atoms data

Constructors

AtomData 

Fields

Instances
Eq AtomData Source # 
Instance details

Defined in Bio.MMTF.Type

Show AtomData Source # 
Instance details

Defined in Bio.MMTF.Type

Generic AtomData Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep AtomData :: Type -> Type #

Methods

from :: AtomData -> Rep AtomData x #

to :: Rep AtomData x -> AtomData #

NFData AtomData Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: AtomData -> () #

type Rep AtomData Source # 
Instance details

Defined in Bio.MMTF.Type

data MMTF Source #

MMTF datatype

Constructors

MMTF 

Fields

Instances
Eq MMTF Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

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

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

Show MMTF Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

showsPrec :: Int -> MMTF -> ShowS #

show :: MMTF -> String #

showList :: [MMTF] -> ShowS #

Generic MMTF Source # 
Instance details

Defined in Bio.MMTF.Type

Associated Types

type Rep MMTF :: Type -> Type #

Methods

from :: MMTF -> Rep MMTF x #

to :: Rep MMTF x -> MMTF #

NFData MMTF Source # 
Instance details

Defined in Bio.MMTF.Type

Methods

rnf :: MMTF -> () #

MessagePack MMTF Source # 
Instance details

Defined in Bio.MMTF.MessagePack

Methods

toObject :: MMTF -> Object #

fromObject :: (Applicative m, Monad m) => Object -> m MMTF #

StructureModels MMTF Source # 
Instance details

Defined in Bio.MMTF

type Rep MMTF Source # 
Instance details

Defined in Bio.MMTF.Type