biohazard-1.0.4: bioinformatics support library

Safe HaskellNone
LanguageHaskell2010

Bio.Bam.Rec

Description

Parsers and Printers for BAM and SAM. We employ an Iteratee interface, and we strive to support everything possible in BAM. So far, the implementation of the nucleotides is somewhat lacking: we do not have support for ambiguity codes, and the "=" symbol is not understood.

Synopsis

Documentation

data BamRaw Source #

Bam record in its native encoding along with virtual address.

Instances
IsBamRec BamRaw Source # 
Instance details

Defined in Bio.Bam.Writer

bamRaw :: FileOffset -> Bytes -> BamRaw Source #

Smart constructor. Makes sure we got a at least a full record.

data BamRec Source #

internal representation of a BAM record

Constructors

BamRec 
Instances
Show BamRec Source # 
Instance details

Defined in Bio.Bam.Rec

IsBamRec BamRec Source # 
Instance details

Defined in Bio.Bam.Writer

data Cigar Source #

Cigar line in BAM coding Bam encodes an operation and a length into a single integer, we keep those integers in an array.

Constructors

!CigOp :* !Int infix 9 
Instances
Eq Cigar Source # 
Instance details

Defined in Bio.Bam.Rec

Methods

(==) :: Cigar -> Cigar -> Bool #

(/=) :: Cigar -> Cigar -> Bool #

Ord Cigar Source # 
Instance details

Defined in Bio.Bam.Rec

Methods

compare :: Cigar -> Cigar -> Ordering #

(<) :: Cigar -> Cigar -> Bool #

(<=) :: Cigar -> Cigar -> Bool #

(>) :: Cigar -> Cigar -> Bool #

(>=) :: Cigar -> Cigar -> Bool #

max :: Cigar -> Cigar -> Cigar #

min :: Cigar -> Cigar -> Cigar #

Show Cigar Source # 
Instance details

Defined in Bio.Bam.Rec

Methods

showsPrec :: Int -> Cigar -> ShowS #

show :: Cigar -> String #

showList :: [Cigar] -> ShowS #

Storable Cigar Source # 
Instance details

Defined in Bio.Bam.Rec

Methods

sizeOf :: Cigar -> Int #

alignment :: Cigar -> Int #

peekElemOff :: Ptr Cigar -> Int -> IO Cigar #

pokeElemOff :: Ptr Cigar -> Int -> Cigar -> IO () #

peekByteOff :: Ptr b -> Int -> IO Cigar #

pokeByteOff :: Ptr b -> Int -> Cigar -> IO () #

peek :: Ptr Cigar -> IO Cigar #

poke :: Ptr Cigar -> Cigar -> IO () #

data CigOp Source #

Constructors

Mat 
Ins 
Del 
Nop 
SMa 
HMa 
Pad 
Instances
Bounded CigOp Source # 
Instance details

Defined in Bio.Bam.Rec

Enum CigOp Source # 
Instance details

Defined in Bio.Bam.Rec

Eq CigOp Source # 
Instance details

Defined in Bio.Bam.Rec

Methods

(==) :: CigOp -> CigOp -> Bool #

(/=) :: CigOp -> CigOp -> Bool #

Ord CigOp Source # 
Instance details

Defined in Bio.Bam.Rec

Methods

compare :: CigOp -> CigOp -> Ordering #

(<) :: CigOp -> CigOp -> Bool #

(<=) :: CigOp -> CigOp -> Bool #

(>) :: CigOp -> CigOp -> Bool #

(>=) :: CigOp -> CigOp -> Bool #

max :: CigOp -> CigOp -> CigOp #

min :: CigOp -> CigOp -> CigOp #

Show CigOp Source # 
Instance details

Defined in Bio.Bam.Rec

Methods

showsPrec :: Int -> CigOp -> ShowS #

show :: CigOp -> String #

showList :: [CigOp] -> ShowS #

Ix CigOp Source # 
Instance details

Defined in Bio.Bam.Rec

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 Nucleotidess 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.

Constructors

Ns 

Fields

Instances
Bounded Nucleotides Source # 
Instance details

Defined in Bio.Base

Enum Nucleotides Source # 
Instance details

Defined in Bio.Base

Eq Nucleotides Source # 
Instance details

Defined in Bio.Base

Ord Nucleotides Source # 
Instance details

Defined in Bio.Base

Read Nucleotides Source # 
Instance details

Defined in Bio.Base

Show Nucleotides Source # 
Instance details

Defined in Bio.Base

Ix Nucleotides Source # 
Instance details

Defined in Bio.Base

Storable Nucleotides Source # 
Instance details

Defined in Bio.Base

Unbox Nucleotides Source # 
Instance details

Defined in Bio.Base

Vector Vector Nucleotides Source # 
Instance details

Defined in Bio.Base

Vector Vector_Nucs_half Nucleotides # 
Instance details

Defined in Bio.Bam.Rec

MVector MVector Nucleotides Source # 
Instance details

Defined in Bio.Base

Show (Vector_Nucs_half Nucleotides) # 
Instance details

Defined in Bio.Bam.Rec

data Vector Nucleotides Source # 
Instance details

Defined in Bio.Base

data MVector s Nucleotides Source # 
Instance details

Defined in Bio.Base

type Extensions = [(BamKey, Ext)] Source #

A collection of extension fields. A BamKey is actually two ASCII characters.

data Ext Source #

Instances
Eq Ext Source # 
Instance details

Defined in Bio.Bam.Rec

Methods

(==) :: Ext -> Ext -> Bool #

(/=) :: Ext -> Ext -> Bool #

Ord Ext Source # 
Instance details

Defined in Bio.Bam.Rec

Methods

compare :: Ext -> Ext -> Ordering #

(<) :: Ext -> Ext -> Bool #

(<=) :: Ext -> Ext -> Bool #

(>) :: Ext -> Ext -> Bool #

(>=) :: Ext -> Ext -> Bool #

max :: Ext -> Ext -> Ext #

min :: Ext -> Ext -> Ext #

Show Ext Source # 
Instance details

Defined in Bio.Bam.Rec

Methods

showsPrec :: Int -> Ext -> ShowS #

show :: Ext -> String #

showList :: [Ext] -> ShowS #

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.

progressBam :: MonadIO m => String -> Refs -> Int -> (String -> IO ()) -> Enumeratee [BamRaw] [BamRaw] m a Source #

A simple progress indicator that prints sequence id and position.

data Word32 #

32-bit unsigned integer type

Instances
Bounded Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word32 -> Word32 -> Bool #

(/=) :: Word32 -> Word32 -> Bool #

Integral Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word32

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word32 -> c Word32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word32 #

toConstr :: Word32 -> Constr #

dataTypeOf :: Word32 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word32) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word32) #

gmapT :: (forall b. Data b => b -> b) -> Word32 -> Word32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

Num Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word32

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word32 -> Q Exp #

PrintfArg Word32

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word32

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word32

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Hashable Word32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

Prim Word32 
Instance details

Defined in Data.Primitive.Types

Unbox Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Word32 
Instance details

Defined in Data.Vector.Unboxed.Base