biohazard-0.6.16: bioinformatics support library

Safe HaskellNone
LanguageHaskell2010

Bio.Iteratee.Base

Contents

Description

Monadic Iteratees: incremental input parsers, processors and transformers

Synopsis

Types

data Stream c Source #

A stream is a (continuing) sequence of elements bundled in Chunks. The first variant indicates termination of the stream. Chunk a gives the currently available part of the stream. The stream is not terminated yet. The case (null Chunk) signifies a stream with no currently available data but which is still continuing. A stream processor should, informally speaking, ``suspend itself'' and wait for more data to arrive.

Constructors

EOF (Maybe SomeException) 
Chunk c 

Instances

Functor Stream Source #

Map a function over a stream.

Methods

fmap :: (a -> b) -> Stream a -> Stream b #

(<$) :: a -> Stream b -> Stream a #

Eq c => Eq (Stream c) Source # 

Methods

(==) :: Stream c -> Stream c -> Bool #

(/=) :: Stream c -> Stream c -> Bool #

Show c => Show (Stream c) Source # 

Methods

showsPrec :: Int -> Stream c -> ShowS #

show :: Stream c -> String #

showList :: [Stream c] -> ShowS #

Monoid c => Monoid (Stream c) Source # 

Methods

mempty :: Stream c #

mappend :: Stream c -> Stream c -> Stream c #

mconcat :: [Stream c] -> Stream c #

data StreamStatus Source #

Describe the status of a stream of data.

Exception types

Iteratees

newtype Iteratee s m a Source #

Monadic iteratee

Constructors

Iteratee 

Fields

Instances

NullPoint s => MonadTrans (Iteratee s) Source # 

Methods

lift :: Monad m => m a -> Iteratee s m a #

(Monad m, Nullable s) => Monad (Iteratee s m) Source # 

Methods

(>>=) :: Iteratee s m a -> (a -> Iteratee s m b) -> Iteratee s m b #

(>>) :: Iteratee s m a -> Iteratee s m b -> Iteratee s m b #

return :: a -> Iteratee s m a #

fail :: String -> Iteratee s m a #

Functor m => Functor (Iteratee s m) Source # 

Methods

fmap :: (a -> b) -> Iteratee s m a -> Iteratee s m b #

(<$) :: a -> Iteratee s m b -> Iteratee s m a #

(Functor m, Monad m, Nullable s) => Applicative (Iteratee s m) Source # 

Methods

pure :: a -> Iteratee s m a #

(<*>) :: Iteratee s m (a -> b) -> Iteratee s m a -> Iteratee s m b #

(*>) :: Iteratee s m a -> Iteratee s m b -> Iteratee s m b #

(<*) :: Iteratee s m a -> Iteratee s m b -> Iteratee s m a #

(MonadIO m, Nullable s, NullPoint s) => MonadIO (Iteratee s m) Source # 

Methods

liftIO :: IO a -> Iteratee s m a #

(MonadThrow m, Nullable s, NullPoint s) => MonadThrow (Iteratee s m) Source # 

Methods

throwM :: Exception e => e -> Iteratee s m a #

(MonadCatch m, Nullable s, NullPoint s) => MonadCatch (Iteratee s m) Source # 

Methods

catch :: Exception e => Iteratee s m a -> (e -> Iteratee s m a) -> Iteratee s m a #

(MonadMask m, Nullable s, NullPoint s) => MonadMask (Iteratee s m) Source # 

Methods

mask :: ((forall a. Iteratee s m a -> Iteratee s m a) -> Iteratee s m b) -> Iteratee s m b #

uninterruptibleMask :: ((forall a. Iteratee s m a -> Iteratee s m a) -> Iteratee s m b) -> Iteratee s m b #

Functions

Control functions

run :: Monad m => Iteratee s m a -> m a Source #

Send EOF to the Iteratee and disregard the unconsumed part of the stream. If the iteratee is in an exception state, that exception is thrown with throw. Iteratees that do not terminate on EOF will throw EofException.

tryRun :: (Exception e, Monad m) => Iteratee s m a -> m (Either e a) Source #

Run an iteratee, returning either the result or the iteratee exception. Note that only internal iteratee exceptions will be returned; exceptions thrown with Control.Exception.throw or Control.Monad.CatchIO.throw will not be returned.

See IFException for details.

mapIteratee :: (NullPoint s, Monad n, Monad m) => (m a -> n b) -> Iteratee s m a -> Iteratee s n b Source #

Deprecated: This function will be removed, compare to ilift

Transform a computation inside an Iteratee.

ilift :: (Monad m, Monad n) => (forall r. m r -> n r) -> Iteratee s m a -> Iteratee s n a Source #

Lift a computation in the inner monad of an iteratee.

A simple use would be to lift a logger iteratee to a monad stack.

logger :: Iteratee String IO ()
logger = mapChunksM_ putStrLn

loggerG :: MonadIO m => Iteratee String m ()
loggerG = ilift liftIO logger

A more complex example would involve lifting an iteratee to work with interleaved streams. See the example at merge.

ifold :: (Monad m, Monad n) => (forall r. m r -> acc -> n (r, acc)) -> acc -> Iteratee s m a -> Iteratee s n (a, acc) Source #

Lift a computation in the inner monad of an iteratee, while threading through an accumulator.

Creating Iteratees

idone :: a -> Stream s -> Iteratee s m a Source #

icont :: (Stream s -> Iteratee s m a) -> Maybe SomeException -> Iteratee s m a Source #

liftI :: (Stream s -> Iteratee s m a) -> Iteratee s m a Source #

idoneM :: Monad m => a -> Stream s -> m (Iteratee s m a) Source #

icontM :: Monad m => (Stream s -> Iteratee s m a) -> Maybe SomeException -> m (Iteratee s m a) Source #

Stream Functions

setEOF :: Stream c -> SomeException Source #

Produce the EOF error message. If the stream was terminated because of an error, keep the error message.

Classes

class NullPoint c where Source #

NullPoint class. Containers that have a null representation, corresponding to Data.Monoid.mempty.

Minimal complete definition

emptyP

Methods

emptyP :: c Source #

class NullPoint c => Nullable c where Source #

Nullable container class

Minimal complete definition

nullC

Methods

nullC :: c -> Bool Source #