Monadic Iteratees: incremental input parsers, processors and transformers
This module provides many basic iteratees from which more complicated
iteratees can be built. In general these iteratees parallel those in
Data.List
, with some additions.
- isFinished :: (Monad m, Nullable s) => Iteratee s m Bool
- stream2list :: (Monad m, Nullable s, ListLike s el) => Iteratee s m [el]
- stream2stream :: (Monad m, Nullable s, Monoid s) => Iteratee s m s
- break :: (Monad m, ListLike s el) => (el -> Bool) -> Iteratee s m s
- dropWhile :: (Monad m, ListLike s el) => (el -> Bool) -> Iteratee s m ()
- drop :: (Monad m, Nullable s, ListLike s el) => Int -> Iteratee s m ()
- head :: (Monad m, ListLike s el) => Iteratee s m el
- tryHead :: (Monad m, ListLike s el) => Iteratee s m (Maybe el)
- last :: (Monad m, ListLike s el, Nullable s) => Iteratee s m el
- heads :: (Monad m, Nullable s, ListLike s el, Eq el) => s -> Iteratee s m Int
- peek :: (Monad m, ListLike s el) => Iteratee s m (Maybe el)
- roll :: (Monad m, Functor m, Nullable s, ListLike s el, ListLike s' s) => Int -> Int -> Iteratee s m s'
- length :: (Monad m, Num a, ListLike s el) => Iteratee s m a
- chunkLength :: (Monad m, ListLike s el) => Iteratee s m (Maybe Int)
- takeFromChunk :: (Monad m, Nullable s, ListLike s el) => Int -> Iteratee s m s
- breakE :: (Monad m, ListLike s el, NullPoint s) => (el -> Bool) -> Enumeratee s s m a
- take :: (Monad m, Nullable s, ListLike s el) => Int -> Enumeratee s s m a
- takeUpTo :: (Monad m, Nullable s, ListLike s el) => Int -> Enumeratee s s m a
- takeWhile :: (ListLike s el, Monad m) => (el -> Bool) -> Iteratee s m s
- takeWhileE :: (Monad m, ListLike s el, NullPoint s) => (el -> Bool) -> Enumeratee s s m a
- mapStream :: (Monad m, ListLike (s el) el, ListLike (s el') el', NullPoint (s el), LooseMap s el el') => (el -> el') -> Enumeratee (s el) (s el') m a
- rigidMapStream :: (Monad m, ListLike s el, NullPoint s) => (el -> el) -> Enumeratee s s m a
- filter :: (Monad m, Functor m, Nullable s, ListLike s el) => (el -> Bool) -> Enumeratee s s m a
- group :: (ListLike s el, Monad m, Nullable s) => Int -> Enumeratee s [s] m a
- groupBy :: (ListLike s el, Monad m, Nullable s) => (el -> el -> Bool) -> Enumeratee s [s] m a
- merge :: (ListLike s1 el1, ListLike s2 el2, Nullable s1, Nullable s2, Monad m, Functor m) => (el1 -> el2 -> b) -> Enumeratee s2 b (Iteratee s1 m) a
- mergeByChunks :: (Nullable c2, Nullable c1, NullPoint c2, NullPoint c1, ListLike c1 el1, ListLike c2 el2, Functor m, Monad m) => (c1 -> c2 -> c3) -> (c1 -> c3) -> (c2 -> c3) -> Enumeratee c2 c3 (Iteratee c1 m) a
- foldl :: (Monad m, ListLike s el, FoldableLL s el) => (a -> el -> a) -> a -> Iteratee s m a
- foldl' :: (Monad m, ListLike s el, FoldableLL s el) => (a -> el -> a) -> a -> Iteratee s m a
- foldl1 :: (Monad m, ListLike s el, FoldableLL s el) => (el -> el -> el) -> Iteratee s m el
- foldl1' :: (Monad m, ListLike s el, FoldableLL s el) => (el -> el -> el) -> Iteratee s m el
- sum :: (Monad m, ListLike s el, Num el) => Iteratee s m el
- product :: (Monad m, ListLike s el, Num el) => Iteratee s m el
- enumPureNChunk :: (Monad m, ListLike s el) => s -> Int -> Enumerator s m a
- enumPair :: (Monad m, Nullable s, ListLike s el) => Iteratee s m a -> Iteratee s m b -> Iteratee s m (a, b)
- enumWith :: (Monad m, Nullable s, ListLike s el) => Iteratee s m a -> Iteratee s m b -> Iteratee s m (a, b)
- zip :: (Monad m, Nullable s, ListLike s el) => Iteratee s m a -> Iteratee s m b -> Iteratee s m (a, b)
- zip3 :: (Monad m, Nullable s, ListLike s el) => Iteratee s m a -> Iteratee s m b -> Iteratee s m c -> Iteratee s m (a, b, c)
- zip4 :: (Monad m, Nullable s, ListLike s el) => Iteratee s m a -> Iteratee s m b -> Iteratee s m c -> Iteratee s m d -> Iteratee s m (a, b, c, d)
- zip5 :: (Monad m, Nullable s, ListLike s el) => Iteratee s m a -> Iteratee s m b -> Iteratee s m c -> Iteratee s m d -> Iteratee s m e -> Iteratee s m (a, b, c, d, e)
- sequence_ :: (Monad m, ListLike s el, Nullable s) => [Iteratee s m a] -> Iteratee s m ()
- mapM_ :: (Monad m, ListLike s el, Nullable s) => (el -> m b) -> Iteratee s m ()
- foldM :: (Monad m, ListLike s b, Nullable s) => (a -> b -> m a) -> a -> Iteratee s m a
- module Data.Iteratee.Iteratee
Iteratees
Iteratee Utilities
stream2list :: (Monad m, Nullable s, ListLike s el) => Iteratee s m [el]Source
Read a stream to the end and return all of its elements as a list. This iteratee returns all data from the stream *strictly*.
stream2stream :: (Monad m, Nullable s, Monoid s) => Iteratee s m sSource
Read a stream to the end and return all of its elements as a stream. This iteratee returns all data from the stream *strictly*.
Basic Iteratees
break :: (Monad m, ListLike s el) => (el -> Bool) -> Iteratee s m sSource
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 of the remaining stream satisfies the predicate.
N.B. breakE
should be used in preference to break
.
break
will retain all data until the predicate is met, which may
result in a space leak.
The analogue of List.break
dropWhile :: (Monad m, ListLike s el) => (el -> Bool) -> Iteratee s m ()Source
Skip all elements while the predicate is true.
The analogue of List.dropWhile
drop :: (Monad m, Nullable s, ListLike s el) => Int -> Iteratee s m ()Source
Drop n elements of the stream, if there are that many.
The analogue of List.drop
head :: (Monad m, ListLike s el) => Iteratee s m elSource
Attempt to read the next element of the stream and return it Raise a (recoverable) error if the stream is terminated.
The analogue of List.head
Because head
can raise an error, it shouldn't be used when constructing
iteratees for convStream
. Use tryHead
instead.
tryHead :: (Monad m, ListLike s el) => Iteratee s m (Maybe el)Source
Similar to head
, except it returns Nothing
if the stream
is terminated.
last :: (Monad m, ListLike s el, Nullable s) => Iteratee s m elSource
Attempt to read the last element of the stream and return it Raise a (recoverable) error if the stream is terminated
The analogue of List.last
heads :: (Monad m, Nullable s, ListLike s el, Eq el) => s -> Iteratee s m IntSource
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.
peek :: (Monad m, ListLike s el) => Iteratee s m (Maybe el)Source
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
.
:: (Monad m, Functor m, Nullable s, ListLike s el, ListLike s' s) | |
=> Int | length of chunk (t) |
-> Int | amount to consume (d) |
-> Iteratee s m s' |
Return a chunk of t
elements length while consuming d
elements
from the stream. Useful for creating a 'rolling average' with
convStream
.
length :: (Monad m, Num a, ListLike s el) => Iteratee s m aSource
Return the total length of the remaining part of the stream.
This forces evaluation of the entire stream.
The analogue of List.length
chunkLength :: (Monad m, ListLike s el) => Iteratee s m (Maybe Int)Source
Get the length of the current chunk, or Nothing
if EOF
.
This function consumes no input.
takeFromChunk :: (Monad m, Nullable s, ListLike s el) => Int -> Iteratee s m sSource
Take n
elements from the current chunk, or the whole chunk if
n
is greater.
Nested iteratee combinators
breakE :: (Monad m, ListLike s el, NullPoint s) => (el -> Bool) -> Enumeratee s s m aSource
Takes an element predicate and an iteratee, running the iteratee on all elements of the stream until the predicate is met.
the following rule relates break
to breakE
break
pred === joinI
(breakE
pred stream2stream)
breakE
should be used in preference to break
whenever possible.
:: (Monad m, Nullable s, ListLike s el) | |
=> Int | number of elements to consume |
-> Enumeratee s s m a |
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.
The analogue of List.take
takeUpTo :: (Monad m, Nullable s, ListLike s el) => Int -> Enumeratee s s m aSource
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.
Iteratees composed with takeUpTo
will consume only enough elements to
reach a done state. Any remaining data will be available in the outer
stream.
> let iter = do h <- joinI $ takeUpTo 5 I.head t <- stream2list return (h,t) > enumPureNChunk [1..10::Int] 3 iter >>= run >>= print (1,[2,3,4,5,6,7,8,9,10]) > enumPureNChunk [1..10::Int] 7 iter >>= run >>= print (1,[2,3,4,5,6,7,8,9,10])
in each case, I.head
consumes only one element, returning the remaining
4 elements to the outer stream
takeWhile :: (ListLike s el, Monad m) => (el -> Bool) -> Iteratee s m sSource
Takes an element predicate and returns the (possibly empty) prefix of the stream. All characters in the string will satisfy the character predicate. If the stream is not terminated, the first character of the remaining stream will not satisfy the predicate.
The analogue of List.takeWhile
, see also break
and takeWhileE
takeWhileE :: (Monad m, ListLike s el, NullPoint s) => (el -> Bool) -> Enumeratee s s m aSource
Takes an element predicate and an iteratee, running the iteratee on all elements of the stream while the predicate is met.
This is preferred to takeWhile
.
mapStream :: (Monad m, ListLike (s el) el, ListLike (s el') el', NullPoint (s el), LooseMap s el el') => (el -> el') -> Enumeratee (s el) (s el') m aSource
Map the stream: 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.
The analog of List.map
rigidMapStream :: (Monad m, ListLike s el, NullPoint s) => (el -> el) -> Enumeratee s s m aSource
filter :: (Monad m, Functor m, Nullable s, ListLike s el) => (el -> Bool) -> Enumeratee s s m aSource
Creates an enumeratee
with only elements from the stream that
satisfy the predicate function. The outer stream is completely consumed.
The analogue of List.filter
:: (ListLike s el, Monad m, Nullable s) | |
=> Int | size of group |
-> Enumeratee s [s] m a |
Creates an Enumeratee
in which elements from the stream are
grouped into sz
-sized blocks. The final block may be smaller
than sz.
groupBy :: (ListLike s el, Monad m, Nullable s) => (el -> el -> Bool) -> Enumeratee s [s] m aSource
Creates an enumeratee
in which elements are grouped into
contiguous blocks that are equal according to a predicate.
The analogue of List.groupBy
merge :: (ListLike s1 el1, ListLike s2 el2, Nullable s1, Nullable s2, Monad m, Functor m) => (el1 -> el2 -> b) -> Enumeratee s2 b (Iteratee s1 m) aSource
merge
offers another way to nest iteratees: as a monad stack.
This allows for the possibility of interleaving data from multiple
streams.
-- print each element from a stream of lines. logger :: (MonadIO m) => Iteratee [ByteString] m () logger = mapM_ (liftIO . putStrLn . B.unpack) -- combine alternating lines from two sources -- To see how this was derived, follow the types from -- 'ileaveLines logger' and work outwards. run =<< enumFile 10 "file1" (joinI $ enumLinesBS $ ( enumFile 10 "file2" . joinI . enumLinesBS $ joinI (ileaveLines logger)) >>= run) ileaveLines :: (Functor m, Monad m) => Enumeratee [ByteString] [ByteString] (Iteratee [ByteString] m) [ByteString] ileaveLines = merge (\l1 l2 -> [B.pack "f1:\n\t" ,l1 ,B.pack "f2:\n\t" ,l2 ]
:: (Nullable c2, Nullable c1, NullPoint c2, NullPoint c1, ListLike c1 el1, ListLike c2 el2, Functor m, Monad m) | |
=> (c1 -> c2 -> c3) | merge function |
-> (c1 -> c3) | |
-> (c2 -> c3) | |
-> Enumeratee c2 c3 (Iteratee c1 m) a |
A version of merge which operates on chunks instead of elements.
mergeByChunks offers more control than merge
. merge
terminates
when the first stream terminates, however mergeByChunks will continue
until both streams are exhausted.
mergeByChunks
guarantees that both chunks passed to the merge function
will have the same number of elements, although that number may vary
between calls.
Folds
foldl :: (Monad m, ListLike s el, FoldableLL s el) => (a -> el -> a) -> a -> Iteratee s m aSource
Left-associative fold.
The analogue of List.foldl
foldl' :: (Monad m, ListLike s el, FoldableLL s el) => (a -> el -> a) -> a -> Iteratee s m aSource
Left-associative fold that is strict in the accumulator.
This function should be used in preference to foldl
whenever possible.
The analogue of List.foldl'
.
foldl1 :: (Monad m, ListLike s el, FoldableLL s el) => (el -> el -> el) -> Iteratee s m elSource
Variant of foldl with no base case. Requires at least one element in the stream.
The analogue of List.foldl1
.
foldl1' :: (Monad m, ListLike s el, FoldableLL s el) => (el -> el -> el) -> Iteratee s m elSource
Strict variant of foldl1
.
Special Folds
Enumerators
Basic enumerators
enumPureNChunk :: (Monad m, ListLike s el) => s -> Int -> Enumerator s m aSource
The pure n-chunk enumerator
It passes a given stream of elements to the iteratee in n
-sized chunks.
Enumerator Combinators
enumPair :: (Monad m, Nullable s, ListLike s el) => Iteratee s m a -> Iteratee s m b -> Iteratee s m (a, b)Source
Enumerate two iteratees over a single stream simultaneously.
Deprecated, use zip
instead.
Compare to zip
.
enumWith :: (Monad m, Nullable s, ListLike s el) => Iteratee s m a -> Iteratee s m b -> Iteratee s m (a, b)Source
Enumerate over two iteratees in parallel as long as the first iteratee is still consuming input. The second iteratee will be terminated with EOF when the first iteratee has completed. An example use is to determine how many elements an iteratee has consumed:
snd <$> enumWith (dropWhile (<5)) length
Compare to zip
zip :: (Monad m, Nullable s, ListLike s el) => Iteratee s m a -> Iteratee s m b -> Iteratee s m (a, b)Source
Enumerate two iteratees over a single stream simultaneously.
Compare to List.zip
.
zip3 :: (Monad m, Nullable s, ListLike s el) => Iteratee s m a -> Iteratee s m b -> Iteratee s m c -> Iteratee s m (a, b, c)Source
zip4 :: (Monad m, Nullable s, ListLike s el) => Iteratee s m a -> Iteratee s m b -> Iteratee s m c -> Iteratee s m d -> Iteratee s m (a, b, c, d)Source
zip5 :: (Monad m, Nullable s, ListLike s el) => Iteratee s m a -> Iteratee s m b -> Iteratee s m c -> Iteratee s m d -> Iteratee s m e -> Iteratee s m (a, b, c, d, e)Source
sequence_ :: (Monad m, ListLike s el, Nullable s) => [Iteratee s m a] -> Iteratee s m ()Source
Enumerate a list of iteratees over a single stream simultaneously and discard the results. This is a different behavior than Prelude's sequence_ which runs iteratees in the list one after the other.
Compare to Prelude.sequence_
.
Monadic functions
mapM_ :: (Monad m, ListLike s el, Nullable s) => (el -> m b) -> Iteratee s m ()Source
Map a monadic function over the elements of the stream and ignore the result.
foldM :: (Monad m, ListLike s b, Nullable s) => (a -> b -> m a) -> a -> Iteratee s m aSource
The analogue of Control.Monad.foldM
Re-exported modules
module Data.Iteratee.Iteratee