biohazard-0.6.15: bioinformatics support library

Safe HaskellNone
LanguageHaskell2010

Bio.Base

Description

Common data types used everywhere. This module is a collection of very basic "bioinformatics" data types that are simple, but don't make sense to define over and over.

Synopsis

Documentation

newtype Nucleotide Source #

A nucleotide base. We only represent A,C,G,T. The contained Word8 ist guaranteed to be 0..3.

Constructors

N 

Fields

Instances

Bounded Nucleotide Source # 
Enum Nucleotide Source # 
Eq Nucleotide Source # 
Ord Nucleotide Source # 
Read Nucleotide Source # 
Show Nucleotide Source # 
Ix Nucleotide Source # 
Storable Nucleotide Source # 
Unbox Nucleotide Source # 
Vector Vector Nucleotide Source # 
MVector MVector Nucleotide Source # 
data Vector Nucleotide Source # 
data MVector s Nucleotide Source # 

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 # 
Vector Vector Nucleotides Source # 
Vector Vector_Nucs_half Nucleotides # 
MVector MVector Nucleotides Source # 
Show (Vector_Nucs_half Nucleotides) # 
data Vector Nucleotides Source # 
data MVector s Nucleotides Source # 

newtype Qual Source #

Qualities are stored in deciban, also known as the Phred scale. To represent a value p, we store -10 * log_10 p. Operations work directly on the "Phred" value, as the name suggests. The same goes for the Ord instance: greater quality means higher "Phred" score, meand lower error probability.

Constructors

Q 

Fields

Instances

Bounded Qual Source # 
Eq Qual Source # 

Methods

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

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

Ord Qual Source # 

Methods

compare :: Qual -> Qual -> Ordering #

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

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

(>) :: Qual -> Qual -> Bool #

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

max :: Qual -> Qual -> Qual #

min :: Qual -> Qual -> Qual #

Show Qual Source # 

Methods

showsPrec :: Int -> Qual -> ShowS #

show :: Qual -> String #

showList :: [Qual] -> ShowS #

Storable Qual Source # 

Methods

sizeOf :: Qual -> Int #

alignment :: Qual -> Int #

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

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

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

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

peek :: Ptr Qual -> IO Qual #

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

Unbox Qual Source # 
Vector Vector Qual Source # 
MVector MVector Qual Source # 
data Vector Qual Source # 
data MVector s Qual Source # 

toQual :: (Floating a, RealFrac a) => a -> Qual Source #

newtype Prob' a Source #

A positive floating point value stored in log domain. We store the natural logarithm (makes computation easier), but allow conversions to the familiar "Phred" scale used for Qual values.

Constructors

Pr 

Fields

Instances

Unbox a0 => Vector Vector (Prob' a0) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Prob' a0) -> m (Vector (Prob' a0)) #

basicUnsafeThaw :: PrimMonad m => Vector (Prob' a0) -> m (Mutable Vector (PrimState m) (Prob' a0)) #

basicLength :: Vector (Prob' a0) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Prob' a0) -> Vector (Prob' a0) #

basicUnsafeIndexM :: Monad m => Vector (Prob' a0) -> Int -> m (Prob' a0) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Prob' a0) -> Vector (Prob' a0) -> m () #

elemseq :: Vector (Prob' a0) -> Prob' a0 -> b -> b #

Unbox a0 => MVector MVector (Prob' a0) Source # 

Methods

basicLength :: MVector s (Prob' a0) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Prob' a0) -> MVector s (Prob' a0) #

basicOverlaps :: MVector s (Prob' a0) -> MVector s (Prob' a0) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Prob' a0)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Prob' a0) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Prob' a0 -> m (MVector (PrimState m) (Prob' a0)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Prob' a0) -> Int -> m (Prob' a0) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Prob' a0) -> Int -> Prob' a0 -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Prob' a0) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Prob' a0) -> Prob' a0 -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Prob' a0) -> MVector (PrimState m) (Prob' a0) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Prob' a0) -> MVector (PrimState m) (Prob' a0) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Prob' a0) -> Int -> m (MVector (PrimState m) (Prob' a0)) #

Eq a => Eq (Prob' a) Source # 

Methods

(==) :: Prob' a -> Prob' a -> Bool #

(/=) :: Prob' a -> Prob' a -> Bool #

(Floating a, Fractional a, Ord a) => Fractional (Prob' a) Source # 

Methods

(/) :: Prob' a -> Prob' a -> Prob' a #

recip :: Prob' a -> Prob' a #

fromRational :: Rational -> Prob' a #

(Floating a, Ord a) => Num (Prob' a) Source # 

Methods

(+) :: Prob' a -> Prob' a -> Prob' a #

(-) :: Prob' a -> Prob' a -> Prob' a #

(*) :: Prob' a -> Prob' a -> Prob' a #

negate :: Prob' a -> Prob' a #

abs :: Prob' a -> Prob' a #

signum :: Prob' a -> Prob' a #

fromInteger :: Integer -> Prob' a #

Ord a => Ord (Prob' a) Source # 

Methods

compare :: Prob' a -> Prob' a -> Ordering #

(<) :: Prob' a -> Prob' a -> Bool #

(<=) :: Prob' a -> Prob' a -> Bool #

(>) :: Prob' a -> Prob' a -> Bool #

(>=) :: Prob' a -> Prob' a -> Bool #

max :: Prob' a -> Prob' a -> Prob' a #

min :: Prob' a -> Prob' a -> Prob' a #

RealFloat a => Show (Prob' a) Source # 

Methods

showsPrec :: Int -> Prob' a -> ShowS #

show :: Prob' a -> String #

showList :: [Prob' a] -> ShowS #

Storable a => Storable (Prob' a) Source # 

Methods

sizeOf :: Prob' a -> Int #

alignment :: Prob' a -> Int #

peekElemOff :: Ptr (Prob' a) -> Int -> IO (Prob' a) #

pokeElemOff :: Ptr (Prob' a) -> Int -> Prob' a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Prob' a) #

pokeByteOff :: Ptr b -> Int -> Prob' a -> IO () #

peek :: Ptr (Prob' a) -> IO (Prob' a) #

poke :: Ptr (Prob' a) -> Prob' a -> IO () #

Unbox a0 => Unbox (Prob' a0) Source # 
data MVector s (Prob' a0) Source # 
data MVector s (Prob' a0) = MV_Prob' (MVector s a)
data Vector (Prob' a0) Source # 
data Vector (Prob' a0) = V_Prob' (Vector a)

type Prob = Prob' Double Source #

Common way of using Prob'.

toProb :: Floating a => a -> Prob' a Source #

fromProb :: Floating a => Prob' a -> a Source #

pow :: Num a => Prob' a -> a -> Prob' a infixr 8 Source #

data Word8 :: * #

8-bit unsigned integer type

Instances

Bounded Word8 
Enum Word8 
Eq Word8 

Methods

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

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

Integral Word8 
Data Word8 

Methods

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

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

toConstr :: Word8 -> Constr #

dataTypeOf :: Word8 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Word8 
Ord Word8 

Methods

compare :: Word8 -> Word8 -> Ordering #

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

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

(>) :: Word8 -> Word8 -> Bool #

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

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8 
Real Word8 

Methods

toRational :: Word8 -> Rational #

Show Word8 

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8 
Lift Word8 

Methods

lift :: Word8 -> Q Exp #

Hashable Word8 

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

ToJSON Word8 
ToJSONKey Word8 
FromJSON Word8 
FromJSONKey Word8 
Storable Word8 

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

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

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

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

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

peek :: Ptr Word8 -> IO Word8 #

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

Bits Word8 
FiniteBits Word8 
Prim Word8 
Random Word8 

Methods

randomR :: RandomGen g => (Word8, Word8) -> g -> (Word8, g) #

random :: RandomGen g => g -> (Word8, g) #

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

randoms :: RandomGen g => g -> [Word8] #

randomRIO :: (Word8, Word8) -> IO Word8 #

randomIO :: IO Word8 #

Unbox Word8 
Vector Vector Word8 
MVector MVector Word8 
data Vector Word8 
data MVector s Word8 

toNucleotide :: Char -> Nucleotide Source #

Converts a character into a Nucleotides. The usual codes for A,C,G,T and U are understood, - and . become gaps and everything else is an N.

toNucleotides :: Char -> Nucleotides Source #

Converts a character into a Nucleotides. The usual codes for A,C,G,T and U are understood, - and . become gaps and everything else is an N.

isGap :: Nucleotides -> Bool Source #

Tests if a Nucleotides is a gap. Returns true only for the gap.

isBase :: Nucleotides -> Bool Source #

Tests if a Nucleotides is a base. Returns True for everything but gaps.

isProperBase :: Nucleotides -> Bool Source #

Tests if a Nucleotides is a proper base. Returns True for A,C,G,T only.

compl :: Nucleotide -> Nucleotide Source #

Complements a Nucleotides.

compls :: Nucleotides -> Nucleotides Source #

Complements a Nucleotides.

type Seqid = ByteString Source #

Sequence identifiers are ASCII strings Since we tend to store them for a while, we use strict byte strings.

data Position Source #

Coordinates in a genome. The position is zero-based, no questions about it. Think of the position as pointing to the crack between two bases: looking forward you see the next base to the right, looking in the reverse direction you see the complement of the first base to the left.

To encode the strand, we (virtually) reverse-complement any sequence and prepend it to the normal one. That way, reversed coordinates have a negative sign and automatically make sense. Position 0 could either be the beginning of the sequence or the end on the reverse strand... that ambiguity shouldn't really matter.

Constructors

Pos 

Fields

shiftPosition :: Int -> Position -> Position Source #

Moves a Position. The position is moved forward according to the strand, negative indexes move backward accordingly.

data Range Source #

Ranges in genomes We combine a position with a length. In 'Range pos len', pos is always the start of a stretch of length len. Positions therefore move in the opposite direction on the reverse strand. To get the same stretch on the reverse strand, shift r_pos by r_length, then reverse direction (or call reverseRange).

Constructors

Range 

Fields

Instances

Eq Range Source # 

Methods

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

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

Ord Range Source # 

Methods

compare :: Range -> Range -> Ordering #

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

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

(>) :: Range -> Range -> Bool #

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

max :: Range -> Range -> Range #

min :: Range -> Range -> Range #

Show Range Source # 

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

shiftRange :: Int -> Range -> Range Source #

Moves a Range. This is just shiftPosition lifted.

reverseRange :: Range -> Range Source #

Reverses a Range to give the same Range on the opposite strand.

extendRange :: Int -> Range -> Range Source #

Extends a range. The length of the range is simply increased.

insideRange :: Range -> Range -> Range Source #

Expands a subrange. (range1 insideRange range2) interprets range1 as a subrange of range2 and computes its absolute coordinates. The sequence name of range1 is ignored.

wrapRange :: Int -> Range -> Range Source #

Wraps a range to a region. This simply normalizes the start position to be in the interval '[0,n)', which only makes sense if the Range is to be mapped onto a circular genome. This works on both strands and the strand information is retained.

w2c :: Word8 -> Char #

Conversion between Word8 and Char. Should compile to a no-op.

c2w :: Char -> Word8 #

Unsafe conversion between Char and Word8. This is a no-op and silently truncates to 8 bits Chars > '\255'. It is provided as convenience for ByteString construction.

findAuxFile :: FilePath -> IO FilePath Source #

Finds a file by searching the environment variable BIOHAZARD like a PATH.