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

Methods

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

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

basicLength :: Vector Nucleotide -> Int

basicUnsafeSlice :: Int -> Int -> Vector Nucleotide -> Vector Nucleotide

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

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

elemseq :: Vector Nucleotide -> Nucleotide -> b -> b

MVector MVector Nucleotide Source # 
Instance details

Defined in Bio.Base

Methods

basicLength :: MVector s Nucleotide -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Nucleotide -> MVector s Nucleotide

basicOverlaps :: MVector s Nucleotide -> MVector s Nucleotide -> Bool

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

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

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

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

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

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

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

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

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

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

data Vector Nucleotide Source # 
Instance details

Defined in Bio.Base

data Vector Nucleotide = V_Nucleotide (Vector Word8)
data MVector s Nucleotide Source # 
Instance details

Defined in Bio.Base

data MVector s Nucleotide = MV_Nucleotide (MVector s Word8)

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

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

Defined in Bio.Bam.Rec

MVector MVector Nucleotides Source # 
Instance details

Defined in Bio.Base

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)

Show (Vector_Nucs_half Nucleotides) Source # 
Instance details

Defined in Bio.Bam.Rec

data Vector Nucleotides Source # 
Instance details

Defined in Bio.Base

data Vector Nucleotides = V_Nucleotides (Vector Word8)
data MVector s Nucleotides Source # 
Instance details

Defined in Bio.Base

data MVector s Nucleotides = MV_Nucleotides (MVector s Word8)

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 Source #

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

Ord Qual Source # 
Instance details

Defined in Bio.Base

Show Qual Source # 
Instance details

Defined in Bio.Base

Storable Qual Source # 
Instance details

Defined in Bio.Base

Unbox Qual Source # 
Instance details

Defined in Bio.Base

Vector Vector Qual Source # 
Instance details

Defined in Bio.Base

Methods

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

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

basicLength :: Vector Qual -> Int

basicUnsafeSlice :: Int -> Int -> Vector Qual -> Vector Qual

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

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

elemseq :: Vector Qual -> Qual -> b -> b

MVector MVector Qual Source # 
Instance details

Defined in Bio.Base

Methods

basicLength :: MVector s Qual -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Qual -> MVector s Qual

basicOverlaps :: MVector s Qual -> MVector s Qual -> Bool

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

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

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

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

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

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

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

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

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

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

data Vector Qual Source # 
Instance details

Defined in Bio.Base

data Vector Qual = V_Qual (Vector Word8)
data MVector s Qual Source # 
Instance details

Defined in Bio.Base

data MVector s Qual = MV_Qual (MVector s Word8)

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

Methods

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

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

basicLength :: Vector (Prob' a) -> Int

basicUnsafeSlice :: Int -> Int -> Vector (Prob' a) -> Vector (Prob' a)

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

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

elemseq :: Vector (Prob' a) -> Prob' a -> b -> b

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

Defined in Bio.Base

Methods

basicLength :: MVector s (Prob' a) -> Int

basicUnsafeSlice :: Int -> Int -> MVector s (Prob' a) -> MVector s (Prob' a)

basicOverlaps :: MVector s (Prob' a) -> MVector s (Prob' a) -> Bool

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

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

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

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

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

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

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

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

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

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

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

Defined in Bio.Base

Methods

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

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

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

Defined in Bio.Base

Methods

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

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

fromRational :: Rational -> Prob' a Source #

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

Defined in Bio.Base

Methods

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

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

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

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

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

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

fromInteger :: Integer -> Prob' a Source #

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

Defined in Bio.Base

Methods

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

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

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

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

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

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

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

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

Defined in Bio.Base

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

Defined in Bio.Base

Methods

sizeOf :: Prob' a -> Int Source #

alignment :: Prob' a -> Int Source #

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

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

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

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

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

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

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 Source #

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 Source #

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

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 Source #

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

toConstr :: Word8 -> Constr Source #

dataTypeOf :: Word8 -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Num Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word8

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

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 Source #

PrintfArg Word8

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

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

Unbox Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Vector Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

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

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

basicLength :: Vector Word8 -> Int

basicUnsafeSlice :: Int -> Int -> Vector Word8 -> Vector Word8

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

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

elemseq :: Vector Word8 -> Word8 -> b -> b

MVector MVector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s Word8 -> Int

basicUnsafeSlice :: Int -> Int -> MVector s Word8 -> MVector s Word8

basicOverlaps :: MVector s Word8 -> MVector s Word8 -> Bool

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

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

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

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

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

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

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

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

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

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

data Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector Word8 = V_Word8 (Vector Word8)
data MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s Word8 = MV_Word8 (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 # 
Instance details

Defined in Bio.Base

Methods

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

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

Ord Range Source # 
Instance details

Defined in Bio.Base

Show Range Source # 
Instance details

Defined in Bio.Base

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 Source #

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

c2w :: Char -> Word8 Source #

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.