Safe Haskell | None |
---|---|
Language | Haskell2010 |
Bio.Bam.Rec
Description
Parsers and Printers for BAM and SAM.
Synopsis
- data BamRaw
- bamRaw :: MonadThrow m => Int64 -> Bytes -> m BamRaw
- virt_offset :: BamRaw -> Int64
- raw_data :: BamRaw -> Bytes
- br_copy :: BamRaw -> BamRaw
- data BamRec = BamRec {}
- unpackBam :: BamRaw -> BamRec
- nullBamRec :: BamRec
- getMd :: BamRec -> Maybe [MdOp]
- data LengthMismatch = LengthMismatch !Bytes
- data BrokenRecord = BrokenRecord !Int [Int] !Bytes
- data Cigar = !CigOp :* !Int
- data CigOp
- alignedLength :: Vector v Cigar => v Cigar -> Int
- newtype Nucleotides = Ns {}
- data Vector_Nucs_half a = Vector_Nucs_half !Int !Int !(ForeignPtr Word8)
- type Extensions = [(BamKey, Ext)]
- data Ext
- extAsInt :: Int -> BamKey -> BamRec -> Int
- extAsString :: BamKey -> BamRec -> Bytes
- setQualFlag :: Char -> BamRec -> BamRec
- deleteE :: BamKey -> Extensions -> Extensions
- insertE :: BamKey -> Ext -> Extensions -> Extensions
- updateE :: BamKey -> Ext -> Extensions -> Extensions
- adjustE :: (Ext -> Ext) -> BamKey -> Extensions -> Extensions
- isPaired :: BamRec -> Bool
- isProperlyPaired :: BamRec -> Bool
- isUnmapped :: BamRec -> Bool
- isMateUnmapped :: BamRec -> Bool
- isReversed :: BamRec -> Bool
- isMateReversed :: BamRec -> Bool
- isFirstMate :: BamRec -> Bool
- isSecondMate :: BamRec -> Bool
- isSecondary :: BamRec -> Bool
- isFailsQC :: BamRec -> Bool
- isDuplicate :: BamRec -> Bool
- isSupplementary :: BamRec -> Bool
- isTrimmed :: BamRec -> Bool
- isMerged :: BamRec -> Bool
- isAlternative :: BamRec -> Bool
- isExactIndex :: BamRec -> Bool
- type_mask :: Int
Documentation
Bam record in its native encoding along with virtual address.
Instances
IsBamRec BamRaw Source # | |
Defined in Bio.Bam.Writer Methods pushBam :: BamRaw -> BgzfTokens -> BgzfTokens Source # unpackBamRec :: BamRaw -> BamRec Source # |
bamRaw :: MonadThrow m => Int64 -> Bytes -> m BamRaw Source #
Smart constructor. Makes sure we got a at least a full record.
virt_offset :: BamRaw -> Int64 Source #
More convenient representation of a BAM record.
Invariant: Either b_qual == Nothing
or
fmap V.length b_qual == Just (V.length b_seq)
.
Constructors
BamRec | |
Fields |
Instances
Show BamRec Source # | |
IsBamRec BamRec Source # | |
Defined in Bio.Bam.Writer Methods pushBam :: BamRec -> BgzfTokens -> BgzfTokens Source # unpackBamRec :: BamRec -> BamRec Source # |
nullBamRec :: BamRec Source #
data LengthMismatch Source #
Constructors
LengthMismatch !Bytes |
Instances
Show LengthMismatch Source # | |
Defined in Bio.Bam.Rec Methods showsPrec :: Int -> LengthMismatch -> ShowS # show :: LengthMismatch -> String # showList :: [LengthMismatch] -> ShowS # | |
Exception LengthMismatch Source # | |
Defined in Bio.Bam.Rec Methods toException :: LengthMismatch -> SomeException # |
data BrokenRecord Source #
Constructors
BrokenRecord !Int [Int] !Bytes |
Instances
Show BrokenRecord Source # | |
Defined in Bio.Bam.Rec Methods showsPrec :: Int -> BrokenRecord -> ShowS # show :: BrokenRecord -> String # showList :: [BrokenRecord] -> ShowS # | |
Exception BrokenRecord Source # | |
Defined in Bio.Bam.Rec Methods toException :: BrokenRecord -> SomeException # fromException :: SomeException -> Maybe BrokenRecord # displayException :: BrokenRecord -> String # |
Cigar line in BAM coding Bam encodes an operation and a length into a single integer, we keep those integers in an array.
Instances
Eq Cigar Source # | |
Ord Cigar Source # | |
Show Cigar Source # | |
Storable Cigar Source # | |
alignedLength :: Vector v Cigar => v Cigar -> Int Source #
Extracts the aligned length from a cigar line. This gives the length of an alignment as measured on the reference, which is different from the length on the query or the length of the alignment.
newtype Nucleotides Source #
A nucleotide base in an alignment. Experience says we're dealing with Ns and gaps all the type, so purity be damned, they are included as if they were real bases.
To allow Nucleotides
s to be unpacked and incorporated into
containers, we choose to represent them the same way as the BAM file
format: as a 4 bit wide field. Gaps are encoded as 0 where they
make sense, N is 15. The contained Word8
is guaranteed to be
0..15.
Instances
data Vector_Nucs_half a Source #
A vector that packs two Nucleotides
into one byte, just like Bam does.
Constructors
Vector_Nucs_half !Int !Int !(ForeignPtr Word8) |
Instances
type Extensions = [(BamKey, Ext)] Source #
A collection of extension fields. A BamKey
is actually two ASCII
characters.
Constructors
Int Int | |
Float Float | |
Text Bytes | |
Bin Bytes | |
Char Word8 | |
IntArr (Vector Int) | |
FloatArr (Vector Float) |
deleteE :: BamKey -> Extensions -> Extensions Source #
Deletes all occurences of some extension field.
insertE :: BamKey -> Ext -> Extensions -> Extensions Source #
Blindly inserts an extension field. This can create duplicates (and there is no telling how other tools react to that).
updateE :: BamKey -> Ext -> Extensions -> Extensions Source #
Deletes all occurences of an extension field, then inserts it with
a new value. This is safer than insertE
, but also more expensive.
adjustE :: (Ext -> Ext) -> BamKey -> Extensions -> Extensions Source #
Adjusts a named extension by applying a function.
isProperlyPaired :: BamRec -> Bool Source #
isUnmapped :: BamRec -> Bool Source #
isMateUnmapped :: BamRec -> Bool Source #
isReversed :: BamRec -> Bool Source #
isMateReversed :: BamRec -> Bool Source #
isFirstMate :: BamRec -> Bool Source #
isSecondMate :: BamRec -> Bool Source #
isSecondary :: BamRec -> Bool Source #
isDuplicate :: BamRec -> Bool Source #
isSupplementary :: BamRec -> Bool Source #
isAlternative :: BamRec -> Bool Source #
isExactIndex :: BamRec -> Bool Source #