Safe Haskell | Safe-Infered |
---|
Data.Iteratee.Base
Contents
Description
Monadic Iteratees: incremental input parsers, processors and transformers
- data Stream c
- = EOF (Maybe SomeException)
- | Chunk c
- module Data.Iteratee.Exception
- newtype Iteratee s m a = Iteratee {}
- run :: forall s m a. Monad m => Iteratee s m a -> m a
- tryRun :: forall s m a e. (Exception e, Monad m) => Iteratee s m a -> m (Either e a)
- ilift :: forall m n s a. (Monad m, Monad n) => (forall r. m r -> n r) -> Iteratee s m a -> Iteratee s n a
- ifold :: forall m n acc s a. (Monad m, Monad n) => (forall r. m r -> acc -> n (r, acc)) -> acc -> Iteratee s m a -> Iteratee s n (a, acc)
- idone :: a -> Iteratee s m a
- icont :: (Stream s -> m (Iteratee s m a, Stream s)) -> Iteratee s m a
- icontP :: Monad m => (Stream s -> (Iteratee s m a, Stream s)) -> Iteratee s m a
- ierr :: Iteratee s m a -> SomeException -> Iteratee s m a
- ireq :: m b -> (b -> Iteratee s m a) -> Iteratee s m a
- liftI :: Monad m => (Stream s -> (Iteratee s m a, Stream s)) -> Iteratee s m a
- idoneM :: Monad m => a -> m (Iteratee s m a)
- ierrM :: Monad m => Iteratee s m a -> 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.
Constructors
EOF (Maybe SomeException) | |
Chunk c |
Exception types
module Data.Iteratee.Exception
Iteratees
Monadic iteratee
Constructors
Iteratee | |
Instances
MonadBase b m => MonadBase b (Iteratee s m) | |
(MonadBaseControl b m, Nullable s) => MonadBaseControl b (Iteratee s m) | |
MonadTrans (Iteratee s) | |
(NullPoint s, Nullable s) => MonadTransControl (Iteratee s) | |
Monad m => Monad (Iteratee s m) | |
Functor m => Functor (Iteratee s m) | |
(Functor m, Monad m) => Applicative (Iteratee s m) | |
MonadCatchIO m => MonadCatchIO (Iteratee s m) | |
MonadIO m => MonadIO (Iteratee s m) |
Functions
Control functions
run :: forall s m a. 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 throw
. Iteratees that do not terminate
on EOF
will throw EofException
.
tryRun :: forall s m a e. (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 :: forall m n s a. (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 merge
.
ifold :: forall m n acc s a. (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
ierr :: Iteratee s m a -> SomeException -> Iteratee s m aSource
liftI :: Monad m => (Stream s -> (Iteratee s m a, Stream s)) -> Iteratee s m aSource
identical to icont, left in for compatibility-ish reasons
Stream Functions
setEOF :: Stream c -> SomeExceptionSource
Produce the EOF
error message. If the stream was terminated because
of an error, keep the error message.