cobot-0.1.1.7: Computational biology toolkit to collaborate with researchers in constructive protein engineering
Safe HaskellNone
LanguageHaskell2010

Bio.Protein.AminoAcid.Instances

Synopsis

Documentation

class Createable a where Source #

Single object can be created

Associated Types

type Create a :: Type Source #

Methods

create :: Create a Source #

Function to create single object

Instances

Instances details
Createable (BBOXTRH a) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type Create (BBOXTRH a) Source #

Methods

create :: Create (BBOXTRH a) Source #

Createable (BBORH a) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type Create (BBORH a) Source #

Methods

create :: Create (BBORH a) Source #

Createable (BBOXTR a) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type Create (BBOXTR a) Source #

Methods

create :: Create (BBOXTR a) Source #

Createable (BBOR a) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type Create (BBOR a) Source #

Methods

create :: Create (BBOR a) Source #

Createable (BBOCG a) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type Create (BBOCG a) Source #

Methods

create :: Create (BBOCG a) Source #

Createable (BBOT a) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type Create (BBOT a) Source #

Methods

create :: Create (BBOT a) Source #

Createable (BBO a) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type Create (BBO a) Source #

Methods

create :: Create (BBO a) Source #

Createable (BBCG a) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type Create (BBCG a) Source #

Methods

create :: Create (BBCG a) Source #

Createable (BBCAT a) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type Create (BBCAT a) Source #

Methods

create :: Create (BBCAT a) Source #

Createable (BBT a) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type Create (BBT a) Source #

Methods

create :: Create (BBT a) Source #

Createable (BBCA a) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type Create (BBCA a) Source #

Methods

create :: Create (BBCA a) Source #

Createable (BB a) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type Create (BB a) Source #

Methods

create :: Create (BB a) Source #

class Functor r => HasRadical r where Source #

Has lens to observe, set and modify radicals

Associated Types

type RadicalType r a :: Type Source #

Methods

radical :: (Functor f, Functor g) => Lens' (AminoAcid f (Env r) g a) (RadicalType r a) Source #

Lens for radical atom or group

Instances

Instances details
HasRadical Identity Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type RadicalType Identity a Source #

Methods

radical :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Lens' (AminoAcid f (Env Identity) g a) (RadicalType Identity a) Source #

HasRadical CG Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type RadicalType CG a Source #

Methods

radical :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Lens' (AminoAcid f (Env CG) g a) (RadicalType CG a) Source #

HasRadical Radical Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type RadicalType Radical a Source #

Methods

radical :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Lens' (AminoAcid f (Env Radical) g a) (RadicalType Radical a) Source #

HasRadical (Const x :: Type -> Type) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Associated Types

type RadicalType (Const x) a Source #

Methods

radical :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Lens' (AminoAcid f (Env (Const x)) g a) (RadicalType (Const x) a) Source #

class Functor r => HasRadicalType r where Source #

Has lens to observe radical types

Methods

radicalType :: (Functor f, Functor g) => Getting AA (AminoAcid f (Env r) g a) AA Source #

Getter for radical type

Instances

Instances details
HasRadicalType CG Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

radicalType :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Getting AA (AminoAcid f (Env CG) g a) AA Source #

HasRadicalType Radical Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

radicalType :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Getting AA (AminoAcid f (Env Radical) g a) AA Source #

HasRadicalType (Const AA :: Type -> Type) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

radicalType :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Getting AA (AminoAcid f (Env (Const AA)) g a) AA Source #

class Functor r => HasCA r where Source #

Has lens to observe, set and modify ca_ atom

Methods

ca :: (Functor f, Functor g) => Lens' (AminoAcid f r g a) a Source #

Lens for ca_ atom

Instances

Instances details
HasCA Identity Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

ca :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Lens' (AminoAcid f Identity g a) a Source #

Functor f => HasCA (Env f) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

ca :: forall (f0 :: Type -> Type) (g :: Type -> Type) a. (Functor f0, Functor g) => Lens' (AminoAcid f0 (Env f) g a) a Source #

class Functor r => HasC r where Source #

Has lens to observe, set and modify c_ atom

Methods

c :: (Functor f, Functor g) => Lens' (AminoAcid f g r a) a Source #

Lens for c_ atom

Instances

Instances details
HasC Identity Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

c :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Lens' (AminoAcid f g Identity a) a Source #

Functor f => HasC (Env f) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

c :: forall (f0 :: Type -> Type) (g :: Type -> Type) a. (Functor f0, Functor g) => Lens' (AminoAcid f0 g (Env f) a) a Source #

class Functor r => HasO r where Source #

Has lens to observe, set and modify o_ atom

Methods

o :: (Functor f, Functor g) => Lens' (AminoAcid f g (Env r) a) a Source #

Lens for o_ atom

Instances

Instances details
HasO Identity Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

o :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Lens' (AminoAcid f g (Env Identity) a) a Source #

HasO OXT Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

o :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Lens' (AminoAcid f g (Env OXT) a) a Source #

class Functor r => HasOXT r where Source #

Has lens to observe, set and modify OXT atom

Methods

oxt :: (Functor f, Functor g) => Lens' (AminoAcid f g (Env r) a) a Source #

Lens for OXT atom

Instances

Instances details
HasOXT OXT Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

oxt :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Lens' (AminoAcid f g (Env OXT) a) a Source #

class Functor r => HasN r where Source #

Has lens to observe, set and modify n_ atom

Methods

n :: (Functor f, Functor g) => Lens' (AminoAcid r f g a) a Source #

Lens for n_ atom

Instances

Instances details
HasN Identity Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

n :: forall (f :: Type -> Type) (g :: Type -> Type) a. (Functor f, Functor g) => Lens' (AminoAcid Identity f g a) a Source #

Functor f => HasN (Env f) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

n :: forall (f0 :: Type -> Type) (g :: Type -> Type) a. (Functor f0, Functor g) => Lens' (AminoAcid (Env f) f0 g a) a Source #

class Functor f => HasAtom f where Source #

Lens to get atom from some enviroment

Methods

atom :: Lens' (f a) a Source #

Lens for exact atom get

Instances

Instances details
HasAtom Identity Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

atom :: Lens' (Identity a) a Source #

Functor r => HasAtom (Env r) Source # 
Instance details

Defined in Bio.Protein.AminoAcid.Instances

Methods

atom :: Lens' (Env r a) a Source #

hydrogens :: Lens' (Env [] a) [a] Source #

Lens to get hydrogens from hydrated atom

Orphan instances

FromThreeSymbols AA Source #

Parse three symbols encoding

Instance details

ThreeSymbols AA Source #

Three symbols encoding

Instance details

Methods

threeSymbols :: AA -> Text Source #

FromSymbol AA Source #

Parse symbol encoding

Instance details

Symbol AA Source #

Symbol encoding

Instance details

Methods

symbol :: AA -> Char Source #

IsString [AA] Source # 
Instance details

Methods

fromString :: String -> [AA] #

IsString (Array Int AA) Source # 
Instance details

Methods

fromString :: String -> Array Int AA #

(Functor nr, HasRadicalType car, Functor cr) => Symbol (AminoAcid nr (Env car) cr a) Source #

Lens to get Symbol from every suitable amino acid

Instance details

Methods

symbol :: AminoAcid nr (Env car) cr a -> Char Source #