Portability | portable |
---|---|
Maintainer | [email protected] |
Data.Enumerator
Description
An implementation of Oleg Kiselyov’s left-fold enumerators
- data Stream a
- data Step e a m b
- newtype Iteratee e a m b = Iteratee {
- runIteratee :: m (Step e a m b)
- type Enumerator e a m b = Step e a m b -> Iteratee e a m b
- type Enumeratee e aOut aIn m b = Step e aIn m b -> Iteratee e aOut m (Step e aIn m b)
- returnI :: Monad m => Step e a m b -> Iteratee e a m b
- yield :: Monad m => b -> Stream a -> Iteratee e a m b
- continue :: Monad m => (Stream a -> Iteratee e a m b) -> Iteratee e a m b
- throwError :: Monad m => e -> Iteratee e a m b
- catchError :: Monad m => Iteratee e a m b -> (e -> Iteratee e a m b) -> Iteratee e a m b
- liftI :: Monad m => (Stream a -> Step e a m b) -> Iteratee e a m b
- (>>==) :: Monad m => Iteratee e a m b -> (Step e a m b -> Iteratee e a' m b') -> Iteratee e a' m b'
- (==<<) :: Monad m => (Step e a m b -> Iteratee e a' m b') -> Iteratee e a m b -> Iteratee e a' m b'
- ($$) :: Monad m => (Step e a m b -> Iteratee e a' m b') -> Iteratee e a m b -> Iteratee e a' m b'
- (>==>) :: Monad m => Enumerator e a m b -> (Step e a m b -> Iteratee e a' m b') -> Step e a m b -> Iteratee e a' m b'
- (<==<) :: Monad m => (Step e a m b -> Iteratee e a' m b') -> Enumerator e a m b -> Step e a m b -> Iteratee e a' m b'
- run :: Monad m => Iteratee e a m b -> m (Either e b)
- consume :: Monad m => Iteratee e a m [a]
- isEOF :: Monad m => Iteratee e a m Bool
- liftTrans :: (Monad m, MonadTrans t, Monad (t m)) => Iteratee e a m b -> Iteratee e a (t m) b
- liftFoldL :: Monad m => (b -> a -> b) -> b -> Iteratee e a m b
- liftFoldL' :: Monad m => (b -> a -> b) -> b -> Iteratee e a m b
- liftFoldM :: Monad m => (b -> a -> m b) -> b -> Iteratee e a m b
- printChunks :: (MonadIO m, Show a) => Bool -> Iteratee e a m ()
- enumEOF :: Monad m => Enumerator e a m b
- enumList :: Monad m => Integer -> [a] -> Enumerator e a m b
- concatEnums :: Monad m => [Enumerator e a m b] -> Enumerator e a m b
- checkDone :: Monad m => ((Stream a -> Iteratee e a m b) -> Iteratee e a' m (Step e a m b)) -> Enumeratee e a' a m b
- map :: Monad m => (ao -> ai) -> Enumeratee e ao ai m b
- sequence :: Monad m => Iteratee e ao m ai -> Enumeratee e ao ai m b
- joinI :: Monad m => Iteratee e a m (Step e a' m b) -> Iteratee e a m b
- head :: Monad m => Iteratee e a m (Maybe a)
- peek :: Monad m => Iteratee e a m (Maybe a)
- last :: Monad m => Iteratee e a m (Maybe a)
- length :: Monad m => Iteratee e a m Integer
- drop :: Monad m => Integer -> Iteratee e a m ()
- dropWhile :: Monad m => (a -> Bool) -> Iteratee e a m ()
- span :: Monad m => (a -> Bool) -> Iteratee e a m [a]
- break :: Monad m => (a -> Bool) -> Iteratee e a m [a]
Types
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
Continue (Stream a -> Iteratee e a m b) | The |
Yield b (Stream a) | The |
Error e | The |
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
|
type Enumerator e a m b = Step e a m b -> Iteratee e a m bSource
While Iteratee
s consume data, enumerators generate it. Since
is an alias for Iteratee
m (
, Step
e a m b)Enumerator
s can
be considered step transformers of type
.
Step
e a m b -> m (Step
e a m b)
Enumerator
s 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 (Yield
s 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.
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 Iteratee
s 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 (>>==)
($$) :: Monad m => (Step e a m b -> Iteratee e a' m b') -> Iteratee e a m b -> Iteratee e a' m b'Source
($$) = (==<<)
This might be easier to read when passing a chain of iteratees to an enumerator.
(>==>) :: Monad m => Enumerator e a m b -> (Step e a m b -> Iteratee e a' m b') -> Step e a m b -> Iteratee e a' m b'Source
(>==>) e1 e2 s = e1 s >>== e2
(<==<) :: Monad m => (Step e a m b -> Iteratee e a' m b') -> Enumerator e a m b -> Step e a m b -> Iteratee e a' m b'Source
(<==<) = flip (>==>)
Iteratees
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).
consume :: Monad m => Iteratee e a m [a]Source
Consume all input until EOF
, then return consumed input as a list.
liftFoldL :: Monad m => (b -> a -> b) -> b -> Iteratee e a m bSource
Lifts a pure left fold into an iteratee.
liftFoldL' :: Monad m => (b -> a -> b) -> b -> Iteratee e a m bSource
As liftFoldL
, but strict in its accumulator.
liftFoldM :: Monad m => (b -> a -> m b) -> b -> Iteratee e a m bSource
Lifts a monadic left fold into an iteratee.
printChunks :: (MonadIO m, Show a) => Bool -> Iteratee e a m ()Source
Print chunks as they're received from the enumerator, optionally printing empty chunks.
Enumerators
enumEOF :: Monad m => Enumerator e a m bSource
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 Enumerator
s 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” Enumeratee
s 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).