Skip to content

Commit

Permalink
Version 0.1.2.10. Lenses for Structure (#30)
Browse files Browse the repository at this point in the history
* lenses in Structure

* Version 0.1.2.10. Lenses for Structure
  • Loading branch information
AlexKaneRUS authored Mar 27, 2020
1 parent 4b53aff commit 94796ca
Show file tree
Hide file tree
Showing 6 changed files with 60 additions and 14 deletions.
4 changes: 4 additions & 0 deletions ChangeLog.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,10 @@

## [Unreleased]

## [0.1.2.10] - 2020-03-27
### Added
- Lenses for `Structure`.

## [0.1.2.9] - 2020-03-12
### Added
- Function `filterAtomsOfModel` to filter atoms of model by the given predicate.
Expand Down
2 changes: 1 addition & 1 deletion package.yaml
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: cobot-io
version: 0.1.2.9
version: 0.1.2.10
github: "less-wrong/cobot-io"
license: BSD3
category: Bio
Expand Down
8 changes: 4 additions & 4 deletions src/Bio/MMTF.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ import Data.Vector (Vector, empty, toList, (!))
import Linear.V3 (V3 (..))
import Network.HTTP.Simple (getResponseBody, httpLBS)
#if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail (MonadFail(..))
import Control.Monad.Fail (MonadFail (..))
import Prelude hiding (fail)
#endif

Expand Down Expand Up @@ -70,9 +70,9 @@ instance StructureModels MMTF where
in (end, mkAtom <$> zip4 cl nl el ics)

mkResidue :: (GroupType, SecondaryStructure, [Atom]) -> Residue
mkResidue (gt, ss, atoms) = Residue (gtGroupName gt) (l2v atoms)
(mkBonds (gtBondAtomList gt) (gtBondOrderList gt))
ss (gtChemCompType gt)
mkResidue (gt, ss, atoms') = Residue (gtGroupName gt) (l2v atoms')
(mkBonds (gtBondAtomList gt) (gtBondOrderList gt))
ss (gtChemCompType gt)

mkBonds :: Vector (Int32, Int32) -> Vector Int32 -> Vector (Bond LocalID)
mkBonds bal bol = let ball = bimap (LocalID . fromIntegral) (LocalID . fromIntegral) <$> toList bal
Expand Down
12 changes: 6 additions & 6 deletions src/Bio/PDB.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,12 +43,12 @@ instance StructureModels PDB.PDB where


mkResidue :: [PDB.Atom] -> Residue
mkResidue [] = error "Cound not make residue from empty list"
mkResidue atoms = Residue (PDB.atomResName . head $ atoms)
(V.fromList $ mkAtom <$> atoms)
V.empty -- now we do not read bonds
Undefined -- now we do not read secondary structure
"" -- chemical component type?!
mkResidue [] = error "Cound not make residue from empty list"
mkResidue atoms' = Residue (PDB.atomResName . head $ atoms')
(V.fromList $ mkAtom <$> atoms')
V.empty -- now we do not read bonds
Undefined -- now we do not read secondary structure
"" -- chemical component type?!


mkAtom :: PDB.Atom -> Atom
Expand Down
16 changes: 14 additions & 2 deletions src/Bio/Structure.hs
Original file line number Diff line number Diff line change
@@ -1,15 +1,21 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}

module Bio.Structure
( SecondaryStructure (..)
, Atom (..), Bond (..)
, Residue (..), Chain (..), Model (..)
, StructureModels (..), StructureSerializable (..)
, LocalID (..)
, GlobalID (..)
, atoms, localBonds
, residues
, chains, globalBonds
) where

import Control.DeepSeq (NFData (..))
import Control.Lens (makeLensesFor)
import Data.Text (Text)
import Data.Vector (Vector)
import GHC.Generics (Generic)
Expand Down Expand Up @@ -78,20 +84,26 @@ data Residue = Residue { resName :: Text -- ^ residue n
}
deriving (Show, Eq, Generic, NFData)

makeLensesFor [("resAtoms", "atoms"), ("resBonds", "localBonds")] ''Residue

-- | Chain organizes linear structure of residues
--
data Chain = Chain { chainName :: Text -- ^ name of a chain
, chainResidues :: Vector Residue -- ^ residues of a chain
}
deriving (Show, Eq, Generic, NFData)

makeLensesFor [("chainResidues", "residues")] ''Chain

-- | Model represents a single experiment of structure determination
--
data Model = Model { modelChains :: Vector Chain -- ^ chains in the model
, modelBonds :: Vector (Bond GlobalID) -- ^ bonds with global identifiers (field `atomId` in 'Atom')
}
deriving (Show, Eq, Generic, NFData)

makeLensesFor [("modelChains", "chains"), ("modelBonds", "globalBonds")] ''Model

-- | Convert any format-specific data to an intermediate representation of structure
class StructureModels a where
-- | Get an array of models
Expand Down
32 changes: 31 additions & 1 deletion src/Bio/Structure/Functions.hs
Original file line number Diff line number Diff line change
@@ -1,16 +1,46 @@
module Bio.Structure.Functions
( filterAtomsOfModel
, chain, globalBond
, residue
, atom, localBond
) where

import Bio.Structure (Atom (..), Bond (..), Chain (..),
GlobalID (..), LocalID (..), Model (..),
Residue (..))
Residue (..), atoms, chains, globalBonds,
localBonds, residues)
import Control.Lens (Traversal', each)
import qualified Data.Map.Strict as M (fromList, (!))
import Data.Set (Set)
import qualified Data.Set as S (fromList, notMember, unions)
import Data.Vector (Vector)
import qualified Data.Vector as V (filter, fromList, length, toList, unzip)

-- | Traversal for every 'Chain' of the 'Model'.
--
chain :: Traversal' Model Chain
chain = chains . each

-- | Traversal for every 'Bond' of the 'Model'.
--
globalBond :: Traversal' Model (Bond GlobalID)
globalBond = globalBonds . each

-- | Traversal for every 'Residue' of the 'Chain'.
--
residue :: Traversal' Chain Residue
residue = residues . each

-- | Traversal for every 'Atom' of the 'Residue'.
--
atom :: Traversal' Residue Atom
atom = atoms . each

-- | Traversal for every 'Bond' of the 'Residue'.
--
localBond :: Traversal' Residue (Bond LocalID)
localBond = localBonds . each

-- | Takes predicate on 'Atom's of 'Model' and returns new 'Model' containing only atoms
-- satisfying given predicate.
--
Expand Down

0 comments on commit 94796ca

Please sign in to comment.