align-0.1.1.2: Sequence alignment algorithms.

Safe HaskellNone
LanguageHaskell98

Data.Align

Contents

Description

Collection of functions for global, local and multi-sequence alignment.

Synopsis

Global and local 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.

>>> :{
let tr = align
           (alignConfig (\a b -> if a == b then 1 else (-0.25 :: Double)) 
                        (-0.5) (-1))
           (Data.Vector.fromList "dopple")
           (Data.Vector.fromList "applied")
in do
   print $ traceScore tr
   putStrLn . debugAlign . trace $ tr
:}
1.25
doppl-e-
-applied

alignConfig Source

Arguments

:: (a -> a -> s)

Scoring function.

-> s

Initial gap score.

-> s

Gap score.

-> AlignConfig a s 

Configures the scores used when aligning. The gap scores should be negative in order to be penalties.

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

(Show a, Show s) => Show (Trace a s) 

traceScore :: Trace a s -> s Source

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

Align streams using sliding windows

windowedAlign Source

Arguments

:: (Num s, Eq s, Ord s) 
=> AlignConfig a s 
-> Int

Window size.

-> [a]

Left stream.

-> [a]

Right stream.

-> [Step a]

Alignment result.

Aligns long streams by performing alignment on windowed sections.

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 heuristic method by Chin, Ho, Lam, Wong and Chan (2003). http://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.90.7448&rep=rep1&type=pdf. 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.

Debugging and demonstration

debugAlign :: [Step Char] -> String Source

Utility for displaying a Char-based alignment.

debugMultiAlign :: [MultiStep Char] -> String Source

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