enumerator-0.4.16: Reliable, high-performance processing with left-fold enumerators

Portabilityportable
Maintainerjmillikin@gmail.com

Data.Enumerator

Contents

Description

For compatibility reasons, this module should imported qualified:

 import qualified Data.Enumerator as E

Synopsis

Types

newtype Iteratee a m b Source

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.

Constructors

Iteratee 

Fields

runIteratee :: m (Step a m b)
 

Instances

MonadTrans (Iteratee a) 
Monad m => Monad (Iteratee a m) 
Monad m => Functor (Iteratee a m) 
(Typeable a, Typeable1 m) => Typeable1 (Iteratee a m)

Since: 0.4.6

Monad m => Applicative (Iteratee a m) 
MonadIO m => MonadIO (Iteratee a m) 

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

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)Source

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.

Running iteratees

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

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 bSource

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

Operators

Compatibility note: Most of these will be obsoleted by version 0.5. Please make sure your .cabal files have a <0.5 limit on the enumerator dependency.

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

The most primitive stream operator. iter >>== enum returns a new iteratee which will read from enum before continuing.

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

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

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

($$) = (==<<)

This is somewhat easier to read when constructing an iteratee from many processing stages. You can treat it like ($), and read the data flow from left to right.

Since: 0.1.1

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

(>==>) enum1 enum2 step = enum1 step >>== enum2

The moral equivalent of (>=>) for iteratees.

Since: 0.1.1

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

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

Since: 0.1.1

(=$) :: Monad m => Enumeratee ao ai m b -> Iteratee ai m b -> Iteratee ao m bSource

“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

($=) :: Monad m => Enumerator ao m (Step ai m b) -> Enumeratee ao ai m b -> Enumerator ai m bSource

“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

Error handling

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

The moral equivalent of throwIO for iteratees.

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

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

Miscellaneous

concatEnums :: Monad m => [Enumerator a m b] -> Enumerator a m bSource

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

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

“Wraps” an iteratee inner in an enumeratee wrapper. The resulting iteratee will consume wrapper’s input type and yield inner’s output type.

See the documentation for (=$).

joinI (enum $$ iter) = enum =$ iter

joinE :: Monad m => Enumerator ao m (Step ai m b) -> Enumeratee ao ai m b -> Enumerator ai m bSource

“Wraps” an enumerator inner in an enumeratee wrapper. The resulting enumerator will generate wrapper’s output type.

See the documentation for ($=).

joinE enum enee = enum $= enee

Since: 0.4.5

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

Feeds outer input elements into the provided iteratee until it yields an inner input, passes that to the inner iteratee, and then loops.

isEOF :: Monad m => Iteratee a m BoolSource

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.

tryIO :: MonadIO m => IO b -> Iteratee a m bSource

Try to run an IO computation. If it throws an exception, the exception is caught and passed to throwError.

Since: 0.4.9

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

Lift an Iteratee onto a monad transformer, re-wrapping its inner monadic values.

Since: 0.1.1

Testing and debugging

printChunksSource

Arguments

:: (MonadIO m, Show a) 
=> Bool

Print empty chunks

-> Iteratee a m () 

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

enumList :: Monad m => Integer -> [a] -> Enumerator a m bSource

enumList n xs enumerates xs as a stream, passing n inputs per chunk. This is primarily useful for testing, debugging, and REPL exploration.

Compatibility note: In version 0.5, enumList will be changed to the type:

 enumList :: Monad m => [a] -> Enumerator a m b

enumLists :: Monad m => [[a]] -> Enumerator a m bSource

enumLists xs enumerates xs as a stream, where each element is a separate chunk. This is primarily useful for testing and debugging.

Since: 0.4.15

runLists :: [[a]] -> Iteratee a Identity b -> Either SomeException bSource

Run an iteratee with the given input, and return either the final value (if it succeeded) or the error (if it failed).

Since: 0.4.15

runLists_ :: [[a]] -> Iteratee a Identity b -> bSource

Like runLists, except errors are converted to exceptions and thrown.

Since: 0.4.15

Internal interfaces

This module export will be removed in version 0.5. If you depend on internal implementation details, please import Data.Enumerator.Internal directly.

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

Peek at the next element in the stream, or Nothing if the stream has ended.

last :: Monad m => Iteratee a m (Maybe a)Source

Get the last element in the stream, or Nothing if the stream has ended.

Consumes the entire stream.

length :: Monad m => Iteratee a m IntegerSource

Get how many elements remained in the stream.

Consumes the entire stream.

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

Deprecated in 0.4.5: use Data.Enumerator.continue instead

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

Deprecated in 0.4.5: use Data.Enumerator.List.head instead

drop :: Monad m => Integer -> Iteratee a m ()Source

Deprecated in 0.4.5: use Data.Enumerator.List.drop instead

dropWhile :: Monad m => (a -> Bool) -> Iteratee a m ()Source

Deprecated in 0.4.5: use Data.Enumerator.List.dropWhile instead

span :: Monad m => (a -> Bool) -> Iteratee a m [a]Source

Deprecated in 0.4.5: use Data.Enumerator.List.takeWhile instead

break :: Monad m => (a -> Bool) -> Iteratee a m [a]Source

Deprecated in 0.4.5: use Data.Enumerator.List.takeWhile instead

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

Deprecated in 0.4.5: use Data.Enumerator.List.consume instead

foldl :: Monad m => (b -> a -> b) -> b -> Iteratee a m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.fold instead

Since: 0.4.5

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

Deprecated in 0.4.8: use Data.Enumerator.List.fold instead

Since: 0.4.5

foldM :: Monad m => (b -> a -> m b) -> b -> Iteratee a m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.foldM instead

Since: 0.4.5

iterate :: Monad m => (a -> a) -> a -> Enumerator a m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.iterate instead

Since: 0.4.5

iterateM :: Monad m => (a -> m a) -> a -> Enumerator a m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.iterateM instead

Since: 0.4.5

repeat :: Monad m => a -> Enumerator a m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.repeat instead

Since: 0.4.5

repeatM :: Monad m => m a -> Enumerator a m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.repeatM instead

Since: 0.4.5

replicate :: Monad m => Integer -> a -> Enumerator a m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.replicate instead

Since: 0.4.5

replicateM :: Monad m => Integer -> m a -> Enumerator a m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.replicateM instead

Since: 0.4.5

generateM :: Monad m => m (Maybe a) -> Enumerator a m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.generateM instead

Since: 0.4.5

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

Deprecated in 0.4.8: use Data.Enumerator.List.map instead

mapM :: Monad m => (ao -> m ai) -> Enumeratee ao ai m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.mapM instead

Since: 0.4.3

concatMap :: Monad m => (ao -> [ai]) -> Enumeratee ao ai m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.concatMap instead

Since: 0.4.3

concatMapM :: Monad m => (ao -> m [ai]) -> Enumeratee ao ai m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.concatMapM instead

Since: 0.4.5

filter :: Monad m => (a -> Bool) -> Enumeratee a a m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.filter instead

Since: 0.4.5

filterM :: Monad m => (a -> m Bool) -> Enumeratee a a m bSource

Deprecated in 0.4.8: use Data.Enumerator.List.filterM instead

Since: 0.4.5

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

Deprecated in 0.4.5: use Data.Enumerator.List.fold instead

Since: 0.1.1

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

Deprecated in 0.4.5: use Data.Enumerator.List.fold instead

Since: 0.1.1

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

Deprecated in 0.4.5: use Data.Enumerator.List.foldM instead

Since: 0.1.1