snap-core-0.3.0: Snap: A Haskell Web Framework (Core)

Snap.Iteratee

Contents

Description

Snap Framework type aliases and utilities for iteratees. Note that as a convenience, this module also exports everything from Data.Enumerator in the enumerator library.

Synopsis

Enumerators

enumBS :: Monad m => ByteString -> Enumerator ByteString m aSource

Enumerates a strict bytestring.

enumLBS :: Monad m => ByteString -> Enumerator ByteString m aSource

Enumerates a lazy bytestring.

Iteratee utilities

countBytes :: Monad m => forall a. Iteratee ByteString m a -> Iteratee ByteString m (a, Int64)Source

Wraps an Iteratee, counting the number of bytes consumed by it.

drop' :: Monad m => Int64 -> Iteratee ByteString m ()Source

Skip n elements of the stream, if there are that many

unsafeBufferIterateeWithBuffer :: ForeignPtr CChar -> Iteratee ByteString IO a -> Iteratee ByteString IO aSource

Buffers an iteratee, "unsafely". Here we use a fixed binary buffer which we'll re-use, meaning that if you hold on to any of the bytestring data passed into your iteratee (instead of, let's say, shoving it right out a socket) it'll get changed out from underneath you, breaking referential transparency. Use with caution!

This version accepts a buffer created by mkIterateeBuffer.

unsafeBufferIteratee :: Iteratee ByteString IO a -> IO (Iteratee ByteString IO a)Source

Buffers an iteratee, "unsafely". Here we use a fixed binary buffer which we'll re-use, meaning that if you hold on to any of the bytestring data passed into your iteratee (instead of, let's say, shoving it right out a socket) it'll get changed out from underneath you, breaking referential transparency. Use with caution!

drop :: Monad m => Int -> Iteratee ByteString m ()Source

Skip n elements of the stream, if there are that many

takeExactly :: Monad m => Int64 -> Enumeratee ByteString ByteString m aSource

Reads n bytes from a stream and applies the given iteratee to the stream of the read elements. Reads exactly n bytes, and if the stream is short propagates an error.

Re-export types and functions from Data.Enumerator

data Stream a

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 a m b

Constructors

Continue (Stream a -> Iteratee 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 SomeException

The Iteratee encountered an error which prevents it from proceeding further.

newtype Iteratee a m b

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 a m b)
 

Instances

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

While Iteratees consume data, enumerators generate it. Since Iteratee is an alias for m (Step a m b), Enumerators can be considered step transformers of type Step a m b -> m (Step 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 aOut aIn m b = Step aIn m b -> Iteratee aOut m (Step aIn m b)

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 a m b -> Iteratee a m b

returnI x = Iteratee (return x)

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

yield x chunk = returnI (Yield x chunk)

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

continue k = returnI (Continue k)

throwError :: (Monad m, Exception e) => e -> Iteratee a m b

throwError err = returnI (Error err)

catchError :: Monad m => Iteratee a m b -> (SomeException -> Iteratee a m b) -> Iteratee a m b

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

liftI f = continue (returnI . f)

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

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

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

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

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

($$) = (==<<)

This might be easier to read when passing a chain of iteratees to an enumerator.

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

(>==>) e1 e2 s = e1 s >>== e2

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

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

Iteratees

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

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

run_ :: Monad m => Iteratee a m b -> m b

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

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

isEOF :: Monad m => Iteratee a m Bool

Return True if the next Stream is EOF.

liftTrans :: (Monad m, MonadTrans t, Monad (t m)) => Iteratee a m b -> Iteratee a (t m) b

Lift an Iteratee onto a monad transformer, re-wrapping the Iteratee’s inner monadic values.

liftFoldL :: Monad m => (b -> a -> b) -> b -> Iteratee a m b

Lifts a pure left fold into an iteratee.

liftFoldL' :: Monad m => (b -> a -> b) -> b -> Iteratee a m b

As liftFoldL, but strict in its accumulator.

liftFoldM :: Monad m => (b -> a -> m b) -> b -> Iteratee a m b

Lifts a monadic left fold into an iteratee.

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

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

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

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

Enumerators

enumEOF :: Monad m => Enumerator a m b

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 a m b

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 a m b] -> Enumerator a m b

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

Enumeratees

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

checkDone = checkDoneEx (Chunks [])

Use this for enumeratees which do not have an input buffer.

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

sequence :: Monad m => Iteratee ao m ai -> Enumeratee ao ai m b

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

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