biohazard-1.1.0: 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 # 
Instance details

Defined in Bio.Base

Enum Nucleotide Source # 
Instance details

Defined in Bio.Base

Eq Nucleotide Source # 
Instance details

Defined in Bio.Base

Ord Nucleotide Source # 
Instance details

Defined in Bio.Base

Read Nucleotide Source # 
Instance details

Defined in Bio.Base

Show Nucleotide Source # 
Instance details

Defined in Bio.Base

Ix Nucleotide Source # 
Instance details

Defined in Bio.Base

Storable Nucleotide Source # 
Instance details

Defined in Bio.Base

Unbox Nucleotide Source # 
Instance details

Defined in Bio.Base

Vector Vector Nucleotide Source # 
Instance details

Defined in Bio.Base

MVector MVector Nucleotide Source # 
Instance details

Defined in Bio.Base

data Vector Nucleotide Source # 
Instance details

Defined in Bio.Base

data MVector s Nucleotide Source # 
Instance details

Defined in Bio.Base

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

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 # 
Instance details

Defined in Bio.Base

Eq Qual Source # 
Instance details

Defined in Bio.Base

Methods

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

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

Ord Qual Source # 
Instance details

Defined in Bio.Base

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 # 
Instance details

Defined in Bio.Base

Methods

showsPrec :: Int -> Qual -> ShowS #

show :: Qual -> String #

showList :: [Qual] -> ShowS #

Storable Qual Source # 
Instance details

Defined in Bio.Base

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 # 
Instance details

Defined in Bio.Base

Vector Vector Qual Source # 
Instance details

Defined in Bio.Base

MVector MVector Qual Source # 
Instance details

Defined in Bio.Base

data Vector Qual Source # 
Instance details

Defined in Bio.Base

data MVector s Qual Source # 
Instance details

Defined in Bio.Base

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 a => Vector Vector (Prob' a) Source # 
Instance details

Defined in Bio.Base

Unbox a => MVector MVector (Prob' a) Source # 
Instance details

Defined in Bio.Base

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

Defined in Bio.Base

Methods

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

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

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

Defined in Bio.Base

Methods

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

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

fromRational :: Rational -> Prob' a #

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

Defined in Bio.Base

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 # 
Instance details

Defined in Bio.Base

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 # 
Instance details

Defined in Bio.Base

Methods

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

show :: Prob' a -> String #

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

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

Defined in Bio.Base

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 a => Unbox (Prob' a) Source # 
Instance details

Defined in Bio.Base

data MVector s (Prob' a) Source # 
Instance details

Defined in Bio.Base

data MVector s (Prob' a) = MV_Prob' (MVector s a)
data Vector (Prob' a) Source # 
Instance details

Defined in Bio.Base

data Vector (Prob' a) = 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

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

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

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

Integral Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word8

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

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

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

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

toRational :: Word8 -> Rational #

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word8 -> Q Exp #

PrintfArg Word8

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

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

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word8

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Unbox Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

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

Instances
Eq Position Source # 
Instance details

Defined in Bio.Base

Ord Position Source # 
Instance details

Defined in Bio.Base

Show Position Source # 
Instance details

Defined in Bio.Base

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 # 
Instance details

Defined in Bio.Base

Methods

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

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

Ord Range Source # 
Instance details

Defined in Bio.Base

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 # 
Instance details

Defined in Bio.Base

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.