iteratee-0.8.9.6: Iteratee-based I/O

Safe HaskellNone

Data.Iteratee.PTerm

Contents

Description

Enumeratees - pass terminals variant.

Provides enumeratees that pass terminal markers (EOF) to the inner iteratee.

Most enumeratees, upon receipt of EOF, will enter a done state and return the inner iteratee without sending EOF to it. This allows for composing enumerators as in:

 myEnum extraData i = do
 nested <- enumFile "file" (mapChunks unpacker i)
 inner <- run nested
 enumList extraData inner

if mapChunks unpacker sent EOF to the inner iteratee i, there would be no way to submit extra data to it after runing the result from enumFile.

In certain cases, this is not the desired behavior. Consider:

 consumer :: Iteratee String IO ()
 consumer = liftI (go 0)
   where
     go c (Chunk xs) = liftIO (putStr s) >> liftI (go c)
     go 10 e         = liftIO (putStr "10 loops complete")
                         >> idone () (Chunk "")
     go n  e         = I.seek 0 >> liftI (go (n+1))

The consumer iteratee does not complete until after it has received 10 EOFs. If you attempt to use it in a standard enumeratee, it will never terminate. When the outer enumeratee is terminated, the inner iteratee will remain in a cont state, but in general there is no longer any valid data for the continuation. The enumeratee itself must pass the EOF marker to the inner iteratee and remain in a cont state until the inner iteratee signals its completion.

All enumeratees in this module will pass EOF terminators to the inner iteratees.

Synopsis

Nested iteratee combinators

mapChunksPT :: NullPoint s => (s -> s') -> Enumeratee s s' m aSource

Convert one stream into another with the supplied mapping function.

A version of mapChunks that sends EOFs to the inner iteratee.

mapChunksMPT :: (Monad m, NullPoint s, Nullable s) => (s -> m s') -> Enumeratee s s' m aSource

Convert a stream of s to a stream of s' using the supplied function.

A version of mapChunksM that sends EOFs to the inner iteratee.

convStreamPT :: (Monad m, Nullable s, NullPoint s') => Iteratee s m s' -> Enumeratee s s' m aSource

Convert one stream into another, not necessarily in lockstep.

A version of convStream that sends EOFs to the inner iteratee.

unfoldConvStreamPT :: (Monad m, Nullable s, NullPoint s') => (acc -> Iteratee s m (acc, s')) -> acc -> Enumeratee s s' m aSource

The most general stream converter.

A version of unfoldConvStream that sends EOFs to the inner iteratee.

unfoldConvStreamCheckPT :: (Monad m, Nullable elo) => (((Stream eli -> Iteratee eli m a) -> Maybe SomeException -> Iteratee elo m (Iteratee eli m a)) -> Enumeratee elo eli m a) -> (acc -> Iteratee elo m (acc, eli)) -> acc -> Enumeratee elo eli m aSource

A version of unfoldConvStreamCheck that sends EOFs to the inner iteratee.

ListLike analog functions

breakEPT :: (ListLike s el, NullPoint s) => (el -> Bool) -> Enumeratee s s m aSource

A variant of breakE that passes EOFs.

takePTSource

Arguments

:: (Monad m, Nullable s, ListLike s el) 
=> Int

number of elements to consume

-> Enumeratee s s m a 

A variant of take that passes EOFs.

takeUpToPT :: (Monad m, Nullable s, ListLike s el) => Int -> Enumeratee s s m aSource

A variant of takeUpTo that passes EOFs.

takeWhileEPT :: (ListLike s el, NullPoint s) => (el -> Bool) -> Enumeratee s s m aSource

A variant of takeWhileE that passes EOFs.

mapStreamPT :: (ListLike (s el) el, ListLike (s el') el', NullPoint (s el), LooseMap s el el') => (el -> el') -> Enumeratee (s el) (s el') m aSource

A variant of mapStream that passes EOFs.

rigidMapStreamPT :: (ListLike s el, NullPoint s) => (el -> el) -> Enumeratee s s m aSource

A variant of rigidMapStream that passes EOFs.

filterPT :: (Monad m, Functor m, Nullable s, ListLike s el) => (el -> Bool) -> Enumeratee s s m aSource

A variant of filter that passes EOFs.