biohazard-1.0.4: 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.

Instance details

Defined in Bio.Iteratee.Base

Methods

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

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

Eq c => Eq (Stream c) Source # 
Instance details

Defined in Bio.Iteratee.Base

Methods

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

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

Show c => Show (Stream c) Source # 
Instance details

Defined in Bio.Iteratee.Base

Methods

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

show :: Stream c -> String #

showList :: [Stream c] -> ShowS #

Semigroup c => Semigroup (Stream c) Source # 
Instance details

Defined in Bio.Iteratee.Base

Methods

(<>) :: Stream c -> Stream c -> Stream c #

sconcat :: NonEmpty (Stream c) -> Stream c #

stimes :: Integral b => b -> Stream c -> Stream c #

Monoid c => Monoid (Stream c) Source # 
Instance details

Defined in Bio.Iteratee.Base

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.

Instances
Show StreamStatus Source # 
Instance details

Defined in Bio.Iteratee.Base

Exception types

Iteratees

newtype Iteratee s m a Source #

Monadic iteratee

Constructors

Iteratee 

Fields

Instances
NullPoint s => MonadTrans (Iteratee s) Source # 
Instance details

Defined in Bio.Iteratee.Base

Methods

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

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

Defined in Bio.Iteratee.Base

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

Defined in Bio.Iteratee.Base

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

Defined in Bio.Iteratee.Base

Methods

pure :: a -> Iteratee s m a #

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

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

(*>) :: 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 # 
Instance details

Defined in Bio.Iteratee.Base

Methods

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

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

Defined in Bio.Iteratee.Base

Methods

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

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

Defined in Bio.Iteratee.Base

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

Defined in Bio.Iteratee.Base

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.

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 #

Instances
NullPoint ByteString Source # 
Instance details

Defined in Bio.Iteratee.Base

NullPoint ByteString Source # 
Instance details

Defined in Bio.Iteratee.Base

NullPoint BgzfChunk Source # 
Instance details

Defined in Bio.Iteratee.Bgzf

NullPoint Block Source # 
Instance details

Defined in Bio.Iteratee.Bgzf

Methods

emptyP :: Block Source #

NullPoint [a] Source # 
Instance details

Defined in Bio.Iteratee.Base

Methods

emptyP :: [a] Source #

NullPoint (Endo a) Source # 
Instance details

Defined in Bio.Iteratee.Base

Methods

emptyP :: Endo a Source #

class NullPoint c => Nullable c where Source #

Nullable container class

Minimal complete definition

nullC

Methods

nullC :: c -> Bool Source #

Instances
Nullable ByteString Source # 
Instance details

Defined in Bio.Iteratee.Base

Nullable ByteString Source # 
Instance details

Defined in Bio.Iteratee.Base

Nullable BgzfChunk Source # 
Instance details

Defined in Bio.Iteratee.Bgzf

Methods

nullC :: BgzfChunk -> Bool Source #

Nullable Block Source # 
Instance details

Defined in Bio.Iteratee.Bgzf

Methods

nullC :: Block -> Bool Source #

Nullable [a] Source # 
Instance details

Defined in Bio.Iteratee.Base

Methods

nullC :: [a] -> Bool Source #

Nullable (Endo BgzfTokens) Source # 
Instance details

Defined in Bio.Iteratee.Builder