Safe Haskell | None |
---|---|
Language | Haskell2010 |
Pileup, similar to Samtools
Pileup turns a sorted sequence of reads into a sequence of "piles", one for each site where a genetic variant might be called. We will scan each read's CIGAR line and MD field in concert with the sequence and effective quality. Effective quality is the lowest available quality score of QUAL, MAPQ, and BQ. For aDNA calling, a base is represented as four probabilities, derived from a position dependent damage model.
Synopsis
- data PrimChunks
- = Seek !Int PrimBase
- | Indel [Nucleotides] [DamagedBase] PrimBase
- | EndOfRead
- data PrimBase = Base {
- _pb_wait :: !Int
- _pb_base :: !DamagedBase
- _pb_mapq :: !Qual
- _pb_chunks :: PrimChunks
- type PosPrimChunks = (Refseq, Int, Bool, PrimChunks)
- data DamagedBase = DB {
- db_call :: !Nucleotide
- db_qual :: !Qual
- db_dmg_tk :: !DmgToken
- db_dmg_pos :: !Int
- db_ref :: !Nucleotides
- newtype DmgToken = DmgToken {
- fromDmgToken :: Int
- dissect :: DmgToken -> BamRaw -> [PosPrimChunks]
- data CallStats = CallStats {
- read_depth :: !Int
- reads_mapq0 :: !Int
- sum_mapq :: !Int
- sum_mapq_squared :: !Int
- newtype V_Nuc = V_Nuc (Vector Nucleotide)
- newtype V_Nucs = V_Nucs (Vector Nucleotides)
- data IndelVariant = IndelVariant {
- deleted_bases :: !V_Nucs
- inserted_bases :: !V_Nuc
- type BasePile = [DamagedBase]
- type IndelPile = [(Qual, ([Nucleotides], [DamagedBase]))]
- data Pile' a b = Pile {
- p_refseq :: !Refseq
- p_pos :: !Int
- p_snp_stat :: !CallStats
- p_snp_pile :: a
- p_indel_stat :: !CallStats
- p_indel_pile :: b
- type Pile = Pile' (BasePile, BasePile) (IndelPile, IndelPile)
- pileup :: Monad m => Stream (Of PosPrimChunks) m b -> Stream (Of Pile) m b
Documentation
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.
Seek !Int PrimBase | skip to position (at start or after N operation) |
Indel [Nucleotides] [DamagedBase] PrimBase | observed deletion and insertion between two bases |
EndOfRead | nothing anymore |
Instances
Show PrimChunks Source # | |
Defined in Bio.Bam.Pileup showsPrec :: Int -> PrimChunks -> ShowS # show :: PrimChunks -> String # showList :: [PrimChunks] -> ShowS # |
Base | more chunks |
|
type PosPrimChunks = (Refseq, Int, Bool, PrimChunks) Source #
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.
Damage information is polymorphic. We might run with a simple version (a matrix) for calling, but we need more (a matrix and a mutable matrix, I think) for estimation.
DB | reference base from MD field |
|
Instances
Show DamagedBase Source # | |
Defined in Bio.Bam.Pileup showsPrec :: Int -> DamagedBase -> ShowS # show :: DamagedBase -> String # showList :: [DamagedBase] -> ShowS # |
dissect :: DmgToken -> BamRaw -> [PosPrimChunks] Source #
Decomposes a BAM record into chunks suitable for piling up. We pick apart the CIGAR and MD fields, and combine them with sequence and quality as appropriate. Clipped bases are removed/skipped as needed. We also apply a substitution matrix to each base, which must be supplied along with the read.
Statistics about a genotype call. Probably only useful for filtering (so not very useful), but we keep them because it's easy to track them.
CallStats | |
|
Instances
Eq CallStats Source # | |
Show CallStats Source # | |
Generic CallStats Source # | |
Semigroup CallStats Source # | |
Monoid CallStats Source # | |
type Rep CallStats Source # | |
Defined in Bio.Bam.Pileup type Rep CallStats = D1 (MetaData "CallStats" "Bio.Bam.Pileup" "biohazard-2.1-LAR9kjxyI4PJ81NLnLu2iq" False) (C1 (MetaCons "CallStats" PrefixI True) ((S1 (MetaSel (Just "read_depth") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "reads_mapq0") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)) :*: (S1 (MetaSel (Just "sum_mapq") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "sum_mapq_squared") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)))) |
data IndelVariant Source #
Instances
type BasePile = [DamagedBase] Source #
Map quality and a list of encountered bases, with damage information and reference base if known.
type IndelPile = [(Qual, ([Nucleotides], [DamagedBase]))] Source #
Map quality and a list of encountered indel variants. The deletion has the reference sequence, if known, an insertion has the inserted sequence with damage information.
Running pileup results in a series of piles. A Pile'
has the
basic statistics of a VarCall
, but no likelihood values and a
pristine list of variants instead of a proper call. We emit one pile
with two BasePile
s (one for each strand) and one IndelPile
(the
one immediately following) at a time.
Pile | |
|
type Pile = Pile' (BasePile, BasePile) (IndelPile, IndelPile) Source #
Raw pile. Bases and indels are piled separately on forward and backward strands.
pileup :: Monad m => Stream (Of PosPrimChunks) m b -> Stream (Of Pile) m b Source #
The pileup enumeratee takes BamRaw
s, dissects them, interleaves
the pieces appropriately, and generates Pile'
s. The output will
contain at most one BasePile
and one IndelPile
for each position,
piles are sorted by position.
This top level driver receives BamRaw
s. 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.