|
|
|
|
|
Description |
Monadic and General Iteratees:
incremental input parsers, processors and transformers
|
|
Synopsis |
|
| | | | | | newtype IterateeG c el m a = IterateeG {} | | type EnumeratorN s_outer el_outer s_inner el_inner m a = IterateeG s_inner el_inner m a -> IterateeG s_outer el_outer m (IterateeG s_inner el_inner m a) | | type EnumeratorGM s el m a = IterateeG s el m a -> m (IterateeG s el m a) | | type EnumeratorGMM sfrom elfrom sto elto m a = IterateeG sto elto m a -> m (IterateeG sfrom elfrom m a) | | joinI :: (StreamChunk s el, StreamChunk s' el', Monad m) => IterateeG s el m (IterateeG s' el' m a) -> IterateeG s el m a | | liftI :: (Monad m, StreamChunk s el) => IterGV s el m a -> IterateeG s el m a | | isFinished :: (StreamChunk s el, Monad m) => IterateeG s el m (Maybe ErrMsg) | | run :: (Monad m, StreamChunk s el) => IterateeG s el m a -> m a | | joinIM :: Monad m => m (IterateeG s el m a) -> IterateeG s el m a | | stream2list :: (StreamChunk s el, Monad m) => IterateeG s el m [el] | | checkIfDone :: (StreamChunk s el, Monad m) => (IterateeG s el m a -> m (IterateeG s el m a)) -> IterGV s el m a -> m (IterateeG s el m a) | | setEOF :: StreamG c el -> ErrMsg | | throwErr :: Monad m => ErrMsg -> IterateeG s el m a | | checkErr :: (Monad m, StreamChunk s el) => IterateeG s el m a -> IterateeG s el m (Either ErrMsg a) | | break :: (StreamChunk s el, Monad m) => (el -> Bool) -> IterateeG s el m (s el) | | drop :: (StreamChunk s el, Monad m) => Int -> IterateeG s el m () | | identity :: Monad m => IterateeG s el m () | | head :: (StreamChunk s el, Monad m) => IterateeG s el m el | | heads :: (StreamChunk s el, Monad m, Eq el) => s el -> IterateeG s el m Int | | peek :: (StreamChunk s el, Monad m) => IterateeG s el m (Maybe el) | | skipToEof :: Monad m => IterateeG s el m () | | length :: (Num a, ListLike (s el) el, Monad m) => IterateeG s el m a | | take :: (StreamChunk s el, Monad m) => Int -> EnumeratorN s el s el m a | | takeR :: (StreamChunk s el, Monad m) => Int -> IterateeG s el m a -> IterateeG s el m (IterateeG s el m a) | | mapStream :: (StreamChunk s el, StreamChunk s el', Monad m) => (el -> el') -> EnumeratorN s el s el' m a | | convStream :: Monad m => IterateeG s el m (Maybe (s' el')) -> EnumeratorN s el s' el' m a | | filter :: (ListLike (s el) el, Monad m) => (el -> Bool) -> EnumeratorN s el s el m a | | foldl :: (ListLike (s el) el, FoldableLL (s el) el, Monad m) => (a -> el -> a) -> a -> IterateeG s el m a | | foldl' :: (ListLike (s el) el, FoldableLL (s el) el, Monad m) => (a -> el -> a) -> a -> IterateeG s el m a | | foldl1 :: (ListLike (s el) el, FoldableLL (s el) el, Monad m) => (el -> el -> el) -> IterateeG s el m el | | enumEof :: Monad m => EnumeratorGM s el m a | | enumErr :: (StreamChunk s el, Monad m) => String -> EnumeratorGM s el m a | | (>.) :: (StreamChunk s el, Monad m) => EnumeratorGM s el m a -> EnumeratorGM s el m a -> EnumeratorGM s el m a | | enumPure1Chunk :: (StreamChunk s el, Monad m) => s el -> EnumeratorGM s el m a | | enumPureNChunk :: (StreamChunk s el, Monad m) => s el -> Int -> EnumeratorGM s el m a | | seek :: Monad m => FileOffset -> IterateeG s el m () | | type FileOffset = COff |
|
|
|
Types
|
|
|
Constructors | | Instances | |
|
|
|
A stream is a (continuing) sequence of elements bundled in Chunks.
The first two variants indicate 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 | | Instances | |
|
|
|
Iteratee -- a generic stream processor, what is being folded over
a stream
When Iteratee is in the done state, it contains the computed
result and the remaining part of the stream.
In the cont state, the iteratee has not finished the computation
and needs more input.
We assume that all iteratees are good -- given bounded input,
they do the bounded amount of computation and take the bounded amount
of resources. The monad m describes the sort of computations done
by the iteratee as it processes the stream. The monad m could be
the identity monad (for pure computations) or the IO monad
(to let the iteratee store the stream processing results as they
are computed).
We also assume that given a terminated stream, an iteratee
moves to the done state, so the results computed so far could be returned.
| Constructors | | Instances | |
|
|
newtype IterateeG c el m a | Source |
|
Constructors | | Instances | |
|
|
|
The type of the converter from the stream with elements el_outer
to the stream with element el_inner. The result is the iteratee
for the outer stream that uses an `IterateeG el_inner m a'
to process the embedded, inner stream as it reads the outer stream.
|
|
|
Each enumerator takes an iteratee and returns an iteratee
an Enumerator is an iteratee transformer.
The enumerator normally stops when the stream is terminated
or when the iteratee moves to the done state, whichever comes first.
When to stop is of course up to the enumerator...
|
|
|
More general enumerator type: enumerator that maps
streams (not necessarily in lock-step). This is
a flattened (`joinI-ed') EnumeratorN sfrom elfrom sto elto m a
|
|
Iteratees
|
|
Iteratee Combinators
|
|
|
The following is a variant of join in the IterateeGM s el m monad
When el' is the same as el, the type of joinI is indeed that of
true monadic join. However, joinI is subtly different: since
generally el' is different from el, it makes no sense to
continue using the internal, IterateeG el' m a: we no longer
have elements of the type el' to feed to that iteratee.
We thus send EOF to the internal Iteratee and propagate its result.
This join function is useful when dealing with `derived iteratees'
for embedded/nested streams. In particular, joinI is useful to
process the result of take, mapStream, or convStream below.
|
|
|
Lift an IterGV result into an IterateeG
|
|
|
Check if a stream has finished (EOF).
|
|
|
Run an IterateeG and get the result. An EOF is sent to the
iteratee as it is run.
|
|
|
A variant of join for Iteratees in a monad.
|
|
|
Read a stream to the end and return all of its elements as a list
|
|
|
If the iteratee (IterGV) has finished, return its value. If it has not
finished then apply it to the given EnumeratorGM.
If in error, throw the error.
|
|
Error handling
|
|
|
Produce the EOF error message. If the stream was terminated because
of an error, keep the original error message.
|
|
|
Report and propagate an error. Disregard the input first and then
propagate the error.
|
|
|
Check if an iteratee produces an error.
Returns 'Right a' if it completes without errors, otherwise 'Left ErrMsg'
checkErr is useful for iteratees that may not terminate, such as head
with an empty stream. In particular, it enables them to be used with
convStream.
|
|
Basic Iteratees
|
|
|
The analogue of List.break
It takes an element predicate and returns the (possibly empty) prefix of
the stream. None of the characters in the string satisfy the character
predicate.
If the stream is not terminated, the first character on the stream
satisfies the predicate.
|
|
|
Skip n elements of the stream, if there are that many
This is the analogue of List.drop
|
|
|
The identity iterator. Doesn't do anything.
|
|
|
Attempt to read the next element of the stream and return it
Raise a (recoverable) error if the stream is terminated
|
|
|
Given a sequence of characters, attempt to match them against
the characters on the stream. Return the count of how many
characters matched. The matched characters are removed from the
stream.
For example, if the stream contains abd, then (heads abc)
will remove the characters ab and return 2.
|
|
|
Look ahead at the next element of the stream, without removing
it from the stream.
Return (Just c) if successful, return Nothing if the stream is
terminated (by EOF or an error)
|
|
|
Skip the rest of the stream
|
|
|
Return the total length of the stream
|
|
Nested iteratee combinators
|
|
|
Read n elements from a stream and apply the given iteratee to the
stream of the read elements. Unless the stream is terminated early, we
read exactly n elements (even if the iteratee has accepted fewer).
|
|
|
Read n elements from a stream and apply the given iteratee to the
stream of the read elements. If the given iteratee accepted fewer
elements, we stop.
This is the variation of take with the early termination
of processing of the outer stream once the processing of the inner stream
finished early.
|
|
|
Map the stream: yet another iteratee transformer
Given the stream of elements of the type el and the function el->el',
build a nested stream of elements of the type el' and apply the
given iteratee to it.
Note the contravariance
|
|
|
Convert one stream into another, not necessarily in lockstep
The transformer mapStream maps one element of the outer stream
to one element of the nested stream. The transformer below is more
general: it may take several elements of the outer stream to produce
one element of the inner stream, or the other way around.
The transformation from one stream to the other is specified as
IterateeGM s el m (Maybe (s' el')). The Maybe type is in case of
errors (or end of stream).
|
|
|
Creates an enumerator with only elements from the stream that
satisfy the predicate function.
|
|
Folds
|
|
|
Left-associative fold.
|
|
|
Left-associative fold that is strict in the accumulator.
|
|
|
Variant of foldl with no base case. Requires at least one element
in the stream.
|
|
Enumerators
|
|
|
The most primitive enumerator: applies the iteratee to the terminated
stream. The result is the iteratee usually in the done state.
|
|
|
Another primitive enumerator: report an error
|
|
|
The composition of two enumerators: essentially the functional composition
It is convenient to flip the order of the arguments of the composition
though: in e1 >. e2, e1 is executed first
|
|
|
The pure 1-chunk enumerator
It passes a given list of elements to the iteratee in one chunk
This enumerator does no IO and is useful for testing of base parsing
|
|
|
The pure n-chunk enumerator
It passes a given chunk of elements to the iteratee in n chunks
This enumerator does no IO and is useful for testing of base parsing
and handling of chunk boundaries
|
|
Misc.
|
|
|
Seek to a position in the stream
|
|
|
|
Produced by Haddock version 2.6.0 |