Monadic Iteratees: incremental input parsers, processors and transformers
- data Stream c
- = EOF (Maybe SomeException)
- | Chunk c
- data StreamStatus
- module Data.Iteratee.Exception
- newtype Iteratee s m a = Iteratee {}
- run :: Monad m => Iteratee s m a -> m a
- tryRun :: (Exception e, Monad m) => Iteratee s m a -> m (Either e a)
- mapIteratee :: (NullPoint s, Monad n, Monad m) => (m a -> n b) -> Iteratee s m a -> Iteratee s n b
- ilift :: (Monad m, Monad n) => (forall r. m r -> n r) -> Iteratee s m a -> Iteratee s n a
- idone :: Monad m => a -> Stream s -> Iteratee s m a
- icont :: (Stream s -> Iteratee s m a) -> Maybe SomeException -> Iteratee s m a
- liftI :: Monad m => (Stream s -> Iteratee s m a) -> Iteratee s m a
- idoneM :: Monad m => a -> Stream s -> m (Iteratee s m a)
- icontM :: Monad m => (Stream s -> Iteratee s m a) -> Maybe SomeException -> m (Iteratee s m a)
- setEOF :: Stream c -> SomeException
Types
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.
EOF (Maybe SomeException) | |
Chunk c |
data StreamStatus Source
Describe the status of a stream of data.
Exception types
module Data.Iteratee.Exception
Iteratees
Monadic iteratee
NullPoint s => MonadTrans (Iteratee s) | |
(Monad m, Nullable s) => Monad (Iteratee s m) | |
(Functor m, Monad m) => Functor (Iteratee s m) | |
(Functor m, Monad m, Nullable s) => Applicative (Iteratee s m) | |
(MonadCatchIO m, Nullable s, NullPoint s) => MonadCatchIO (Iteratee s m) | |
(MonadIO m, Nullable s, NullPoint s) => MonadIO (Iteratee s m) |
Functions
Control functions
run :: Monad m => Iteratee s m a -> m aSource
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 Control.Exception.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 bSource
Transform a computation inside an Iteratee
.
ilift :: (Monad m, Monad n) => (forall r. m r -> n r) -> Iteratee s m a -> Iteratee s n aSource
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 Data.Iteratee.ListLike.merge
.
Creating Iteratees
icontM :: Monad m => (Stream s -> Iteratee s m a) -> Maybe SomeException -> m (Iteratee s m a)Source
Stream Functions
setEOF :: Stream c -> SomeExceptionSource
Produce the EOF
error message. If the stream was terminated because
of an error, keep the error message.