biohazard-0.6.15: bioinformatics support library

Safe HaskellNone
LanguageHaskell2010

Bio.Iteratee

Description

Basically a reexport of Data.Iteratee less the names that clash with Prelude plus a handful of utilities.

Synopsis

Documentation

iGetString :: Int -> Iteratee ByteString m ByteString Source

Collects a string of a given length. Don't use this for long strings, use takeStream instead.

iterGet :: Get a -> Iteratee ByteString m a Source

Convert a Get into an Iteratee. The Get is applied once, the decoded data is returned, unneded input remains in the stream.

iterLoop :: (Nullable s, Monad m) => (a -> Iteratee s m a) -> a -> Iteratee s m a Source

Repeatedly apply an Iteratee to a value until end of stream. Returns the final value.

iLookAhead :: Monoid s => Iteratee s m a -> Iteratee s m a Source

Run an Iteratee, collect the input. When it finishes, return the result along with *all* input. Effectively allows lookahead. Be careful, this will eat memory if the Iteratee doesn't return speedily.

protectTerm :: (Nullable s, MonadIO m) => Iteratee s m a -> Iteratee s m a Source

Protects the terminal from binary junk. If i is an Iteratee that might write binary to stdout, then protectTerm i is the same Iteratee, but it will abort if stdout is a terminal device.

parMapChunksIO :: (MonadIO m, Nullable s) => Int -> (s -> IO t) -> Enumeratee s t m a Source

Parallel map of an IO action over the elements of a stream

This Enumeratee applies an IO action to every chunk of the input stream. These IO actions are run asynchronously in a limited parallel way. Don't forget to evaluate

parRunIO :: MonadIO m => Int -> Enumeratee [IO a] a m b Source

progressGen :: MonadIO m => (Int -> a -> String) -> Int -> (String -> IO ()) -> Enumeratee [a] [a] m b Source

A general progress indicator that prints some message after a set number of records have passed through.

progressNum :: MonadIO m => String -> Int -> (String -> IO ()) -> Enumeratee [a] [a] m b Source

A simple progress indicator that prints the number of records.

progressPos :: MonadIO m => (a -> (Refseq, Int)) -> String -> Refs -> Int -> (String -> IO ()) -> Enumeratee [a] [a] m b Source

A simple progress indicator that prints a position every set number of passed records.

($==) :: Monad m => Enumerator' hdr input m (Iteratee output m result) -> Enumeratee input output m result -> Enumerator' hdr output m result infixl 1 Source

Compose an 'Enumerator\'' with an Enumeratee, giving a new 'Enumerator\''.

class Monad m => MonadIO m where

Methods

liftIO :: IO a -> m a

Instances

MonadIO IO 
MonadIO m => MonadIO (ListT m) 
MonadIO m => MonadIO (MaybeT m) 
MonadIO m => MonadIO (IdentityT m) 
(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
MonadIO m => MonadIO (StateT s m) 
MonadIO m => MonadIO (ReaderT r m) 
MonadIO m => MonadIO (ExceptT e m) 
(Error e, MonadIO m) => MonadIO (ErrorT e m) 
(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
MonadIO m => MonadIO (StateT s m) 
MonadIO m => MonadIO (ContT r m) 
(MonadIO m, Nullable s, NullPoint s) => MonadIO (Iteratee s m) 
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

class MonadCatch m => MonadMask m

Minimal complete definition

mask, uninterruptibleMask

Instances

MonadMask IO 
MonadMask m => MonadMask (IdentityT m) 
(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
MonadMask m => MonadMask (StateT s m) 
MonadMask m => MonadMask (ReaderT r m) 
(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
MonadMask m => MonadMask (StateT s m) 
(MonadMask m, Nullable s, NullPoint s) => MonadMask (Iteratee s m) 
(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 
(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 

lift :: MonadTrans t => forall m a. Monad m => m a -> t m a

liftIO :: MonadIO m => forall a. IO a -> m a

stdin :: Handle

stdout :: Handle

stderr :: Handle

enumAuxFile :: (MonadIO m, MonadMask m) => FilePath -> Iteratee ByteString m a -> m a Source

enumInputs :: (MonadIO m, MonadMask m) => [FilePath] -> Enumerator ByteString m a Source

data Ordering' a Source

Constructors

Less 
Equal a 
NotLess 

mergeSortStreams :: Monad m => (a -> a -> Ordering' a) -> Enumeratee [a] [a] (Iteratee [a] m) b Source

type Enumerator' h eo m b = (h -> Iteratee eo m b) -> m (Iteratee eo m b) Source

type Enumeratee' h ei eo m b = (h -> Iteratee eo m b) -> Iteratee ei m (Iteratee eo m b) Source

mergeEnums' Source

Arguments

:: (Nullable s2, Nullable s1, Monad m) 
=> Enumerator' hi s1 m a

inner enumerator

-> Enumerator' ho s2 (Iteratee s1 m) a

outer enumerator

-> (ho -> Enumeratee s2 s1 (Iteratee s1 m) a)

merging enumeratee

-> Enumerator' hi s1 m a 

Merge two 'Enumerator\''s into one. The header provided by the inner 'Enumerator\'' is passed to the output iterator, the header provided by the outer 'Enumerator\'' is passed to the merging iteratee

XXX Something about those headers is unsatisfactory... there should be an unobtrusive way to combine headers.

data QQ a Source

Constructors

QQ !Int [a] [a] 

lengthQ :: QQ a -> Int Source

pushQ :: a -> QQ a -> QQ a Source

popQ :: QQ a -> Maybe (a, QQ a) Source

cancelAll :: MonadIO m => QQ (Async a) -> m () Source

data ParseError Source

Constructors

ParseError 

Fields

errorContexts :: [String]
 
errorMessage :: String
 

parserToIteratee :: Parser a -> Iteratee ByteString m a Source

A function to convert attoparsec Parsers into Iteratees.

stream2vector :: (MonadIO m, Vector v a) => Iteratee [a] m (v a) Source

Reads the whole stream into a Vector.

stream2vectorN :: (MonadIO m, Vector v a) => Int -> Iteratee [a] m (v a) Source

Equivalent to joinI $ takeStream n $ stream2vector, but more efficient.

data Fd :: *

Instances

Bounded Fd 
Enum Fd 
Eq Fd 
Integral Fd 
Num Fd 
Ord Fd 
Read Fd 
Real Fd 
Show Fd 
Storable Fd 
Bits Fd 
FiniteBits Fd 

withFileFd :: (MonadIO m, MonadMask m) => FilePath -> (Fd -> m a) -> m a Source