iteratee-0.8.1.0: Iteratee-based I/O

Data.Iteratee.ListLike

Contents

Description

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.

Synopsis

Iteratees

Iteratee Utilities

isFinished :: (Monad m, Nullable s) => Iteratee s m BoolSource

Check if a stream has received EOF.

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

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.

roll :: (Monad m, Functor m, Nullable s, ListLike s el, ListLike s' s) => Int -> Int -> Iteratee s m s'Source

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

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 >> iter === joinI (breakE pred iter)

breakE should be used in preference to break whenever possible.

take :: (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. 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.

N.B. If the inner iteratee finishes early, remaining data within the current chunk will be dropped.

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

Map the stream rigidly.

Like mapStream, but the element type cannot change. This function is necessary for ByteString and similar types that cannot have LooseMap instances, and may be more efficient.

filter :: (Monad 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

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

Creates an enumeratee in which elements from the stream are grouped into sz-sized blocks. The outer stream is completely consumed and the final block may be smaller than sz.

groupBy :: (ListLike s el, Monad m, Nullable s) => (el -> el -> Bool) -> Enumeratee s [s] m aSource

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

sum :: (Monad m, ListLike s el, Num el) => Iteratee s m elSource

Sum of a stream.

product :: (Monad m, ListLike s el, Num el) => Iteratee s m elSource

Product of a stream.

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.

Compare to zip.

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

Classes