Safe Haskell | None |
---|
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.
- enumBS :: Monad m => ByteString -> Enumerator ByteString m a
- enumLBS :: Monad m => ByteString -> Enumerator ByteString m a
- enumBuilder :: Monad m => Builder -> Enumerator Builder m a
- enumFile :: FilePath -> Enumerator ByteString IO a
- enumFilePartial :: FilePath -> (Int64, Int64) -> Enumerator ByteString IO a
- data InvalidRangeException
- joinI' :: Monad m => Iteratee a m (Step a m b) -> Iteratee a m b
- countBytes :: Monad m => forall a. Iteratee ByteString m a -> Iteratee ByteString m (a, Int64)
- drop' :: Monad m => Int64 -> Iteratee ByteString m ()
- mkIterateeBuffer :: IO (ForeignPtr CChar)
- unsafeBufferIterateeWithBuffer :: ForeignPtr CChar -> Iteratee ByteString IO a -> Iteratee ByteString IO a
- unsafeBufferIteratee :: Iteratee ByteString IO a -> IO (Iteratee ByteString IO a)
- take :: Monad m => Int -> Enumeratee ByteString ByteString m a
- drop :: Monad m => Int -> Iteratee ByteString m ()
- takeExactly :: Monad m => Int64 -> Enumeratee ByteString ByteString m a
- takeNoMoreThan :: Monad m => Int64 -> Enumeratee ByteString ByteString m a
- skipToEof :: Monad m => Iteratee a m ()
- mapEnum :: Monad m => (aOut -> aIn) -> (aIn -> aOut) -> Enumerator aIn m a -> Enumerator aOut m a
- mapIter :: Monad m => (aOut -> aIn) -> (aIn -> aOut) -> Iteratee aIn m a -> Iteratee aOut m a
- enumBuilderToByteString :: MonadIO m => Enumeratee Builder ByteString m a
- unsafeEnumBuilderToByteString :: MonadIO m => Enumeratee Builder ByteString m a
- enumByteStringToBuilder :: MonadIO m => Enumeratee ByteString Builder m a
- killIfTooSlow :: MonadIO m => m () -> Double -> Int -> Iteratee ByteString m a -> Iteratee ByteString m a
- data TooManyBytesReadException
- data ShortWriteException
- data RateTooSlowException
- data Stream a
- data Step a m b
- newtype Iteratee a m b = Iteratee {
- runIteratee :: m (Step a m b)
- type Enumerator a m b = Step a m b -> Iteratee a m b
- type Enumeratee ao ai m b = Step ai m b -> Iteratee ao m (Step ai m b)
- returnI :: Monad m => Step a m b -> Iteratee a m b
- yield :: Monad m => b -> Stream a -> Iteratee a m b
- continue :: Monad m => (Stream a -> Iteratee a m b) -> Iteratee a m b
- throwError :: (Monad m, Exception e) => e -> Iteratee a m b
- 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
- (>>==) :: Monad m => Iteratee a m b -> (Step a m b -> Iteratee a' m b') -> Iteratee a' m b'
- (==<<) :: Monad m => (Step a m b -> Iteratee a' m b') -> Iteratee a m b -> Iteratee a' m b'
- ($$) :: Monad m => (Step a m b -> Iteratee a' m b') -> Iteratee a m b -> Iteratee a' m b'
- (>==>) :: Monad m => Enumerator a m b -> (Step a m b -> Iteratee a' m b') -> Step a m b -> Iteratee a' m b'
- (<==<) :: Monad m => (Step a m b -> Iteratee a' m b') -> Enumerator a m b -> Step a m b -> Iteratee a' m b'
- ($=) :: Monad m => Enumerator ao m (Step ai m b) -> Enumeratee ao ai m b -> Enumerator ai m b
- (=$) :: Monad m => Enumeratee ao ai m b -> Iteratee ai m b -> Iteratee ao m b
- run :: Monad m => Iteratee a m b -> m (Either SomeException b)
- run_ :: Monad m => Iteratee a m b -> m b
- consume :: Monad m => Iteratee a m [a]
- isEOF :: Monad m => Iteratee a m Bool
- liftTrans :: (Monad m, MonadTrans t, Monad (t m)) => Iteratee a m b -> Iteratee a (t m) b
- liftFoldL :: Monad m => (b -> a -> b) -> b -> Iteratee a m b
- liftFoldL' :: Monad m => (b -> a -> b) -> b -> Iteratee a m b
- liftFoldM :: Monad m => (b -> a -> m b) -> b -> Iteratee a m b
- printChunks :: (MonadIO m, Show a) => Bool -> Iteratee a m ()
- head :: Monad m => Iteratee a m (Maybe a)
- peek :: Monad m => Iteratee a m (Maybe a)
- enumEOF :: Monad m => Enumerator a m b
- enumList :: Monad m => Integer -> [a] -> Enumerator a m b
- concatEnums :: Monad m => [Enumerator a m b] -> Enumerator a m b
- checkDone :: Monad m => ((Stream a -> Iteratee a m b) -> Iteratee a' m (Step a m b)) -> Enumeratee a' a m b
- 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
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.
enumBuilder :: Monad m => Builder -> Enumerator Builder m aSource
Enumerates a Builder.
enumFile :: FilePath -> Enumerator ByteString IO aSource
enumFilePartial :: FilePath -> (Int64, Int64) -> Enumerator ByteString IO aSource
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
mkIterateeBuffer :: IO (ForeignPtr CChar)Source
Creates a buffer to be passed into unsafeBufferIterateeWithBuffer
.
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!
take :: Monad m => Int -> Enumeratee ByteString ByteString m aSource
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.
takeNoMoreThan :: Monad m => Int64 -> Enumeratee ByteString ByteString m aSource
mapEnum :: Monad m => (aOut -> aIn) -> (aIn -> aOut) -> Enumerator aIn m a -> Enumerator aOut m aSource
enumBuilderToByteString :: MonadIO m => Enumeratee Builder ByteString m aSource
enumByteStringToBuilder :: MonadIO m => Enumeratee ByteString Builder m aSource
:: MonadIO m | |
=> m () | action to bump timeout |
-> Double | minimum data rate, in bytes per second |
-> Int | minimum amount of time to let the iteratee run for |
-> Iteratee ByteString m a | iteratee consumer to wrap |
-> Iteratee ByteString m a |
Re-export types and functions from Data.Enumerator
data Stream a
A Stream
is a sequence of chunks generated by an Enumerator
.
(
is used to indicate that a stream is still active, but
currently has no available data. Iteratees should ignore empty chunks.
Chunks
[])
data Step a m b
Continue (Stream a -> Iteratee a m b) | The |
Yield b (Stream a) | The |
Error SomeException | The |
newtype Iteratee a m b
The primary data type for this library; an iteratee consumes chunks of input from a stream until it either yields a value or encounters an error.
Compatibility note: Iteratee
will become abstract in enumerator_0.5
. If
you depend on internal implementation details, please import
Data.Enumerator.Internal
.
Iteratee | |
|
type Enumerator a m b = Step a m b -> Iteratee a m b
Enumerators are sources of data, to be consumed by iteratees. Enumerators typically read from an external source (parser, handle, random generator, etc), then feed chunks into an tteratee until:
- The input source runs out of data.
- The iteratee yields a result value.
- The iteratee throws an exception.
type Enumeratee ao ai m b = Step ai m b -> Iteratee ao m (Step ai m b)
An enumeratee acts as a stream adapter; place one between an enumerator and an iteratee, and it changes the type or contents of the input stream.
Most users will want to combine enumerators, enumeratees, and iteratees
using the stream combinators joinI
and joinE
, or their operator aliases
(=$)
and ($=)
. These combinators are used to manage how left-over input
is passed between elements of the data processing pipeline.
Primitives
Combinators
These are common patterns which occur whenever iteratees are being defined.
yield :: Monad m => b -> Stream a -> Iteratee a m b
yield
x extra =returnI
(Yield
x extra)
WARNING: due to the current encoding of iteratees in this library,
careless use of the yield
primitive may violate the monad laws.
To prevent this, always make sure that an iteratee never yields
extra data unless it has received at least one input element.
More strictly, iteratees may not yield data that they did not
receive as input. Don't use yield
to “inject” elements
into the stream.
throwError :: (Monad m, Exception e) => e -> Iteratee a m b
The moral equivalent of throwIO
for iteratees.
catchError :: Monad m => Iteratee a m b -> (SomeException -> Iteratee a m b) -> Iteratee a m b
Runs the iteratee, and calls an exception handler if an Error
is
returned. By handling errors within the enumerator library, and requiring
all errors to be represented by SomeException
, libraries with
varying error types can be easily composed.
WARNING: Within the error handler, it is difficult or impossible to know
how much input the original iteratee has consumed. Users are strongly
advised to wrap all uses of catchError
with an appropriate isolation
enumeratee, such as Data.Enumerator.List.isolate
or
Data.Enumerator.Binary.isolate
, which will handle input framing even
in the face of unexpected errors.
Since: 0.1.1
liftI :: Monad m => (Stream a -> Step a m b) -> Iteratee a m b
Deprecated in 0.4.5: use continue
instead
(>>==) :: Monad m => Iteratee a m b -> (Step a m b -> Iteratee a' m b') -> Iteratee a' m b'
The most primitive stream operator. iter >>== enum
returns a new
iteratee which will read from enum
before continuing.
(>==>) :: Monad m => Enumerator a m b -> (Step a m b -> Iteratee a' m b') -> Step a m b -> Iteratee a' m b'
(<==<) :: Monad m => (Step a m b -> Iteratee a' m b') -> Enumerator a m b -> Step a m b -> Iteratee a' m b'
($=) :: Monad m => Enumerator ao m (Step ai m b) -> Enumeratee ao ai m b -> Enumerator ai m b
“Wraps” an enumerator inner in an enumeratee wrapper. The resulting enumerator will generate wrapper’s output type.
As an example, consider an enumerator that yields line character counts for a text file (e.g. for source code readability checking):
enumFileCounts :: FilePath -> Enumerator Int IO b
It could be written with either joinE
or ($=)
:
import Data.Text as T import Data.Enumerator.List as EL import Data.Enumerator.Text as ET enumFileCounts path = joinE (enumFile path) (EL.map T.length) enumFileCounts path = enumFile path $= EL.map T.length
Compatibility note: in version 0.4.15, the associativity of ($=)
was
changed from infixr 0
to infixl 1
.
Since: 0.4.9
(=$) :: Monad m => Enumeratee ao ai m b -> Iteratee ai m b -> Iteratee ao m b
“Wraps” an iteratee inner in an enumeratee wrapper. The resulting iteratee will consume wrapper’s input type and yield inner’s output type.
Note: if the inner iteratee yields leftover input when it finishes, that extra will be discarded.
As an example, consider an iteratee that converts a stream of UTF8-encoded
bytes into a single Text
:
consumeUTF8 :: Monad m => Iteratee ByteString m Text
It could be written with either joinI
or (=$)
:
import Data.Enumerator.Text as ET consumeUTF8 = joinI (decode utf8 $$ ET.consume) consumeUTF8 = decode utf8 =$ ET.consume
Since: 0.4.9
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).
import Data.Enumerator import Data.Enumerator.List as EL main = do result <- run (EL.iterate succ 'A' $$ EL.take 5) case result of Left exc -> putStrLn ("Got an exception: " ++ show exc) Right chars -> putStrLn ("Got characters: " ++ show chars)
run_ :: Monad m => Iteratee a m b -> m b
Like run
, except errors are converted to exceptions and thrown.
Primarily useful for small scripts or other simple cases.
import Data.Enumerator import Data.Enumerator.List as EL main = do chars <- run_ (EL.iterate succ 'A' $$ EL.take 5) putStrLn ("Got characters: " ++ show chars)
Since: 0.4.1
isEOF :: Monad m => Iteratee a m Bool
Check whether a stream has reached EOF. Note that if the stream is not
at EOF, isEOF
may cause data to be read from the enumerator.
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 its
inner monadic values.
Since: 0.1.1
liftFoldL :: Monad m => (b -> a -> b) -> b -> Iteratee a m b
Deprecated in 0.4.5: use fold
instead
Since: 0.1.1
liftFoldL' :: Monad m => (b -> a -> b) -> b -> Iteratee a m b
Deprecated in 0.4.5: use fold
instead
Since: 0.1.1
liftFoldM :: Monad m => (b -> a -> m b) -> b -> Iteratee a m b
Deprecated in 0.4.5: use foldM
instead
Since: 0.1.1
Print chunks as they're received from the enumerator, optionally printing empty chunks.
head :: Monad m => Iteratee a m (Maybe a)
Get the next element from the stream, or Nothing
if the stream has
ended.
Since: 0.4.5
peek :: Monad m => Iteratee a m (Maybe a)
Peek at the next element in the stream, or Nothing
if the stream
has ended.
Enumerators
enumEOF :: Monad m => Enumerator a m b
Sends EOF
to its iteratee. Most clients should use run
or run_
instead.
enumList :: Monad m => Integer -> [a] -> Enumerator a m b
concatEnums :: Monad m => [Enumerator a m b] -> Enumerator a m b
Compose a list of Enumerator
s 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
applies f to each input element and
feeds the resulting outputs to the inner iteratee.
map
f
Since: 0.4.8
sequence :: Monad m => Iteratee ao m ai -> Enumeratee ao ai m b
Feeds outer input elements into the provided iteratee until it yields an inner input, passes that to the inner iteratee, and then loops.