Portability | portable |
---|---|
Maintainer | jmillikin@gmail.com |
Safe Haskell | None |
Byte-oriented alternatives to Data.Enumerator.List. Note that the enumeratees in this module must unpack their inputs to work properly. If you do not need to handle leftover input on a byte-by-byte basis, the chunk-oriented versions will be much faster.
This module is intended to be imported qualified:
import qualified Data.Enumerator.Binary as EB
Since: 0.4.5
- enumHandle :: MonadIO m => Integer -> Handle -> Enumerator ByteString m b
- enumHandleRange :: MonadIO m => Integer -> Maybe Integer -> Maybe Integer -> Handle -> Enumerator ByteString m b
- enumFile :: FilePath -> Enumerator ByteString IO b
- enumFileRange :: FilePath -> Maybe Integer -> Maybe Integer -> Enumerator ByteString IO b
- iterHandle :: MonadIO m => Handle -> Iteratee ByteString m ()
- fold :: Monad m => (b -> Word8 -> b) -> b -> Iteratee ByteString m b
- foldM :: Monad m => (b -> Word8 -> m b) -> b -> Iteratee ByteString m b
- map :: Monad m => (Word8 -> Word8) -> Enumeratee ByteString ByteString m b
- mapM :: Monad m => (Word8 -> m Word8) -> Enumeratee ByteString ByteString m b
- mapM_ :: Monad m => (Word8 -> m ()) -> Iteratee ByteString m ()
- concatMap :: Monad m => (Word8 -> ByteString) -> Enumeratee ByteString ByteString m b
- concatMapM :: Monad m => (Word8 -> m ByteString) -> Enumeratee ByteString ByteString m b
- mapAccum :: Monad m => (s -> Word8 -> (s, Word8)) -> s -> Enumeratee ByteString ByteString m b
- mapAccumM :: Monad m => (s -> Word8 -> m (s, Word8)) -> s -> Enumeratee ByteString ByteString m b
- concatMapAccum :: Monad m => (s -> Word8 -> (s, ByteString)) -> s -> Enumeratee ByteString ByteString m b
- concatMapAccumM :: Monad m => (s -> Word8 -> m (s, ByteString)) -> s -> Enumeratee ByteString ByteString m b
- iterate :: Monad m => (Word8 -> Word8) -> Word8 -> Enumerator ByteString m b
- iterateM :: Monad m => (Word8 -> m Word8) -> Word8 -> Enumerator ByteString m b
- repeat :: Monad m => Word8 -> Enumerator ByteString m b
- repeatM :: Monad m => m Word8 -> Enumerator ByteString m b
- replicate :: Monad m => Integer -> Word8 -> Enumerator ByteString m b
- replicateM :: Monad m => Integer -> m Word8 -> Enumerator ByteString m b
- generateM :: Monad m => m (Maybe Word8) -> Enumerator ByteString m b
- unfold :: Monad m => (s -> Maybe (Word8, s)) -> s -> Enumerator ByteString m b
- unfoldM :: Monad m => (s -> m (Maybe (Word8, s))) -> s -> Enumerator ByteString m b
- drop :: Monad m => Integer -> Iteratee ByteString m ()
- dropWhile :: Monad m => (Word8 -> Bool) -> Iteratee ByteString m ()
- filter :: Monad m => (Word8 -> Bool) -> Enumeratee ByteString ByteString m b
- filterM :: Monad m => (Word8 -> m Bool) -> Enumeratee ByteString ByteString m b
- head :: Monad m => Iteratee ByteString m (Maybe Word8)
- head_ :: Monad m => Iteratee ByteString m Word8
- take :: Monad m => Integer -> Iteratee ByteString m ByteString
- takeWhile :: Monad m => (Word8 -> Bool) -> Iteratee ByteString m ByteString
- consume :: Monad m => Iteratee ByteString m ByteString
- zip :: Monad m => Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m (b1, b2)
- zip3 :: Monad m => Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m (b1, b2, b3)
- zip4 :: Monad m => Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m (b1, b2, b3, b4)
- zip5 :: Monad m => Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m b5 -> Iteratee ByteString m (b1, b2, b3, b4, b5)
- zip6 :: Monad m => Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m b5 -> Iteratee ByteString m b6 -> Iteratee ByteString m (b1, b2, b3, b4, b5, b6)
- zip7 :: Monad m => Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m b5 -> Iteratee ByteString m b6 -> Iteratee ByteString m b7 -> Iteratee ByteString m (b1, b2, b3, b4, b5, b6, b7)
- zipWith :: Monad m => (b1 -> b2 -> c) -> Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m c
- zipWith3 :: Monad m => (b1 -> b2 -> b3 -> c) -> Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m c
- zipWith4 :: Monad m => (b1 -> b2 -> b3 -> b4 -> c) -> Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m c
- zipWith5 :: Monad m => (b1 -> b2 -> b3 -> b4 -> b5 -> c) -> Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m b5 -> Iteratee ByteString m c
- zipWith6 :: Monad m => (b1 -> b2 -> b3 -> b4 -> b5 -> b6 -> c) -> Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m b5 -> Iteratee ByteString m b6 -> Iteratee ByteString m c
- zipWith7 :: Monad m => (b1 -> b2 -> b3 -> b4 -> b5 -> b6 -> b7 -> c) -> Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m b5 -> Iteratee ByteString m b6 -> Iteratee ByteString m b7 -> Iteratee ByteString m c
- require :: Monad m => Integer -> Iteratee ByteString m ()
- isolate :: Monad m => Integer -> Enumeratee ByteString ByteString m b
- isolateWhile :: Monad m => (Word8 -> Bool) -> Enumeratee ByteString ByteString m b
- splitWhen :: Monad m => (Word8 -> Bool) -> Enumeratee ByteString ByteString m b
IO
:: MonadIO m | |
=> Integer | Buffer size |
-> Handle | |
-> Enumerator ByteString m b |
Read bytes (in chunks of the given buffer size) from the handle, and
stream them to an Iteratee
. If an exception occurs during file IO,
enumeration will stop and Error
will be returned. Exceptions from the
iteratee are not caught.
This enumerator blocks until at least one byte is available from the handle, and might read less than the maximum buffer size in some cases.
The handle should be opened with no encoding, and in ReadMode
or
ReadWriteMode
.
Since: 0.4.5
:: MonadIO m | |
=> Integer | Buffer size |
-> Maybe Integer | Offset |
-> Maybe Integer | Maximum count |
-> Handle | |
-> Enumerator ByteString m b |
Read bytes (in chunks of the given buffer size) from the handle, and
stream them to an Iteratee
. If an exception occurs during file IO,
enumeration will stop and Error
will be returned. Exceptions from the
iteratee are not caught.
This enumerator blocks until at least one byte is available from the handle, and might read less than the maximum buffer size in some cases.
The handle should be opened with no encoding, and in ReadMode
or
ReadWriteMode
.
If an offset is specified, the handle will be seeked to that offset before reading. If the handle cannot be seeked, an error will be thrown.
If a maximum count is specified, the number of bytes read will not exceed that count.
Since: 0.4.8
enumFile :: FilePath -> Enumerator ByteString IO bSource
Opens a file path in binary mode, and passes the handle to
enumHandle
. The file will be closed when enumeration finishes.
Since: 0.4.5
:: FilePath | |
-> Maybe Integer | Offset |
-> Maybe Integer | Maximum count |
-> Enumerator ByteString IO b |
Opens a file path in binary mode, and passes the handle to
enumHandleRange
. The file will be closed when enumeration finishes.
Since: 0.4.8
iterHandle :: MonadIO m => Handle -> Iteratee ByteString m ()Source
Read bytes from a stream and write them to a handle. If an exception
occurs during file IO, enumeration will stop and Error
will be
returned.
The handle should be opened with no encoding, and in WriteMode
or
ReadWriteMode
.
Since: 0.4.5
List analogues
Folds
fold :: Monad m => (b -> Word8 -> b) -> b -> Iteratee ByteString m bSource
Consume the entire input stream with a strict left fold, one byte at a time.
Since: 0.4.8
foldM :: Monad m => (b -> Word8 -> m b) -> b -> Iteratee ByteString m bSource
Consume the entire input stream with a strict monadic left fold, one byte at a time.
Since: 0.4.8
Maps
map :: Monad m => (Word8 -> Word8) -> Enumeratee ByteString ByteString m bSource
applies f to each input byte and
feeds the resulting outputs to the inner iteratee.
map
f
Since: 0.4.8
mapM :: Monad m => (Word8 -> m Word8) -> Enumeratee ByteString ByteString m bSource
applies f to each input byte and
feeds the resulting outputs to the inner iteratee.
mapM
f
Since: 0.4.8
mapM_ :: Monad m => (Word8 -> m ()) -> Iteratee ByteString m ()Source
applies f to each input byte, and
discards the results.
mapM_
f
Since: 0.4.11
concatMap :: Monad m => (Word8 -> ByteString) -> Enumeratee ByteString ByteString m bSource
applies f to each input byte
and feeds the resulting outputs to the inner iteratee.
concatMap
f
Since: 0.4.8
concatMapM :: Monad m => (Word8 -> m ByteString) -> Enumeratee ByteString ByteString m bSource
applies f to each input byte and feeds the
resulting outputs to the inner iteratee.
concatMapM
f
Since: 0.4.8
Accumulating maps
mapAccum :: Monad m => (s -> Word8 -> (s, Word8)) -> s -> Enumeratee ByteString ByteString m bSource
Similar to map
, but with a stateful step
function.
Since: 0.4.9
mapAccumM :: Monad m => (s -> Word8 -> m (s, Word8)) -> s -> Enumeratee ByteString ByteString m bSource
Similar to mapM
, but with a stateful step
function.
Since: 0.4.9
concatMapAccum :: Monad m => (s -> Word8 -> (s, ByteString)) -> s -> Enumeratee ByteString ByteString m bSource
Similar to concatMap
, but with a stateful step
function.
Since: 0.4.11
concatMapAccumM :: Monad m => (s -> Word8 -> m (s, ByteString)) -> s -> Enumeratee ByteString ByteString m bSource
Similar to concatMapM
, but with a stateful step function.
Since: 0.4.11
Infinite streams
iterate :: Monad m => (Word8 -> Word8) -> Word8 -> Enumerator ByteString m bSource
iterateM :: Monad m => (Word8 -> m Word8) -> Word8 -> Enumerator ByteString m bSource
Similar to iterate
, except the iteration
function is monadic.
Since: 0.4.8
repeat :: Monad m => Word8 -> Enumerator ByteString m bSource
repeatM :: Monad m => m Word8 -> Enumerator ByteString m bSource
Enumerates an infinite stream of byte. Each byte is computed by the underlying monad.
Since: 0.4.8
Bounded streams
replicate :: Monad m => Integer -> Word8 -> Enumerator ByteString m bSource
enumerates a stream containing
n copies of x.
replicate
n x
Since: 0.4.8
replicateM :: Monad m => Integer -> m Word8 -> Enumerator ByteString m bSource
enumerates a stream of n bytes, with each byte
computed by m_x.
replicateM
n m_x
Since: 0.4.8
generateM :: Monad m => m (Maybe Word8) -> Enumerator ByteString m bSource
unfold :: Monad m => (s -> Maybe (Word8, s)) -> s -> Enumerator ByteString m bSource
Enumerates a stream of bytes by repeatedly applying a function to some state.
Similar to iterate
.
Since: 0.4.8
unfoldM :: Monad m => (s -> m (Maybe (Word8, s))) -> s -> Enumerator ByteString m bSource
Enumerates a stream of bytes by repeatedly applying a computation to some state.
Similar to iterateM
.
Since: 0.4.8
Dropping input
drop :: Monad m => Integer -> Iteratee ByteString m ()Source
ignores n bytes of input from the stream.
drop
n
Since: 0.4.5
dropWhile :: Monad m => (Word8 -> Bool) -> Iteratee ByteString m ()Source
ignores input from the stream
until the first byte which does not match the predicate.
dropWhile
p
Since: 0.4.5
filter :: Monad m => (Word8 -> Bool) -> Enumeratee ByteString ByteString m bSource
Applies a predicate to the stream. The inner iteratee only receives
characters for which the predicate is True
.
Since: 0.4.8
filterM :: Monad m => (Word8 -> m Bool) -> Enumeratee ByteString ByteString m bSource
Applies a monadic predicate to the stream. The inner iteratee only
receives bytes for which the predicate returns True
.
Since: 0.4.8
Consumers
head :: Monad m => Iteratee ByteString m (Maybe Word8)Source
Get the next byte from the stream, or Nothing
if the stream has
ended.
Since: 0.4.5
head_ :: Monad m => Iteratee ByteString m Word8Source
Get the next element from the stream, or raise an error if the stream has ended.
Since: 0.4.14
take :: Monad m => Integer -> Iteratee ByteString m ByteStringSource
extracts the next n bytes from the
stream, as a lazy
ByteString.
take
n
Since: 0.4.5
takeWhile :: Monad m => (Word8 -> Bool) -> Iteratee ByteString m ByteStringSource
extracts input from the stream until the first byte which
does not match the predicate.
takeWhile
p
Since: 0.4.5
consume :: Monad m => Iteratee ByteString m ByteStringSource
Zipping
zip :: Monad m => Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m (b1, b2)Source
Pass input from a stream through two iteratees at once. Excess input is yielded if it was not consumed by either iteratee.
Analogous to zip
.
Since: 0.4.14
zip3 :: Monad m => Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m (b1, b2, b3)Source
Pass input from a stream through three iteratees at once. Excess input is yielded if it was not consumed by any iteratee.
Analogous to zip3
.
Since: 0.4.14
zip4 :: Monad m => Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m (b1, b2, b3, b4)Source
Pass input from a stream through four iteratees at once. Excess input is yielded if it was not consumed by any iteratee.
Analogous to zip4
.
Since: 0.4.14
zip5 :: Monad m => Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m b5 -> Iteratee ByteString m (b1, b2, b3, b4, b5)Source
Pass input from a stream through five iteratees at once. Excess input is yielded if it was not consumed by any iteratee.
Analogous to zip5
.
Since: 0.4.14
zip6 :: Monad m => Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m b5 -> Iteratee ByteString m b6 -> Iteratee ByteString m (b1, b2, b3, b4, b5, b6)Source
Pass input from a stream through six iteratees at once. Excess input is yielded if it was not consumed by any iteratee.
Analogous to zip6
.
Since: 0.4.14
zip7 :: Monad m => Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m b5 -> Iteratee ByteString m b6 -> Iteratee ByteString m b7 -> Iteratee ByteString m (b1, b2, b3, b4, b5, b6, b7)Source
Pass input from a stream through seven iteratees at once. Excess input is yielded if it was not consumed by any iteratee.
Analogous to zip7
.
Since: 0.4.14
zipWith :: Monad m => (b1 -> b2 -> c) -> Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m cSource
Pass input from a stream through two iteratees at once. Excess input is yielded if it was not consumed by either iteratee. Output from the iteratees is combined with a user-provided function.
Analogous to zipWith
.
Since: 0.4.14
zipWith3 :: Monad m => (b1 -> b2 -> b3 -> c) -> Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m cSource
Pass input from a stream through two iteratees at once. Excess input is yielded if it was not consumed by either iteratee. Output from the iteratees is combined with a user-provided function.
Analogous to zipWith3
.
Since: 0.4.14
zipWith4 :: Monad m => (b1 -> b2 -> b3 -> b4 -> c) -> Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m cSource
Pass input from a stream through two iteratees at once. Excess input is yielded if it was not consumed by either iteratee. Output from the iteratees is combined with a user-provided function.
Analogous to zipWith4
.
Since: 0.4.14
zipWith5 :: Monad m => (b1 -> b2 -> b3 -> b4 -> b5 -> c) -> Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m b5 -> Iteratee ByteString m cSource
Pass input from a stream through two iteratees at once. Excess input is yielded if it was not consumed by either iteratee. Output from the iteratees is combined with a user-provided function.
Analogous to zipWith5
.
Since: 0.4.14
zipWith6 :: Monad m => (b1 -> b2 -> b3 -> b4 -> b5 -> b6 -> c) -> Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m b5 -> Iteratee ByteString m b6 -> Iteratee ByteString m cSource
Pass input from a stream through two iteratees at once. Excess input is yielded if it was not consumed by either iteratee. Output from the iteratees is combined with a user-provided function.
Analogous to zipWith6
.
Since: 0.4.14
zipWith7 :: Monad m => (b1 -> b2 -> b3 -> b4 -> b5 -> b6 -> b7 -> c) -> Iteratee ByteString m b1 -> Iteratee ByteString m b2 -> Iteratee ByteString m b3 -> Iteratee ByteString m b4 -> Iteratee ByteString m b5 -> Iteratee ByteString m b6 -> Iteratee ByteString m b7 -> Iteratee ByteString m cSource
Pass input from a stream through two iteratees at once. Excess input is yielded if it was not consumed by either iteratee. Output from the iteratees is combined with a user-provided function.
Analogous to zipWith7
.
Since: 0.4.14
Unsorted
require :: Monad m => Integer -> Iteratee ByteString m ()Source
buffers input until at least n bytes are available, or
throws an error if the stream ends early.
require
n
Since: 0.4.5
isolate :: Monad m => Integer -> Enumeratee ByteString ByteString m bSource
reads at most n bytes from the stream, and passes them
to its iteratee. If the iteratee finishes early, bytes continue to be
consumed from the outer stream until n have been consumed.
isolate
n
Since: 0.4.5
isolateWhile :: Monad m => (Word8 -> Bool) -> Enumeratee ByteString ByteString m bSource
reads bytes from the stream until p is false, and
passes them to its iteratee. If the iteratee finishes early, bytes
continue to be consumed from the outer stream until p is false.
isolateWhile
p
Since: 0.4.16
splitWhen :: Monad m => (Word8 -> Bool) -> Enumeratee ByteString ByteString m bSource
Split on bytes satisfying a given predicate.
Since: 0.4.8