enumerator-0.1: Implementation of Oleg Kiselyov's left-fold enumerators

Portabilityportable
Maintainerjmillikin@gmail.com

Data.Enumerator

Contents

Description

An implementation of Oleg Kiselyov’s left-fold enumerators

Synopsis

Types

data Stream a Source

Not to be confused with types from the Stream or stream-fusion packages, a Stream is a sequence of chunks generated by an Enumerator. In contrast to Oleg’s implementation, this stream does not support error handling -- errors encountered while generating a stream are reported in the Step type instead.

(Chunks []) is used to indicate that a stream is still active, but currently has no available data. Iteratees should ignore empty chunks.

Constructors

Chunks [a] 
EOF 

Instances

data Step e a m b Source

Constructors

Continue (Stream a -> Iteratee e a m b)

The Iteratee is capable of accepting more input. Note that more input is not necessarily required; the Iteratee might be able to generate a value immediately if it receives EOF.

Yield b (Stream a)

The Iteratee has received enough input to generate a result. Included in this value is left-over input, which can be passed to composed Iteratees.

Error e

The Iteratee encountered an error which prevents it from proceeding further. The type of error will depend on the Enumerator and/or Iteratee -- common choices are String and SomeException.

newtype Iteratee e a m b Source

The primary data type for this library, which consumes input from a Stream until it either generates a value or encounters an error. Rather than requiring all input at once, an iteratee will return Continue when it is capable of processing more data.

In general, iteratees begin in the Continue state. As each chunk is passed to the continuation, the iteratee returns the next step: Continue for more data, Yield when it's finished, or Error to abort processing.

Constructors

Iteratee 

Fields

runIteratee :: m (Step e a m b)
 

Instances

MonadTrans (Iteratee e a) 
Monad m => Monad (Iteratee e a m) 
Monad m => Functor (Iteratee e a m) 
Monad m => Applicative (Iteratee e a m) 
MonadIO m => MonadIO (Iteratee e a m) 

type Enumerator e a m b = Step e a m b -> Iteratee e a m bSource

While Iteratees consume data, enumerators generate it. Since Iteratee is an alias for m (Step e a m b), Enumerators can be considered step transformers of type Step e a m b -> m (Step e a m b).

Enumerators typically read from an external source (parser, handle, random generator, etc). They feed chunks into an Iteratee until the source runs out of data (triggering EOF) or the iteratee finishes processing (Yields a value).

type Enumeratee e aOut aIn m b = Step e aIn m b -> Iteratee e aOut m (Step e aIn m b)Source

In cases where an enumerator acts as both a source and sink, the resulting type is named an Enumeratee. Enumeratees have two input types, “outer a” (aOut) and “inner a” (aIn).

Primitives

Combinators

These are common patterns which occur whenever iteratees are being defined.

returnI :: Monad m => Step e a m b -> Iteratee e a m bSource

returnI x = Iteratee (return x)

yield :: Monad m => b -> Stream a -> Iteratee e a m bSource

yield x chunk = returnI (Yield x chunk)

continue :: Monad m => (Stream a -> Iteratee e a m b) -> Iteratee e a m bSource

continue k = returnI (Continue k)

throwError :: Monad m => e -> Iteratee e a m bSource

throwError err = returnI (Error err)

liftI :: Monad m => (Stream a -> Step e a m b) -> Iteratee e a m bSource

liftI f = continue (returnI . f)

(>>==) :: Monad m => Iteratee e a m b -> (Step e a m b -> Iteratee e a' m b') -> Iteratee e a' m b'Source

Equivalent to (>>=), but allows Iteratees with different input types to be composed.

(==<<) :: Monad m => (Step e a m b -> Iteratee e a' m b') -> Iteratee e a m b -> Iteratee e a' m b'Source

(==<<) = flip (>>==)

Iteratees

consume :: Monad m => Iteratee e a m [a]Source

Consume all input until EOF, then return consumed input as a list.

isEOF :: Monad m => Iteratee e a m BoolSource

Return True if the next Stream is EOF.

Enumerators

enumEOF :: Monad m => Enumerator e a m bSource

The most primitive enumerator; simply sends EOF. The iteratee must either yield a value or throw an error continuing receiving EOF will not terminate with any useful value.

enumList :: Monad m => Integer -> [a] -> Enumerator e a m bSource

Another small, useful enumerator separates an input list into chunks, and sends them to the iteratee. This is useful for testing iteratees in pure code.

concatEnums :: Monad m => [Enumerator e a m b] -> Enumerator e a m bSource

Compose a list of Enumerators using '(>>==)'

Enumeratees

checkDone :: Monad m => ((Stream a -> Iteratee e a m b) -> Iteratee e a' m (Step e a m b)) -> Enumeratee e a' a m bSource

A common pattern in Enumeratee implementations is to check whether the inner Iteratee has finished, and if so, to return its output. checkDone passes its parameter a continuation if the Iteratee can still consume input, or yields otherwise.

map :: Monad m => (ao -> ai) -> Enumeratee e ao ai m bSource

sequence :: Monad m => Iteratee e ao m ai -> Enumeratee e ao ai m bSource

joinI :: Monad m => Iteratee e a m (Step e a' m b) -> Iteratee e a m bSource

joinI is used to “flatten” Enumeratees into an Iteratee.

Parser combinators

Oleg’s original IterateeM.hs includes some basic iteratees for parsing, so this section ports them to the new interface. However, in practice most parsing will be performed with enumerator-based interfaces to existing parser libraries (such as Parsec or Attoparsec).

head :: Monad m => Iteratee e a m (Maybe a)Source

peek :: Monad m => Iteratee e a m (Maybe a)Source

last :: Monad m => Iteratee e a m (Maybe a)Source

dropWhile :: Monad m => (a -> Bool) -> Iteratee e a m ()Source

span :: Monad m => (a -> Bool) -> Iteratee e a m [a]Source

break :: Monad m => (a -> Bool) -> Iteratee e a m [a]Source

break p = span (not . p)

Utility functions

run :: Monad m => Iteratee e a m b -> m (Either e b)Source

Run an iteratee until it finishes, and return either the final value (if it succeeded) or the error (if it failed).

printChunks :: (MonadIO m, Show a) => Bool -> Iteratee e a m ()Source

Print chunks as they're received from the enumerator, optionally printing empty chunks.