biohazard-1.0.0: 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.

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 

Fields

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 # 

Methods

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

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

Ord Cigar Source # 

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 # 

Methods

showsPrec :: Int -> Cigar -> ShowS #

show :: Cigar -> String #

showList :: [Cigar] -> ShowS #

Storable Cigar Source # 

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 () #

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 # 
Enum Nucleotides Source # 
Eq Nucleotides Source # 
Ord Nucleotides Source # 
Read Nucleotides Source # 
Show Nucleotides Source # 
Ix Nucleotides Source # 
Storable Nucleotides Source # 
Unbox Nucleotides Source # 
MVector MVector Nucleotides Source # 

Methods

basicLength :: MVector s Nucleotides -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Nucleotides -> MVector s Nucleotides

basicOverlaps :: MVector s Nucleotides -> MVector s Nucleotides -> Bool

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Nucleotides)

basicInitialize :: PrimMonad m => MVector (PrimState m) Nucleotides -> m ()

basicUnsafeReplicate :: PrimMonad m => Int -> Nucleotides -> m (MVector (PrimState m) Nucleotides)

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Nucleotides -> Int -> m Nucleotides

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Nucleotides -> Int -> Nucleotides -> m ()

basicClear :: PrimMonad m => MVector (PrimState m) Nucleotides -> m ()

basicSet :: PrimMonad m => MVector (PrimState m) Nucleotides -> Nucleotides -> m ()

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Nucleotides -> MVector (PrimState m) Nucleotides -> m ()

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Nucleotides -> MVector (PrimState m) Nucleotides -> m ()

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Nucleotides -> Int -> m (MVector (PrimState m) Nucleotides)

Vector Vector Nucleotides Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Nucleotides -> m (Vector Nucleotides)

basicUnsafeThaw :: PrimMonad m => Vector Nucleotides -> m (Mutable Vector (PrimState m) Nucleotides)

basicLength :: Vector Nucleotides -> Int

basicUnsafeSlice :: Int -> Int -> Vector Nucleotides -> Vector Nucleotides

basicUnsafeIndexM :: Monad m => Vector Nucleotides -> Int -> m Nucleotides

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Nucleotides -> Vector Nucleotides -> m ()

elemseq :: Vector Nucleotides -> Nucleotides -> b -> b

Vector Vector_Nucs_half Nucleotides 
Show (Vector_Nucs_half Nucleotides) # 
data Vector Nucleotides Source # 
data Vector Nucleotides = V_Nucleotides (Vector Word8)
data MVector s Nucleotides Source # 
data MVector s Nucleotides = MV_Nucleotides (MVector s Word8)

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

A collection of extension fields. The key is actually only two Chars, but that proved impractical. (Hmm... we could introduce a Key type that is a 16 bit int, then give it an instance IsString... practical?)

data Ext Source #

Constructors

Int Int 
Float Float 
Text Bytes 
Bin Bytes 
Char Word8 
IntArr (Vector Int) 
FloatArr (Vector Float) 

Instances

Eq Ext Source # 

Methods

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

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

Ord Ext Source # 

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 # 

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: 2.1

Enum Word32

Since: 2.1

Eq Word32

Since: 2.1

Methods

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

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

Integral Word32

Since: 2.1

Data Word32

Since: 4.0.0.0

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: 2.1

Ord Word32

Since: 2.1

Read Word32

Since: 2.1

Real Word32

Since: 2.1

Show Word32

Since: 2.1

Ix Word32

Since: 2.1

Lift Word32 

Methods

lift :: Word32 -> Q Exp #

Storable Word32

Since: 2.1

Bits Word32

Since: 2.1

FiniteBits Word32

Since: 4.6.0.0

Unbox Word32 
Prim Word32 
Hashable Word32 

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

Random Word32 

Methods

randomR :: RandomGen g => (Word32, Word32) -> g -> (Word32, g)

random :: RandomGen g => g -> (Word32, g)

randomRs :: RandomGen g => (Word32, Word32) -> g -> [Word32]

randoms :: RandomGen g => g -> [Word32]

randomRIO :: (Word32, Word32) -> IO Word32

randomIO :: IO Word32

MVector MVector Word32 

Methods

basicLength :: MVector s Word32 -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Word32 -> MVector s Word32

basicOverlaps :: MVector s Word32 -> MVector s Word32 -> Bool

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Word32)

basicInitialize :: PrimMonad m => MVector (PrimState m) Word32 -> m ()

basicUnsafeReplicate :: PrimMonad m => Int -> Word32 -> m (MVector (PrimState m) Word32)

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Word32 -> Int -> m Word32

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Word32 -> Int -> Word32 -> m ()

basicClear :: PrimMonad m => MVector (PrimState m) Word32 -> m ()

basicSet :: PrimMonad m => MVector (PrimState m) Word32 -> Word32 -> m ()

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Word32 -> MVector (PrimState m) Word32 -> m ()

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Word32 -> MVector (PrimState m) Word32 -> m ()

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Word32 -> Int -> m (MVector (PrimState m) Word32)

Vector Vector Word32 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Word32 -> m (Vector Word32)

basicUnsafeThaw :: PrimMonad m => Vector Word32 -> m (Mutable Vector (PrimState m) Word32)

basicLength :: Vector Word32 -> Int

basicUnsafeSlice :: Int -> Int -> Vector Word32 -> Vector Word32

basicUnsafeIndexM :: Monad m => Vector Word32 -> Int -> m Word32

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Word32 -> Vector Word32 -> m ()

elemseq :: Vector Word32 -> Word32 -> b -> b

data Vector Word32 
data Vector Word32 = V_Word32 (Vector Word32)
data MVector s Word32 
data MVector s Word32 = MV_Word32 (MVector s Word32)