align-affine-0.1.0.0: Sequence alignment with an affine gap penalty model
Safe HaskellNone
LanguageHaskell98

Data.Align.Affine

Description

Pairwise & multi-sequence alignment with an affine gap penalty model. Forked from Data.Align. This algorithm uses a gap opening penalty and a gap extension penalty to score alignments.

Synopsis

Global alignment

align Source #

Arguments

:: (Vector v a, Num s, Ord s) 
=> AlignConfig a s 
-> v a

Left sequence.

-> v a

Right sequence.

-> Trace a s 

Aligns two sequences using the Needleman-Wunsch algorithm. See Needleman & Wunsch 1970: https://doi.org/10.1016/0022-2836(70)90057-4.

alignConfig Source #

Arguments

:: (a -> a -> s)

Scoring function.

-> s

Gap opening score.

-> s

Gap extension score.

-> AlignConfig a s 

This algorithm uses an affine gap penalty model. See section 12.6 "Convex gap weights" in Gusfield 1997: https://doi.org/10.1017/CBO9780511574931.

type Step a = Either (Either a a) (a, a) Source #

Either an unmatched item or a match.

data Trace a s Source #

The result of the alignment.

Instances

Instances details
(Show a, Show s) => Show (Trace a s) Source # 
Instance details

Defined in Data.Align.Affine

Methods

showsPrec :: Int -> Trace a s -> ShowS

show :: Trace a s -> String

showList :: [Trace a s] -> ShowS

traceScore :: Trace a s -> s Source #

trace :: Trace a s -> [Step a] Source #

debugAlign :: [Step Char] -> String Source #

Utility for displaying a Char-based alignment.

Example

>>> :{
let tr = align (alignConfig (\a b -> if a == b then 0.5 else (-0.5)) 
                           (-3) (-0.25)) 
              (Data.Vector.fromList "circumambulate") 
              (Data.Vector.fromList "perambulatory")
in do
  print $ traceScore tr
  putStrLn . debugAlign . trace $ tr
:}

Output

-4.75
circumambulate--
per---ambulatory

debugStrAlign :: [Step String] -> String Source #

Utility for displaying a String-based alignment.

Example

>>> :{
let tr = align (alignConfig (\a b -> if a == b then 0.5 else (-0.5)) 
                            (-3) (-0.25)) 
               (Data.Vector.fromList ["kra","ya","ṇā","ddha","ra","ṇā","tyā","cñā","yāḥ"]) 
               (Data.Vector.fromList ["bha","ra","ṇā","da","pa","ha","ra","ṇā","tyā","cña","yā"])
in do
   print $ traceScore tr
   putStrLn . debugStrAlign . trace $ tr
:}

Output

-4.0
|kra|ya|ṇā|ddha|--|--|ra|ṇā|tyā|cñā|yāḥ|
|bha|ra|ṇā|da  |pa|ha|ra|ṇā|tyā|cñā|yā |

Multi-sequence alignment

centerStar :: (Vector v a, Num s, Ord s, Ord i) => AlignConfig a s -> [(i, v a)] -> MultiTrace i a s Source #

Align multiple sequences using the Center Star method.

See, for example, section 14.6.2, "A bounded-error approximation method for SP alignment" in Gusfield 1997.

Assumes the list of sequences to have length > 1, and the indices to be unique.

data MultiStep a Source #

A step in a multi-sequence alignment.

center :: MultiStep a -> Maybe a Source #

Nothing means gap insertion.

others :: MultiStep a -> [Maybe a] Source #

Parallel to otherIndices.

stepOfAll :: MultiStep a -> [Maybe a] Source #

The center step followed by other steps.

data MultiTrace i a s Source #

The result of a multi-sequence alignment.

allIndices :: MultiTrace i a s -> [i] Source #

The center index followed by other indices.

debugMultiAlign :: [MultiStep Char] -> String Source #

Renders a char-based multi-alignment result to a string.