Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data BamMeta = BamMeta {
- meta_hdr :: !BamHeader
- meta_refs :: !Refs
- meta_other_shit :: [(BamKey, BamOtherShit)]
- meta_comment :: [Bytes]
- parseBamMeta :: Parser BamMeta
- parseBamMetaLine :: Parser (BamMeta -> BamMeta)
- showBamMeta :: BamMeta -> Builder
- addPG :: Maybe Version -> IO (BamMeta -> BamMeta)
- newtype BamKey = BamKey Word16
- data BamHeader = BamHeader {
- hdr_version :: (Int, Int)
- hdr_sorting :: !BamSorting
- hdr_other_shit :: BamOtherShit
- data BamSQ = BamSQ {}
- data BamSorting
- type BamOtherShit = [(BamKey, Bytes)]
- newtype Refseq = Refseq {}
- invalidRefseq :: Refseq
- isValidRefseq :: Refseq -> Bool
- invalidPos :: Int
- isValidPos :: Int -> Bool
- unknownMapq :: Int
- isKnownMapq :: Int -> Bool
- type Refs = Seq BamSQ
- noRefs :: Refs
- getRef :: Refs -> Refseq -> BamSQ
- compareNames :: Seqid -> Seqid -> Ordering
- flagPaired :: Int
- flagProperlyPaired :: Int
- flagUnmapped :: Int
- flagMateUnmapped :: Int
- flagReversed :: Int
- flagMateReversed :: Int
- flagFirstMate :: Int
- flagSecondMate :: Int
- flagAuxillary :: Int
- flagSecondary :: Int
- flagFailsQC :: Int
- flagDuplicate :: Int
- flagSupplementary :: Int
- eflagTrimmed :: Int
- eflagMerged :: Int
- eflagAlternative :: Int
- eflagExactIndex :: Int
- distinctBin :: Int -> Int -> Int
- data MdOp
- = MdNum Int
- | MdRep Nucleotides
- | MdDel [Nucleotides]
- readMd :: Bytes -> Maybe [MdOp]
- showMd :: [MdOp] -> Bytes
Documentation
BamMeta | |
|
parseBamMeta :: Parser BamMeta Source #
parseBamMetaLine :: Parser (BamMeta -> BamMeta) Source #
showBamMeta :: BamMeta -> Builder Source #
Exactly two characters, for the "named" fields in bam.
BamHeader | |
|
BamSQ | |
|
data BamSorting Source #
Possible sorting orders from bam header. Thanks to samtools, which
doesn't declare sorted files properly, we have to have the stupid
Unknown
state, too.
Instances
Eq BamSorting Source # | |
Defined in Bio.Bam.Header (==) :: BamSorting -> BamSorting -> Bool Source # (/=) :: BamSorting -> BamSorting -> Bool Source # | |
Show BamSorting Source # | |
Defined in Bio.Bam.Header |
type BamOtherShit = [(BamKey, Bytes)] Source #
Reference sequence in Bam Bam enumerates the reference sequences and then sorts by index. We need to track that index if we want to reproduce the sorting order.
Instances
Enum Refseq Source # | |
Defined in Bio.Bam.Header succ :: Refseq -> Refseq Source # pred :: Refseq -> Refseq Source # toEnum :: Int -> Refseq Source # fromEnum :: Refseq -> Int Source # enumFrom :: Refseq -> [Refseq] Source # enumFromThen :: Refseq -> Refseq -> [Refseq] Source # enumFromTo :: Refseq -> Refseq -> [Refseq] Source # enumFromThenTo :: Refseq -> Refseq -> Refseq -> [Refseq] Source # | |
Eq Refseq Source # | |
Ord Refseq Source # | |
Defined in Bio.Bam.Header | |
Show Refseq Source # | |
Ix Refseq Source # | |
Defined in Bio.Bam.Header |
invalidRefseq :: Refseq Source #
The invalid Refseq. Bam uses this value to encode a missing reference sequence.
isValidRefseq :: Refseq -> Bool Source #
Tests whether a reference sequence is valid.
Returns true unless the the argument equals invalidRefseq
.
invalidPos :: Int Source #
The invalid position. Bam uses this value to encode a missing position.
isValidPos :: Int -> Bool Source #
Tests whether a position is valid.
Returns true unless the the argument equals invalidPos
.
unknownMapq :: Int Source #
isKnownMapq :: Int -> Bool Source #
The empty list of references. Needed for BAM files that don't really store alignments.
compareNames :: Seqid -> Seqid -> Ordering Source #
Compares two sequence names the way samtools does. samtools sorts by "strnum_cmp":
- if both strings start with a digit, parse the initial sequence of digits and compare numerically, if equal, continue behind the numbers
- else compare the first characters (possibly NUL), if equal continue behind them
- else both strings ended and the shorter one counts as smaller (and that part is stupid)
flagPaired :: Int Source #
flagUnmapped :: Int Source #
flagReversed :: Int Source #
flagFirstMate :: Int Source #
flagSecondMate :: Int Source #
flagAuxillary :: Int Source #
flagSecondary :: Int Source #
flagFailsQC :: Int Source #
flagDuplicate :: Int Source #
eflagTrimmed :: Int Source #
eflagMerged :: Int Source #
distinctBin :: Int -> Int -> Int Source #
Computes the "distinct bin" according to the BAM binning scheme. If
an alignment starts at pos
and its CIGAR implies a length of len
on the reference, then it goes into bin distinctBin pos len
.