biohazard-0.6.2: bioinformatics support library

Safe HaskellNone
LanguageHaskell98

Bio.Bam.Pileup

Contents

Synopsis

TODO*

A whole lot of testing.

Actual genotype calling.

ML fitting and evaluation of parameters for different possible

Maybe specialize to ploidy one and two.

data PrimChunks Source

The primitive pieces for genotype calling: A position, a base represented as four likelihoods, an inserted sequence, and the length of a deleted sequence. The logic is that we look at a base followed by some indel, and all those indels are combined into a single insertion and a single deletion.

Constructors

Seek !Int !PrimBase

skip to position (at start or after N operation)

Indel !Int [DamagedBase] !PrimBase

observed deletion and insertion between two bases

EndOfRead

nothing anymore

data PrimBase Source

Constructors

Base

more chunks

Fields

_pb_wait :: !Int

number of bases to wait due to a deletion

_pb_likes :: !DamagedBase

four likelihoods

_pb_mapq :: !Qual

map quality

_pb_rev :: !Bool

reverse strand?

_pb_chunks :: PrimChunks
 

Instances

data DamagedBase Source

Represents our knowledge about a certain base, which consists of the base itself (A,C,G,T, encoded as 0..3; no Ns), the quality score (anything that isn't A,C,G,T becomes A with quality 0), and a substitution matrix representing post-mortem but pre-sequencing substitutions.

Unfortunately, none of this can be rolled into something more simple, because damage and sequencing error behave so differently.

Constructors

DB 

Fields

db_call :: !Nucleotide
 
db_qual :: !Qual
 
db_dmg :: !Mat44D
 

decompose :: BamRaw -> [Mat44D] -> PrimChunks Source

Decomposes a BAM record into chunks suitable for piling up. We pick apart the CIGAR field, and combine it with sequence and quality as appropriate. We ignore the MD field, even if it is present. Clipped bases are removed/skipped as appropriate. We also ignore the reference allele, in fact, we don't even know it, which nicely avoids any possible reference bias by construction. But we do apply a substitution matrix to each base, which must be supplied along with the read.

data CallStats Source

Statistics about a genotype call. Probably only useful for fitlering (so not very useful), but we keep them because it's easy to track them.

Constructors

CallStats 

type GL = Vector Prob Source

Genotype likelihood values. A variant call consists of a position, some measure of qualities, genotype likelihood values, and a representation of variants. A note about the GL values: VCF would normalize them so that the smallest one becomes zero. We do not do that here, since we might want to compare raw values for a model test. We also store them in a Double to make arithmetics easier. Normalization is appropriate when converting to VCF.

If GL is given, we follow the same order used in VCF: "the ordering of genotypes for the likelihoods is given by: F(jk) = (k*(k+1)2)+j. In other words, for biallelic sites the ordering is: AA,AB,BB; for triallelic sites the ordering is: AA,AB,BB,AC,BC,CC, etc."

data Pile' a b Source

Running pileup results in a series of piles. A Pile has the basic statistics of a VarCall, but no GL values and a pristine list of variants instead of a proper call. We emit one pile with two BasePiles (one for each strand) and one IndelPile (the one immediately following) at a time.

Constructors

Pile 

Instances

(Show a, Show b) => Show (Pile' a b) Source 

pileup :: Monad m => DamageModel Double -> Enumeratee [BamRaw] [Pile] m a Source

The pileup enumeratee takes BamRaws, decomposes them, interleaves the pieces appropriately, and generates Piles. The output will contain at most one BasePile and one IndelPile for each position, piles are sorted by position.

This top level driver receives BamRaws. Unaligned reads and duplicates are skipped (but not those merely failing quality checks). Processing stops when the first read with invalid br_rname is encountered or a t end of file.

newtype PileM m a Source

The pileup logic keeps a current coordinate (just two integers) and two running queues: one of active PrimBases that contribute to current genotype calling and on of waiting PrimBases that will contribute at a later point.

Oppan continuation passing style! Not only is the CPS version of the state monad (we have five distinct pieces of state) somewhat faster, we also need CPS to interact with the mechanisms of Iteratee. It makes implementing yield, peek, and bump straight forward.

Constructors

PileM 

Fields

runPileM :: forall r. (a -> PileF m r) -> PileF m r
 

type PileF m r = Refseq -> Int -> [PrimBase] -> Heap -> DamageModel Double -> (Stream [Pile] -> Iteratee [Pile] m r) -> Stream [BamRaw] -> Iteratee [BamRaw] m (Iteratee [Pile] m r) Source

The things we drag along in PileM. Notes: * The active queue is a simple stack. We add at the front when we encounter reads, which reverses them. When traversing it, we traverse reads backwards, but since we accumulate the BasePile, it gets reversed back. The new active queue, however, is no longer reversed (as it should be). So after the traversal, we reverse it again. (Yes, it is harder to understand than using a proper deque type, but it is cheaper. There may not be much point in the reversing, though.)

upd_pos :: (Int -> Int) -> PileM m () Source

set_pos :: (Refseq, Int) -> PileM m () Source

upd_waiting :: (Heap -> Heap) -> PileM m () Source

yield :: Monad m => Pile -> PileM m () Source

peek :: PileM m (Maybe BamRaw) Source

Inspect next input element, if any. Returns Just b if b is the next input element, Nothing if no such element exists. Waits for more input if nothing is available immediately.

bump :: PileM m () Source

Discard next input element, if any. Does nothing if input has already ended. Waits for input to discard if nothing is available immediately.

consume_active :: a -> (a -> PrimBase -> PileM m a) -> PileM m a Source

pileup' :: Monad m => PileM m () Source

The actual pileup algorithm.

pileup'' :: Monad m => PileM m () Source

partitionPairEithers :: [(a, Either b c)] -> ([(a, b)], [(a, c)]) Source

data Heap Source

We need a simple priority queue. Here's a skew heap (specialized to strict Int priorities and PrimBase values).

Constructors

Empty 
Node !Int !PrimBase Heap Heap