Safe Haskell | None |
---|---|
Language | Haskell2010 |
Monadic and General Iteratees: incremental input parsers, processors and transformers
- type EnumerateeHandler eli elo m a = (Stream eli -> Iteratee eli m a) -> SomeException -> Iteratee elo m (Iteratee eli m a)
- throwErr :: SomeException -> Iteratee s m a
- throwRecoverableErr :: SomeException -> (Stream s -> Iteratee s m a) -> Iteratee s m a
- checkErr :: NullPoint s => Iteratee s m a -> Iteratee s m (Either SomeException a)
- unitIter :: NullPoint s => Iteratee s m ()
- skipToEof :: Iteratee s m ()
- isStreamFinished :: Nullable s => Iteratee s m (Maybe SomeException)
- mBind :: Monad m => m a -> (a -> Iteratee s m b) -> Iteratee s m b
- mBind_ :: Monad m => m a -> Iteratee s m b -> Iteratee s m b
- ioBind :: MonadIO m => IO a -> (a -> Iteratee s m b) -> Iteratee s m b
- ioBind_ :: MonadIO m => IO a -> Iteratee s m b -> Iteratee s m b
- mapChunksM_ :: (Monad m, Nullable s) => (s -> m b) -> Iteratee s m ()
- foldChunksM :: (Monad m, Nullable s) => (a -> s -> m a) -> a -> Iteratee s m a
- getChunk :: Nullable s => Iteratee s m s
- getChunks :: Nullable s => Iteratee s m [s]
- mapChunks :: NullPoint s => (s -> s') -> Enumeratee s s' m a
- mapChunksM :: (Monad m, NullPoint s) => (s -> m s') -> Enumeratee s s' m a
- convStream :: (Monad m, Nullable s) => Iteratee s m s' -> Enumeratee s s' m a
- unfoldConvStream :: (Monad m, Nullable s) => (acc -> Iteratee s m (acc, s')) -> acc -> Enumeratee s s' m a
- unfoldConvStreamCheck :: (Monad m, Nullable elo) => (((Stream eli -> Iteratee eli m a) -> Maybe SomeException -> Iteratee elo m (Iteratee eli m a)) -> Enumeratee elo eli m a) -> (acc -> Iteratee elo m (acc, eli)) -> acc -> Enumeratee elo eli m a
- joinI :: (Monad m, Nullable s) => Iteratee s m (Iteratee s' m a) -> Iteratee s m a
- joinIM :: Monad m => m (Iteratee s m a) -> Iteratee s m a
- type Enumerator s m a = Iteratee s m a -> m (Iteratee s m a)
- type Enumeratee sFrom sTo m a = Iteratee sTo m a -> Iteratee sFrom m (Iteratee sTo m a)
- enumChunk :: Monad m => Stream s -> Enumerator s m a
- enumEof :: Monad m => Enumerator s m a
- enumErr :: (Exception e, Monad m) => e -> Enumerator s m a
- enumPure1Chunk :: Monad m => s -> Enumerator s m a
- enumList :: Monad m => [s] -> Enumerator s m a
- enumCheckIfDone :: Monad m => Iteratee s m a -> m (Bool, Iteratee s m a)
- enumFromCallback :: (Monad m, NullPoint s) => (st -> m (Either SomeException ((Bool, st), s))) -> st -> Enumerator s m a
- enumFromCallbackCatch :: (IException e, Monad m, NullPoint s) => (st -> m (Either SomeException ((Bool, st), s))) -> (e -> m (Maybe EnumException)) -> st -> Enumerator s m a
- eneeCheckIfDone :: (Monad m, NullPoint elo) => ((Stream eli -> Iteratee eli m a) -> Iteratee elo m (Iteratee eli m a)) -> Enumeratee elo eli m a
- eneeCheckIfDoneHandle :: NullPoint elo => EnumerateeHandler eli elo m a -> ((Stream eli -> Iteratee eli m a) -> Maybe SomeException -> Iteratee elo m (Iteratee eli m a)) -> Enumeratee elo eli m a
- eneeCheckIfDoneIgnore :: NullPoint elo => ((Stream eli -> Iteratee eli m a) -> Maybe SomeException -> Iteratee elo m (Iteratee eli m a)) -> Enumeratee elo eli m a
- eneeCheckIfDonePass :: NullPoint elo => ((Stream eli -> Iteratee eli m a) -> Maybe SomeException -> Iteratee elo m (Iteratee eli m a)) -> Enumeratee elo eli m a
- mergeEnums :: (Nullable s2, Nullable s1, Monad m) => Enumerator s1 m a -> Enumerator s2 (Iteratee s1 m) a -> Enumeratee s2 s1 (Iteratee s1 m) a -> Enumerator s1 m a
- ($=) :: Monad m => (forall a. Enumerator s m a) -> Enumeratee s s' m b -> Enumerator s' m b
- (=$) :: (Nullable s, Monad m) => Enumeratee s s' m a -> Iteratee s' m a -> Iteratee s m a
- (><>) :: (Nullable s1, Monad m) => (forall x. Enumeratee s1 s2 m x) -> Enumeratee s2 s3 m a -> Enumeratee s1 s3 m a
- (<><) :: (Nullable s1, Monad m) => Enumeratee s2 s3 m a -> (forall x. Enumeratee s1 s2 m x) -> Enumeratee s1 s3 m a
- seek :: NullPoint s => FileOffset -> Iteratee s m ()
- type FileOffset = COff
- module Bio.Iteratee.Base
Types
type EnumerateeHandler eli elo m a = (Stream eli -> Iteratee eli m a) -> SomeException -> Iteratee elo m (Iteratee eli m a) Source #
Error handling
throwErr :: SomeException -> Iteratee s m a Source #
Report and propagate an unrecoverable error.
Disregard the input first and then propagate the error. This error
cannot be handled by enumFromCallbackCatch
, although it can be cleared
by checkErr
.
throwRecoverableErr :: SomeException -> (Stream s -> Iteratee s m a) -> Iteratee s m a Source #
Report and propagate a recoverable error. This error can be handled by
both enumFromCallbackCatch
and checkErr
.
checkErr :: NullPoint s => Iteratee s m a -> Iteratee s m (Either SomeException a) Source #
Check if an iteratee produces an error.
Returns Right a
if it completes without errors, otherwise
Left SomeException
. checkErr
is useful for iteratees that may not
terminate, such as Data.Iteratee.head
with an empty stream.
Basic Iteratees
unitIter :: NullPoint s => Iteratee s m () Source #
The identity iteratee. Doesn't do any processing of input.
isStreamFinished :: Nullable s => Iteratee s m (Maybe SomeException) Source #
Get the stream status of an iteratee.
Iteratee composition
mBind :: Monad m => m a -> (a -> Iteratee s m b) -> Iteratee s m b infixl 1 Source #
Lifts a monadic action and combines it with a continuation.
mBind m f
is the same as lift m >>= f
, but does not require a
Nullable
constraint on the stream type.
mBind_ :: Monad m => m a -> Iteratee s m b -> Iteratee s m b infixl 1 Source #
Lifts a monadic action, ignored the result and combines it with a
continuation. mBind_ m f
is the same as lift m >>= f
, but does
not require a Nullable
constraint on the stream type.
ioBind :: MonadIO m => IO a -> (a -> Iteratee s m b) -> Iteratee s m b infixl 1 Source #
Lifts an IO action and combines it with a continuation.
ioBind m f
is the same as liftIO m >>= f
, but does not require a
Nullable
constraint on the stream type.
ioBind_ :: MonadIO m => IO a -> Iteratee s m b -> Iteratee s m b infixl 1 Source #
Lifts an IO action, ignores its result, and combines it with a
continuation. ioBind_ m f
is the same as liftIO m >> f
, but does
not require a Nullable
constraint on the stream type.
Chunkwise Iteratees
mapChunksM_ :: (Monad m, Nullable s) => (s -> m b) -> Iteratee s m () Source #
Map a monadic function over the chunks of the stream and ignore the result. Useful for creating efficient monadic iteratee consumers, e.g.
logger = mapChunksM_ (liftIO . putStrLn)
these can be efficiently run in parallel with other iteratees via
Data.Iteratee.ListLike.zip
.
foldChunksM :: (Monad m, Nullable s) => (a -> s -> m a) -> a -> Iteratee s m a Source #
A fold over chunks
Nested iteratee combinators
mapChunks :: NullPoint s => (s -> s') -> Enumeratee s s' m a Source #
Convert one stream into another with the supplied mapping function.
This function operates on whole chunks at a time, contrasting to
mapStream
which operates on single elements.
unpacker :: Enumeratee B.ByteString [Word8] m a unpacker = mapChunks B.unpack
mapChunksM :: (Monad m, NullPoint s) => (s -> m s') -> Enumeratee s s' m a Source #
Convert a stream of s
to a stream of s'
using the supplied function.
convStream :: (Monad m, Nullable s) => Iteratee s m s' -> Enumeratee s s' m a Source #
Convert one stream into another, not necessarily in lockstep.
The transformer mapStream maps one element of the outer stream to one element of the nested stream. The transformer below is more general: it may take several elements of the outer stream to produce one element of the inner stream, or the other way around. The transformation from one stream to the other is specified as Iteratee s m s'.
unfoldConvStream :: (Monad m, Nullable s) => (acc -> Iteratee s m (acc, s')) -> acc -> Enumeratee s s' m a Source #
The most general stream converter. Given a function to produce iteratee transformers and an initial state, convert the stream using iteratees generated by the function while continually updating the internal state.
unfoldConvStreamCheck :: (Monad m, Nullable elo) => (((Stream eli -> Iteratee eli m a) -> Maybe SomeException -> Iteratee elo m (Iteratee eli m a)) -> Enumeratee elo eli m a) -> (acc -> Iteratee elo m (acc, eli)) -> acc -> Enumeratee elo eli m a Source #
joinI :: (Monad m, Nullable s) => Iteratee s m (Iteratee s' m a) -> Iteratee s m a Source #
Collapse a nested iteratee. The inner iteratee is terminated by EOF
.
Errors are propagated through the result.
The stream resumes from the point of the outer iteratee; any remaining
input in the inner iteratee will be lost.
Differs from join
in that the inner iteratee is terminated,
and may have a different stream type than the result.
joinIM :: Monad m => m (Iteratee s m a) -> Iteratee s m a Source #
Lift an iteratee inside a monad to an iteratee.
Enumerators
type Enumerator s m a = Iteratee s m a -> m (Iteratee s m a) Source #
Each enumerator takes an iteratee and returns an iteratee
an Enumerator is an iteratee transformer. The enumerator normally stops when the stream is terminated or when the iteratee moves to the done state, whichever comes first. When to stop is of course up to the enumerator...
Basic enumerators
enumChunk :: Monad m => Stream s -> Enumerator s m a Source #
Applies the iteratee to the given stream. This wraps enumEof
,
enumErr
, and enumPure1Chunk
, calling the appropriate enumerator
based upon Stream
.
enumEof :: Monad m => Enumerator s m a Source #
The most primitive enumerator: applies the iteratee to the terminated stream. The result is the iteratee in the Done state. It is an error if the iteratee does not terminate on EOF.
enumErr :: (Exception e, Monad m) => e -> Enumerator s m a Source #
Another primitive enumerator: tell the Iteratee the stream terminated with an error.
enumPure1Chunk :: Monad m => s -> Enumerator s m a Source #
The pure 1-chunk enumerator
It passes a given list of elements to the iteratee in one chunk This enumerator does no IO and is useful for testing of base parsing
enumList :: Monad m => [s] -> Enumerator s m a Source #
Enumerate chunks from a list
enumCheckIfDone :: Monad m => Iteratee s m a -> m (Bool, Iteratee s m a) Source #
Checks if an iteratee has finished.
This enumerator runs the iteratee, performing any monadic actions. If the result is True, the returned iteratee is done.
enumFromCallback :: (Monad m, NullPoint s) => (st -> m (Either SomeException ((Bool, st), s))) -> st -> Enumerator s m a Source #
Create an enumerator from a callback function
enumFromCallbackCatch :: (IException e, Monad m, NullPoint s) => (st -> m (Either SomeException ((Bool, st), s))) -> (e -> m (Maybe EnumException)) -> st -> Enumerator s m a Source #
Create an enumerator from a callback function with an exception handler. The exception handler is called if an iteratee reports an exception.
Enumerator Combinators
eneeCheckIfDone :: (Monad m, NullPoint elo) => ((Stream eli -> Iteratee eli m a) -> Iteratee elo m (Iteratee eli m a)) -> Enumeratee elo eli m a Source #
Utility function for creating enumeratees. Typical usage is demonstrated
by the breakE
definition.
breakE :: (Monad m, LL.ListLike s el, NullPoint s) => (el -> Bool) -> Enumeratee s s m a breakE cpred = eneeCheckIfDone (liftI . step) where step k (Chunk s) | LL.null s = liftI (step k) | otherwise = case LL.break cpred s of (str', tail') | LL.null tail' -> eneeCheckIfDone (liftI . step) . k $ Chunk str' | otherwise -> idone (k $ Chunk str') (Chunk tail') step k stream = idone (k stream) stream
eneeCheckIfDoneHandle :: NullPoint elo => EnumerateeHandler eli elo m a -> ((Stream eli -> Iteratee eli m a) -> Maybe SomeException -> Iteratee elo m (Iteratee eli m a)) -> Enumeratee elo eli m a Source #
The same as eneeCheckIfDonePass, with one extra argument: a handler which is used to process any exceptions in a separate method.
eneeCheckIfDoneIgnore :: NullPoint elo => ((Stream eli -> Iteratee eli m a) -> Maybe SomeException -> Iteratee elo m (Iteratee eli m a)) -> Enumeratee elo eli m a Source #
eneeCheckIfDonePass :: NullPoint elo => ((Stream eli -> Iteratee eli m a) -> Maybe SomeException -> Iteratee elo m (Iteratee eli m a)) -> Enumeratee elo eli m a Source #
:: (Nullable s2, Nullable s1, Monad m) | |
=> Enumerator s1 m a | inner enumerator |
-> Enumerator s2 (Iteratee s1 m) a | outer enumerator |
-> Enumeratee s2 s1 (Iteratee s1 m) a | merging enumeratee |
-> Enumerator s1 m a |
Combine enumeration over two streams. The merging enumeratee would
typically be the result of merge
or
mergeByChunks
(see merge
for example).
Enumeratee Combinators
($=) :: Monad m => (forall a. Enumerator s m a) -> Enumeratee s s' m b -> Enumerator s' m b infixl 1 Source #
Combines Enumerator which produces stream of s
and Enumeratee
which transforms stream of s
to stream
of s'
to into Enumerator which produces stream of s'
(=$) :: (Nullable s, Monad m) => Enumeratee s s' m a -> Iteratee s' m a -> Iteratee s m a infixr 0 Source #
Combines an Enumeratee from s
to s'
and an Iteratee that
consumes s'
into an Iteratee which consumes s
(><>) :: (Nullable s1, Monad m) => (forall x. Enumeratee s1 s2 m x) -> Enumeratee s2 s3 m a -> Enumeratee s1 s3 m a Source #
Enumeratee composition Run the second enumeratee within the first. In this example, stream2list is run within the 'takeStream 10', which is itself run within 'takeStream 15', resulting in 15 elements being consumed
>>>
run =<< enumPure1Chunk [1..1000 :: Int] (joinI $ (I.takeStream 15 ><> I.takeStream 10) I.stream2list)
[1,2,3,4,5,6,7,8,9,10]
(<><) :: (Nullable s1, Monad m) => Enumeratee s2 s3 m a -> (forall x. Enumeratee s1 s2 m x) -> Enumeratee s1 s3 m a Source #
enumeratee composition with the arguments flipped, see ><>
Misc.
type FileOffset = COff #
Classes
module Bio.Iteratee.Base