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

Bio.Chain.Alignment

Synopsis

Alignment function

align :: forall algo m m'. (SequenceAlignment algo, Alignable m, Alignable m') => algo (IxValue m) (IxValue m') -> m -> m' -> AlignmentResult m m' Source #

Align chains using specifed algorithm

Alignment algorithms

newtype EditDistance e1 e2 Source #

Constructors

EditDistance (e1 -> e2 -> Bool) 

data GlobalAlignment a e1 e2 Source #

Constructors

GlobalAlignment (Scoring e1 e2) a 

Instances

Instances details
IsGap g => SequenceAlignment (GlobalAlignment g) Source # 
Instance details

Defined in Bio.Chain.Alignment.Algorithms

Methods

semi :: GlobalAlignment g e1 e2 -> Bool Source #

cond :: (Alignable m, Alignable m') => GlobalAlignment g (IxValue m) (IxValue m') -> Conditions m m' Source #

traceStart :: (Alignable m, Alignable m') => GlobalAlignment g (IxValue m) (IxValue m') -> Matrix m m' -> m -> m' -> (Index m, Index m') Source #

scoreMatrix :: (Alignable m, Alignable m') => GlobalAlignment g (IxValue m) (IxValue m') -> m -> m' -> Matrix m m' Source #

data LocalAlignment a e1 e2 Source #

Constructors

LocalAlignment (Scoring e1 e2) a 

Instances

Instances details
IsGap g => SequenceAlignment (LocalAlignment g) Source # 
Instance details

Defined in Bio.Chain.Alignment.Algorithms

Methods

semi :: LocalAlignment g e1 e2 -> Bool Source #

cond :: (Alignable m, Alignable m') => LocalAlignment g (IxValue m) (IxValue m') -> Conditions m m' Source #

traceStart :: (Alignable m, Alignable m') => LocalAlignment g (IxValue m) (IxValue m') -> Matrix m m' -> m -> m' -> (Index m, Index m') Source #

scoreMatrix :: (Alignable m, Alignable m') => LocalAlignment g (IxValue m) (IxValue m') -> m -> m' -> Matrix m m' Source #

data SemiglobalAlignment a e1 e2 Source #

Constructors

SemiglobalAlignment (Scoring e1 e2) a 

Instances

Instances details
IsGap g => SequenceAlignment (SemiglobalAlignment g) Source # 
Instance details

Defined in Bio.Chain.Alignment.Algorithms

Methods

semi :: SemiglobalAlignment g e1 e2 -> Bool Source #

cond :: (Alignable m, Alignable m') => SemiglobalAlignment g (IxValue m) (IxValue m') -> Conditions m m' Source #

traceStart :: (Alignable m, Alignable m') => SemiglobalAlignment g (IxValue m) (IxValue m') -> Matrix m m' -> m -> m' -> (Index m, Index m') Source #

scoreMatrix :: (Alignable m, Alignable m') => SemiglobalAlignment g (IxValue m) (IxValue m') -> m -> m' -> Matrix m m' Source #

type SimpleGap = Int Source #

Simple gap penalty

type SimpleGap2 = (SimpleGap, SimpleGap) Source #

Gap penalty with different SimpleGap penalties for sequences.

First element of pair is penalty for first sequence passed to alignment algorithm, second element — penalty for second passed sequence.

data AffineGap Source #

Affine gap penalty

Constructors

AffineGap 

Fields

Instances

Instances details
Eq AffineGap Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

Show AffineGap Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

Generic AffineGap Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

Associated Types

type Rep AffineGap :: Type -> Type #

NFData AffineGap Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

Methods

rnf :: AffineGap -> () #

IsGap AffineGap2 Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

IsGap AffineGap Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

type Rep AffineGap Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

type Rep AffineGap = D1 ('MetaData "AffineGap" "Bio.Chain.Alignment.Type" "cobot-0.1.1.7-1gG22cBgMSxAc2IJYQchnS" 'False) (C1 ('MetaCons "AffineGap" 'PrefixI 'True) (S1 ('MetaSel ('Just "gapOpen") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "gapExtend") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

type AffineGap2 = (AffineGap, AffineGap) Source #

Gap penalty with different AffineGap penalties for sequences.

First element of pair is penalty for first sequence passed to alignment algorithm, second element — penalty for second passed sequence.

class IsGap a where Source #

Type class that describes possible gaps in alignments.

Methods

insertCostOpen :: a -> Int Source #

Insertions are gaps in the first argument of an alignment function.

insertCostExtend :: a -> Int Source #

deleteCostOpen :: a -> Int Source #

Deletions are gaps in the second argument of an alignment function.

deleteCostExtend :: a -> Int Source #

isAffine :: a -> Bool Source #

Alignment result types

data AlignmentResult m m' Source #

Sequence Alignment result

Constructors

AlignmentResult 

Fields

Instances

Instances details
Generic (AlignmentResult m m') Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

Associated Types

type Rep (AlignmentResult m m') :: Type -> Type #

Methods

from :: AlignmentResult m m' -> Rep (AlignmentResult m m') x #

to :: Rep (AlignmentResult m m') x -> AlignmentResult m m' #

(NFData a, NFData b, NFData (Index a), NFData (Index b)) => NFData (AlignmentResult a b) Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

Methods

rnf :: AlignmentResult a b -> () #

type Rep (AlignmentResult m m') Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

type Rep (AlignmentResult m m') = D1 ('MetaData "AlignmentResult" "Bio.Chain.Alignment.Type" "cobot-0.1.1.7-1gG22cBgMSxAc2IJYQchnS" 'False) (C1 ('MetaCons "AlignmentResult" 'PrefixI 'True) ((S1 ('MetaSel ('Just "score") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "alignment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Operation (Index m) (Index m')])) :*: (S1 ('MetaSel ('Just "sequence1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m) :*: S1 ('MetaSel ('Just "sequence2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m'))))

data Operation i j Source #

Operation that was performed on current step of alignment

Constructors

INSERT 

Fields

DELETE 

Fields

MATCH 

Fields

Instances

Instances details
(Eq j, Eq i) => Eq (Operation i j) Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

Methods

(==) :: Operation i j -> Operation i j -> Bool #

(/=) :: Operation i j -> Operation i j -> Bool #

(Ord j, Ord i) => Ord (Operation i j) Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

Methods

compare :: Operation i j -> Operation i j -> Ordering #

(<) :: Operation i j -> Operation i j -> Bool #

(<=) :: Operation i j -> Operation i j -> Bool #

(>) :: Operation i j -> Operation i j -> Bool #

(>=) :: Operation i j -> Operation i j -> Bool #

max :: Operation i j -> Operation i j -> Operation i j #

min :: Operation i j -> Operation i j -> Operation i j #

(Show j, Show i) => Show (Operation i j) Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

Methods

showsPrec :: Int -> Operation i j -> ShowS #

show :: Operation i j -> String #

showList :: [Operation i j] -> ShowS #

Generic (Operation i j) Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

Associated Types

type Rep (Operation i j) :: Type -> Type #

Methods

from :: Operation i j -> Rep (Operation i j) x #

to :: Rep (Operation i j) x -> Operation i j #

(NFData j, NFData i) => NFData (Operation i j) Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

Methods

rnf :: Operation i j -> () #

type Rep (Operation i j) Source # 
Instance details

Defined in Bio.Chain.Alignment.Type

type Rep (Operation i j) = D1 ('MetaData "Operation" "Bio.Chain.Alignment.Type" "cobot-0.1.1.7-1gG22cBgMSxAc2IJYQchnS" 'False) (C1 ('MetaCons "INSERT" 'PrefixI 'True) (S1 ('MetaSel ('Just "getJ") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j)) :+: (C1 ('MetaCons "DELETE" 'PrefixI 'True) (S1 ('MetaSel ('Just "getI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i)) :+: C1 ('MetaCons "MATCH" 'PrefixI 'True) (S1 ('MetaSel ('Just "getI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Just "getJ") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j))))

Viewing alignment results

viewAlignment :: forall m m'. (Alignable m, Alignable m', Symbol (IxValue m), Symbol (IxValue m')) => AlignmentResult m m' -> (String, String) Source #

View alignment results as simple strings with gaps.

prettyAlignmment Source #

Arguments

:: forall m m'. (Alignable m, Alignable m', Symbol (IxValue m), Symbol (IxValue m')) 
=> AlignmentResult m m'

Result of alignment to format

-> Int

Desired width of one alignment row

-> String 

Format alignment result as pretty columns of symbols.

Example with width equal to 20:

 0 --------------------  0

 0 TTTTTTTTTTTTTTTTTTTT 19

 0 --GCCTGAATGGTGTGGTGT 17
     || |||||| |||| |||
20 TTGC-TGAATG-TGTG-TGT 36

18 TCGGCGGAGGGACCCAGCTA 37
    || |||||||||||||||
37 -CG-CGGAGGGACCCAGCT- 53

38 AAAAAAAAAA 47

53 ---------- 53

Similarity functions

These are generic variants of similarity and difference functions alongside with their specialised variants. Generic versions take the alignment algorithm used for sequence alignment, an equality function on elements of both sequences to calculate hamming distance on aligned sequences, and the sequences themselves.

Sample usage of generic functions:

>>> similarityGen (GlobalAlignment (\x y -> if x == ord y then 1 else 0) (AffineGap (-11) (-1))) (\x y -> x == ord y) [ord 'R'.. ord 'z'] ['a'..'z']
0.63414633

This one will calculate similarity between a list of Ints and a list of Chars. Generic scoring function used in alignment is \x y -> if x == ord y then 1 else 0. Generic equality function used in hamming distance is \x y -> x == ord y.

Specialised versions do not take the equality function as the sequences are already constrained to have Eq elements.

Sample usage of specialised function is the same as before:

>>> :{
seq1 :: String
seq1 = "EVQLLESGGGLVQPGGSLRLSCAASGFTFSSYAMSWVRQAPGKGLEWVSAISGSGGSTYYADSVKGRFTISRDNSKNTLYLQMNSLRAEDTAVYYCAKVQLERYFDYWGQGTLVTVSS"

seq2 :: String
seq2 = "EVQLLESGGGLVQPGGSLRLSAAASGFTFSTFSMNWVRQAPGKGLEWVSYISRTSKTIYYADSVKGRFTISRDNSKNTLYLQMNSLRAEDTAVYYVARGRFFDYWGQGTLVTVS"

similarity (GlobalAlignment blosum62 (AffineGap (-11) (-1))) s1 s2
:}
0.8130081

Sometimes for biological reasons gaps appearing in one of two sequences, that are being aligned, are not physical. For that reason we might want to use different gap penalties when aligning these sequences.

Example of usage of different gaps when aligning two sequences is presented below:

>>> :{
seq1 :: String
seq1 = "AAAAAAGGGGGGGGGGGGTTTTTTTTT"

seq2 :: String
seq2 = "AAAAAATTTTTTTTT"

gapForSeq1 :: AffineGap
gapForSeq1 = AffineGap (-5) (-1)

gapForSeq2 :: AffineGap
gapForSeq2 = AffineGap (-1000) (-1000) -- basically, we forbid gaps on @seq2@

local = LocalAlignment nuc44 (gapForSeq1, gapForSeq2)

viewAlignment (align local seq1 seq2)
:}
("TTTTTTTTT", "TTTTTTTTT")

similarityGen' :: forall m m'. (Alignable m, Alignable m') => AlignmentResult m m' -> (IxValue m -> IxValue m' -> Bool) -> R Source #

Calculate similarity by precomputed AlignmentResult.

similarityGen :: forall algo m m'. (SequenceAlignment algo, Alignable m, Alignable m') => algo (IxValue m) (IxValue m') -> (IxValue m -> IxValue m' -> Bool) -> m -> m' -> R Source #

Calculate similarity and difference between two sequences, aligning them first using given algorithm.

differenceGen' :: forall m m'. (Alignable m, Alignable m') => AlignmentResult m m' -> (IxValue m -> IxValue m' -> Bool) -> R Source #

differenceGen :: forall algo m m'. (SequenceAlignment algo, Alignable m, Alignable m') => algo (IxValue m) (IxValue m') -> (IxValue m -> IxValue m' -> Bool) -> m -> m' -> R Source #

similarity' :: forall m m'. (Alignable m, Alignable m', IxValue m ~ IxValue m', Eq (IxValue m), Eq (IxValue m')) => AlignmentResult m m' -> R Source #

similarity :: forall algo m m'. (SequenceAlignment algo, Alignable m, Alignable m', IxValue m ~ IxValue m', Eq (IxValue m), Eq (IxValue m')) => algo (IxValue m) (IxValue m') -> m -> m' -> R Source #

difference' :: forall m m'. (Alignable m, Alignable m', IxValue m ~ IxValue m', Eq (IxValue m), Eq (IxValue m')) => AlignmentResult m m' -> R Source #

difference :: forall algo m m'. (SequenceAlignment algo, Alignable m, Alignable m', IxValue m ~ IxValue m', Eq (IxValue m), Eq (IxValue m')) => algo (IxValue m) (IxValue m') -> m -> m' -> R Source #