Data.IterIO.Inum
Contents
- type Inum tIn tOut m a = Iter tOut m a -> Iter tIn m (IterR tOut m a)
- type Onum t m a = Inum () t m a
- (|$) :: (ChunkData t, Monad m) => Onum t m a -> Iter t m a -> m a
- (.|$) :: (ChunkData tIn, ChunkData tOut, Monad m) => Onum tOut m a -> Iter tOut m a -> Iter tIn m a
- cat :: (ChunkData tIn, ChunkData tOut, Monad m) => Inum tIn tOut m a -> Inum tIn tOut m a -> Inum tIn tOut m a
- lcat :: (ChunkData tIn, ChunkData tOut, Monad m) => Inum tIn tOut m a -> Inum tIn tOut m a -> Inum tIn tOut m a
- (|.) :: (ChunkData tIn, ChunkData tOut, Monad m) => Inum tIn tOut m iR -> (i -> Iter tOut m iR) -> i -> Iter tIn m iR
- (.|) :: (ChunkData tIn, ChunkData tOut, Monad m) => Inum tIn tOut m a -> Iter tOut m a -> Iter tIn m a
- inumCatch :: (Exception e, ChunkData tIn, Monad m) => Inum tIn tOut m a -> (e -> IterR tIn m (IterR tOut m a) -> Iter tIn m (IterR tOut m a)) -> Inum tIn tOut m a
- inumFinally :: (ChunkData tIn, Monad m) => Inum tIn tOut m a -> Iter tIn m b -> Inum tIn tOut m a
- inumOnException :: (ChunkData tIn, Monad m) => Inum tIn tOut m a -> Iter tIn m b -> Inum tIn tOut m a
- resumeI :: (ChunkData tIn, Monad m) => IterR tIn m (IterR tOut m a) -> Iter tIn m (IterR tOut m a)
- verboseResumeI :: (ChunkData tIn, MonadIO m) => IterR tIn m (IterR tOut m a) -> Iter tIn m (IterR tOut m a)
- type ResidHandler tIn tOut = (tIn, tOut) -> (tIn, tOut)
- type CtlHandler m1 t m a = CtlArg t m a -> m1 (IterR t m a)
- mkInumC :: (ChunkData tIn, ChunkData tOut, Monad m) => ResidHandler tIn tOut -> CtlHandler (Iter tIn m) tOut m a -> Iter tIn m tOut -> Inum tIn tOut m a
- mkInum :: (ChunkData tIn, ChunkData tOut, Monad m) => Iter tIn m tOut -> Inum tIn tOut m a
- mkInumP :: (ChunkData tIn, ChunkData tOut, Monad m) => ResidHandler tIn tOut -> Iter tIn m tOut -> Inum tIn tOut m a
- inumBracket :: (ChunkData tIn, Monad m) => Iter tIn m b -> (b -> Iter tIn m c) -> (b -> Inum tIn tOut m a) -> Inum tIn tOut m a
- pullupResid :: ChunkData t => (t, t) -> (t, t)
- noCtl :: Monad m1 => CtlHandler m1 t m a
- passCtl :: Monad mIn => ResidHandler tIn tOut -> CtlHandler (Iter tIn mIn) tOut m a
- consCtl :: (CtlCmd carg cres, ChunkData tIn, Monad mIn) => (carg -> (cres -> Iter t m a) -> Chunk t -> Iter tIn mIn (IterR t m a)) -> CtlHandler (Iter tIn mIn) t m a -> CtlHandler (Iter tIn mIn) t m a
- mkCtl :: (CtlCmd carg cres, Monad m1) => (carg -> Iter t1 m1 cres) -> carg -> (cres -> Iter t m a) -> Chunk t -> Iter t1 m1 (IterR t m a)
- mkFlushCtl :: (CtlCmd carg cres, Monad mIn, ChunkData tIn, ChunkData t) => (carg -> Iter tIn mIn cres) -> carg -> (cres -> Iter t m a) -> Chunk t -> Iter tIn mIn (IterR t m a)
- runIterM :: (Monad m, MonadTrans mt, Monad (mt m)) => Iter t m a -> Chunk t -> mt m (IterR t m a)
- runIterMC :: Monad m => CtlHandler (Iter tIn m) tOut m a -> Iter tOut m a -> Chunk tOut -> Iter tIn m (IterR tOut m a)
- runInum :: (ChunkData tIn, Monad m) => Inum tIn tOut m a -> Inum tIn tOut m a
- inumNop :: (ChunkData t, Monad m) => Inum t t m a
- inumNull :: (ChunkData tOut, Monad m) => Inum tIn tOut m a
- inumPure :: Monad m => tOut -> Inum tIn tOut m a
- enumPure :: Monad m => tOut -> Onum tOut m a
- inumRepeat :: (ChunkData tIn, Monad m) => Inum tIn tOut m a -> Inum tIn tOut m a
- type InumM tIn tOut m a = Iter tIn (IterStateT (InumState tIn tOut m a) m)
- mkInumM :: (ChunkData tIn, ChunkData tOut, Monad m) => InumM tIn tOut m a b -> Inum tIn tOut m a
- mkInumAutoM :: (ChunkData tIn, ChunkData tOut, Monad m) => InumM tIn tOut m a b -> Inum tIn tOut m a
- setCtlHandler :: (ChunkData tIn, Monad m) => CtlHandler (Iter tIn m) tOut m a -> InumM tIn tOut m a ()
- setAutoEOF :: (ChunkData tIn, Monad m) => Bool -> InumM tIn tOut m a ()
- setAutoDone :: (ChunkData tIn, Monad m) => Bool -> InumM tIn tOut m a ()
- addCleanup :: (ChunkData tIn, Monad m) => InumM tIn tOut m a () -> InumM tIn tOut m a ()
- withCleanup :: (ChunkData tIn, Monad m) => InumM tIn tOut m a () -> InumM tIn tOut m a b -> InumM tIn tOut m a b
- ifeed :: (ChunkData tIn, ChunkData tOut, Monad m) => tOut -> InumM tIn tOut m a Bool
- ifeed1 :: (ChunkData tIn, ChunkData tOut, Monad m) => tOut -> InumM tIn tOut m a Bool
- ipipe :: (ChunkData tIn, ChunkData tOut, Monad m) => Inum tIn tOut m a -> InumM tIn tOut m a Bool
- irun :: (ChunkData tAny, ChunkData tIn, ChunkData tOut, Monad m) => Inum tAny tOut m a -> InumM tIn tOut m a Bool
- irepeat :: (ChunkData tIn, Monad m) => InumM tIn tOut m a b -> InumM tIn tOut m a ()
- ipopresid :: (ChunkData tIn, ChunkData tOut, Monad m) => InumM tIn tOut m a tOut
- idone :: (ChunkData tIn, Monad m) => InumM tIn tOut m a b
Base types
type Inum tIn tOut m a = Iter tOut m a -> Iter tIn m (IterR tOut m a)Source
The type of an iterator-enumerator, which transcodes data from
some input type tIn to some output type tOut. An Inum acts
as an Iter when consuming data, then acts as an enumerator when
feeding transcoded data to another Iter.
At a high level, one can think of an Inum as a function from
Iters to IterRs, where an Inum's input and output types are
different. A simpler-seeming alternative to Inum might have
been:
type Inum' tIn tOut m a = Iter tOut m a -> Iter tIn m a
In fact, given an Inum object inum, it is possible to construct
a function of type Inum' with (inum . But sometimes one
might like to concatenate .|)Inums. For instance, consider a
network protocol that changes encryption or compression modes
midstream. Transcoding is done by Inums. To change transcoding
methods after applying an Inum to an iteratee requires the
ability to "pop" the iteratee back out of the Inum so as to be
able to hand it to another Inum. Inum's return type (Iter tIn
m (IterR tOut m a) as opposed to Iter tIn m a) allows the
monadic bind operator >>= to accomplish this popping in
conjunction with the tryRI and reRunIter functions.
All Inums must obey the following two rules.
- An
Inummay never feed a chunk with the EOF flag set to it's targetIter. Instead, upon receiving EOF, theInumshould simply return the state of the innerIter(this is how "popping" the iteratee back out works--If theInumpassed the EOF through to theIter, theIterwould stop requesting more input and could not be handed off to a newInum). - An
Inummust always return the state of its targetIter. This is true even when theInumfails, and is why theFailstate contains afield.Maybea
In addition to returning when it receives an EOF or fails, an
Inum should return when the target Iter returns a result or
fails. An Inum may also unilaterally return the state of the
iteratee at any earlier point, for instance if it has reached some
logical message boundary (e.g., many protocols finish processing
headers upon reading a blank line).
Inums are generally constructed with one of the mkInum or
mkInumM functions, which hide most of the error handling details
and ensure the above rules are obeyed. Most Inums are
polymorphic in the last type, a, in order to work with iteratees
returning any type.
type Onum t m a = Inum () t m aSource
An Onum t m a is just an Inum in which the input is
()--i.e., --so that there is no meaningful input
data to transcode. Such an enumerator is called an
outer enumerator, because it must produce the data it feeds to
Inum () t m aIters by either executing actions in monad m, or from its own
internal pure state (as for enumPure).
As with Inums, an Onum should under no circumstances ever feed
a chunk with the EOF bit set to its Iter argument. When the
Onum runs out of data, it must simply return the current state of
the Iter. This way more data from another source can still be
fed to the iteratee, as happens when enumerators are concatenated
with the cat function.
Onums should generally be constructed using the mkInum or
mkInumM function, just like Inums, the only difference being
that for an Onum the input type is (), so executing Iters to
consume input will be of little use.
Concatenation and fusing operators
(.|$) :: (ChunkData tIn, ChunkData tOut, Monad m) => Onum tOut m a -> Iter tOut m a -> Iter tIn m aSource
.|$ is a variant of |$ that allows you to apply an Onum
from within an Iter monad. This is often useful in conjuction
with enumPure, if you want to parse at some coarse-granularity
(such as lines), and then re-parse the contents of some
coarser-grained parse unit. For example:
rawcommand <- lineI
command <- enumPure rawcommand .|$ parseCommandI
return Request { cmd = command, rawcmd = rawcommand }
.|$ has the same fixity as |$, namely:
infixr 2 .|$
Note the important distinction between (.|$) and (.
.|)(.|$) runs an Onum and does not touch the current input, while
(.|) pipes the current input through an Inum. For instance, to
send the contents of a file to standard output (regardless of the
current input), you must say . But to take the current input, compress it, and send
the result to standard output, you must use enumFile ".signature" .|$
stdoutI.|, as in .
inumGzip
.| stdoutI
As suggested by the types, enum .|$ iter is sort of equivalent to
, except that the latter will call lift (enum |$ iter)throw
on failures, causing language-level exceptions that cannot be
caught within the outer Iter. Thus, it is better to use .|$
than , though in the less general case of
the IO monad, lift (... |$ ...)enum .|$ iter is equivalent to as illustrated by the following examples:
liftIO (enum |$
iter)
-- Catches exception, because .|$ propagates failure through the outer
-- Iter Monad, where it can still be caught.
apply1 :: IO String
apply1 = enumPure "test1" |$ iter `catchI` handler
where
iter = enumPure "test2" .|$ fail "error"
handler (SomeException _) _ = return "caught error"
-- Does not catch error. |$ turns the Iter failure into a language-
-- level exception, which can only be caught in the IO Monad.
apply2 :: IO String
apply2 = enumPure "test1" |$ iter `catchI` handler
where
iter = lift (enumPure "test2" |$ fail "error")
handler (SomeException _) _ = return "caught error"
-- Catches the exception, because liftIO uses the IO catch function to
-- turn language-level exceptions into monadic Iter failures. (By
-- contrast, lift works in any Monad, so cannot do this in apply2.)
-- This example illustrates how liftIO is not equivalent to lift.
apply3 :: IO String
apply3 = enumPure "test1" |$ iter `catchI` handler
where
iter = liftIO (enumPure "test2" |$ fail "error")
handler (SomeException _) _ = return "caught error"
Arguments
| :: (ChunkData tIn, ChunkData tOut, Monad m) | |
| => Inum tIn tOut m a | |
| -> Inum tIn tOut m a | |
| -> Inum tIn tOut m a |
Concatenate the outputs of two enumerators. For example,
produces an
enumFile "file1" `cat` enumFile "file2"Onum that outputs the concatenation of files "file1" and
"file2". Unless the first Inum fails, cat always invokes the
second Inum, as the second Inum may have monadic side-effects
that must be executed even when the Iter has already finished.
See lcat if you want to stop when the Iter no longer requires
input. If you want to continue executing even in the event of an
InumFail condition, you can wrap the first Inum with
inumCatch and invoke resumeI from within the exception handler.
cat (and lcat, described below) are useful in right folds.
Say, for instance, that files is a list of files you wish to
concatenate. You can use a construct such as:
catFiles :: (MonadIOm) => [FilePath] ->OnumL.ByteStringm a catFiles files =foldr(cat.enumFile)inumNullfiles
Note the use of inumNull as the starting value for foldr. This
is not to be confused with inumNop. inumNull acts as a no-op
for concatentation, producing no output analogously to
/dev/null. By contrast inumNop is the no-op for fusing (see
|. and .| below) because it passes all data through untouched.
cat has fixity:
infixr 3 `cat`
Arguments
| :: (ChunkData tIn, ChunkData tOut, Monad m) | |
| => Inum tIn tOut m iR | |
| -> (i -> Iter tOut m iR) | |
| -> i -> Iter tIn m iR |
Left-associative pipe operator. Fuses two Inums when the
output type of the first Inum is the same as the input type of
the second. More specifically, if inum1 transcodes type tIn to
tOut and inum2 transcodes tOut to tOut2, then inum1
|. inum2 produces a new Inum that transcodes from tIn to
tOut2.
Typically types i and iR are and Iter tOut2 m a, respectively, in which case the second argument and
result of IterR
tOut2 m a|. are also Inums.
This function is equivalent to:
outer |. inner = \iter -> outer .| inner iter
infixl 4 |.
But if you like point-free notation, think of it as outer |. inner
= (outer , or better yet .|) . inner(|.) = (.) . (.
.|)
Exception functions
Arguments
| :: (Exception e, ChunkData tIn, Monad m) | |
| => Inum tIn tOut m a |
|
| -> (e -> IterR tIn m (IterR tOut m a) -> Iter tIn m (IterR tOut m a)) | Exception handler |
| -> Inum tIn tOut m a |
Catches errors thrown by an Inum, or a set of fused Inums.
Note that only errors in Inums that are lexically within the
scope of the argument to inumCatch will be caught. For example:
inumBad :: (ChunkData t, Monad m) => Inum t t m a
inumBad = mkInum $ fail "inumBad"
skipError :: (ChunkData tIn, MonadIO m) =>
SomeException
-> IterR tIn m (IterR tOut m a)
-> Iter tIn m (IterR tOut m a)
skipError e iter = do
liftIO $ hPutStrLn stderr $ "skipping error: " ++ show e
resumeI iter
-- Throws an exception, because inumBad was fused outside the argument
-- to inumCatch.
test1 :: IO ()
test1 = inumCatch (enumPure "test") skipError |. inumBad |$ nullI
-- Does not throw an exception, because inumBad fused within the
-- argument to inumCatch.
test2 :: IO ()
test2 = inumCatch (enumPure "test" |. inumBad) skipError |$ nullI
-- Again no exception, because inumCatch is wrapped around inumBad.
test3 :: IO ()
test3 = enumPure "test" |. inumCatch inumBad skipError |$ nullI
Note that `inumCatch` has the default infix precedence (infixl
9 `inumcatch`), which binds more tightly than any concatenation
or fusing operators.
As noted for catchI, exception handlers receive both the
exception thrown and the failed IterR. Particularly in the case
of inumCatch, it is important to re-throw exceptions by
re-executing the failed Iter with reRunIter, not passing the
exception itself to throwI. That way, if the exception is
re-caught, resumeI will continue to work properly. For example,
to copy two files to standard output and ignore file not found
errors but re-throw any other kind of error, you could use the
following:
resumeTest :: IO () resumeTest = doFile "file1" `cat` doFile "file2" |$stdoutIwhere doFile path = inumCatch (enumFile'path) $ \err r -> ifisDoesNotExistErrorerr thenverboseResumeIr elsereRunIterr
inumFinally :: (ChunkData tIn, Monad m) => Inum tIn tOut m a -> Iter tIn m b -> Inum tIn tOut m aSource
Execute some cleanup action when an Inum finishes.
inumOnException :: (ChunkData tIn, Monad m) => Inum tIn tOut m a -> Iter tIn m b -> Inum tIn tOut m aSource
resumeI :: (ChunkData tIn, Monad m) => IterR tIn m (IterR tOut m a) -> Iter tIn m (IterR tOut m a)Source
verboseResumeI :: (ChunkData tIn, MonadIO m) => IterR tIn m (IterR tOut m a) -> Iter tIn m (IterR tOut m a)Source
Simple enumerator construction function
The mkInum function allows you to create stateless Inums out of
simple transcoding Iters. As an example, suppose you are
processing a list of L.ByteStrings representing packets, and want
to concatenate them all into one continuous stream of bytes. You
could implement an Inum called inumConcat to do this as
follows:
iterConcat :: (Monad m) =>Iter[L.ByteString] m L.ByteString iterConcat = L.concat `liftM`dataIinumConcat :: (Monad m) =>Inum[L.ByteString] L.ByteString m a inumConcat =mkInumiterConcat
type ResidHandler tIn tOut = (tIn, tOut) -> (tIn, tOut)Source
A ResidHandler specifies how to handle residual data in an
Inum. Typically, when an Inum finishes executing, there are
two kinds of residual data. First, the Inum itself (in its role
as an iteratee) may have left some unconsumed data. Second, the
target Iter being fed by the Inum may have some resitual data,
and this data may be of a different type. A ResidHandler allows
this residual data to be adjusted by untranslating the residual
data of the target Iter and sticking the result back into the
Inum's residual data.
The two most common ResidHandlers are pullupResid (to pull the
target Iter's residual data back up to the Inum as is), and
id (to do no adjustment of residual data).
ResidHandlers are used by the mkInumC function, and by the
passCtl CtlHandler.
type CtlHandler m1 t m a = CtlArg t m a -> m1 (IterR t m a)Source
Arguments
| :: (ChunkData tIn, ChunkData tOut, Monad m) | |
| => ResidHandler tIn tOut | Adjust residual data (use |
| -> CtlHandler (Iter tIn m) tOut m a | Handle control requests (use |
| -> Iter tIn m tOut | Generate transcoded data chunks |
| -> Inum tIn tOut m a |
Create a stateless Inum from a "codec" Iter that transcodes
the input type to the output type. The codec is invoked repeately
until one of the following occurs: The codec returns null data,
the codec throws an exception, or the underlying target Iter is
no longer active. If the codec throws an exception of type
IterEOF, this is considered normal termination and the error is
not further propagated.
mkInumC requires two other arguments before the codec. First, a
ResidHandler allows residual data to be adjusted between the
input and output Iter monads. Second, a CtlHandler specifies a
handler for control requests. For example, to pass up control
requests and ensure no residual data is lost when the Inum is
fused to an Iter, the inumConcat function given previously for
mkInum at #mkInumExample could be re-written:
inumConcat :: (Monad m) => Inum [L.ByteString] L.ByteString m a
inumConcat = mkInumC reList (passCtl reList) iterConcat
where reList (a, b) = (b:a, mempty)
mkInumP :: (ChunkData tIn, ChunkData tOut, Monad m) => ResidHandler tIn tOut -> Iter tIn m tOut -> Inum tIn tOut m aSource
A simplified version of mkInum that passes all control requests
to enclosing enumerators. It requires a ResidHandler to describe
how to adjust residual data. (E.g., use pullupResid when tIn
and tOut are the same type.)
mkInumP adj = mkInumC adj (passCtl adj)
Arguments
| :: (ChunkData tIn, Monad m) | |
| => Iter tIn m b | Computation to run first |
| -> (b -> Iter tIn m c) | Computation to run last |
| -> (b -> Inum tIn tOut m a) | Inum to bracket |
| -> Inum tIn tOut m a |
Bracket an Inum with a start and end function, which can be
used to acquire and release a resource, must like the IO monad's
function. For example:
bracket
enumFile :: (MonadIO m, ChunkData t, LL.ListLikeIO t e) =>
FilePath -> Onum t m a
enumFile path = inumBracket (liftIO $ openBinaryFile path ReadMode)
(liftIO . hClose)
enumHandle
Utilities
pullupResid :: ChunkData t => (t, t) -> (t, t)Source
pullupResid (a, b) = (mappend a b, mempty). See ResidHandler.
noCtl :: Monad m1 => CtlHandler m1 t m aSource
Reject all control requests.
passCtl :: Monad mIn => ResidHandler tIn tOut -> CtlHandler (Iter tIn mIn) tOut m aSource
Pass all control requests through to the enclosing Iter monad.
The ResidHandler argument says how to adjust residual data, in
case some enclosing CtlHandler decides to flush pending input
data, it is advisable to un-translate any data in the output type
tOut back to the input type tIn.
consCtl :: (CtlCmd carg cres, ChunkData tIn, Monad mIn) => (carg -> (cres -> Iter t m a) -> Chunk t -> Iter tIn mIn (IterR t m a)) -> CtlHandler (Iter tIn mIn) t m a -> CtlHandler (Iter tIn mIn) t m aSource
Create a CtlHandler given a function of a particular control
argument type and a fallback CtlHandler to run if the argument
type does not match. consCtl is used to chain handlers, with the
rightmost handler being either noCtl or passCtl.
For example, to create a control handler that implements seek on
requests, returns the size of the file on SeekC
requests, and passes everything else out to the enclosing
enumerator (if any), you could use the following:
SizeC
fileCtl :: (ChunkData t, MonadIO m) => Handle -> CtlHandler (Iter () m) t m a fileCtl h = (mkFlushCtl$ (SeekC mode pos) -> liftIO (hSeek h mode pos)) `consCtl` (mkCtl$ SizeC -> liftIO (hFileSize h)) `consCtl`passCtlid
Has fixity:
infixr 9 `consCtl`
mkCtl :: (CtlCmd carg cres, Monad m1) => (carg -> Iter t1 m1 cres) -> carg -> (cres -> Iter t m a) -> Chunk t -> Iter t1 m1 (IterR t m a)Source
Make a control function suitable for use as the first argument to
consCtl.
mkFlushCtl :: (CtlCmd carg cres, Monad mIn, ChunkData tIn, ChunkData t) => (carg -> Iter tIn mIn cres) -> carg -> (cres -> Iter t m a) -> Chunk t -> Iter tIn mIn (IterR t m a)Source
runIterM :: (Monad m, MonadTrans mt, Monad (mt m)) => Iter t m a -> Chunk t -> mt m (IterR t m a)Source
runIterMC :: Monad m => CtlHandler (Iter tIn m) tOut m a -> Iter tOut m a -> Chunk tOut -> Iter tIn m (IterR tOut m a)Source
Run an Iter just like runIter, but then keep stepping the
result for as long as it is in the IterM or IterC state (using
the supplied CtlHandler for IterC states). Inums should
generally use this function or runIterM in preference to
runIter, as it is convenient if Inums avoid ever returning
IterRs in the IterM state.
Some basic Inums
inumNop :: (ChunkData t, Monad m) => Inum t t m aSource
inumNop passes all data through to the underlying Iter. It
acts as a no-op when fused to other Inums with |. or when fused
to Iters with .|.
inumNop is particularly useful for conditionally fusing Inums
together. Even though most Inums are polymorphic in the return
type, this library does not use the Rank2Types extension, which
means any given Inum must have a specific return type. Here is
an example of incorrect code:
let enum = if debug then base_enum|.inumStderrelse base_enum -- Error
This doesn't work because base_enum cannot have the same type as
(base_enum |. inumStderr). Instead, you can use the following:
let enum = base_enum|.if debug theninumStderrelse inumNop
inumNull :: (ChunkData tOut, Monad m) => Inum tIn tOut m aSource
inumNull feeds empty data to the underlying Iter. It pretty
much acts as a no-op when concatenated to other Inums with cat
or lcat.
There may be cases where inumNull is required to avoid deadlock.
In an expression such as enum , if |$ iterenum immediately
blocks waiting for some event, and iter immediately starts out
triggering that event before reading any input, then to break the
deadlock you can re-write the code as cat inumNull enum .
|$
iter
Enumerator construction monad
Complex Inums that need state and non-trivial control flow can be
constructed using the mkInumM function to produce an Inum out of a
computation in the InumM monad. The InumM monad implicitly keeps
track of the state of the Iter to which the Inum is feeding data,
which we call the "target" Iter.
InumM is an Iter monad, and so can consume input by invoking
ordinary Iter actions. However, to keep track of the state of the
target Iter, InumM wraps its inner monadic type with an
IterStateT transformer. Specifically, when creating an enumerator
of type , the Inum tIn tOut m aInumM action is of a type like
. That means that to
execute actions of type Iter tIn (IterStateT (InumState ...) m) () that are not polymorphic in
Iter tIn m am, you have to transform them with the liftI function.
Output can be fed to the target Iter by means of the ifeed
function. As an example, here is another version of the inumConcat
function given previously for mkInum at #mkInumExample:
inumConcat :: (Monad m) =>Inum[L.ByteString] L.ByteString m a inumConcat =mkInumMloop where loop = doChunkt eof <-chunkIdone <-ifeed$ L.concat t if not (eof || done) then loop else do resid <-ipopresidungetI[resid]
There are several points to note about this function. It reads data
in Chunks using chunkI, rather than just inputting data with
dataI. The choice of chunkI rather than dataI allows
inumConcat to see the eof flag and know when there is no more
input. chunkI also avoids throwing an IterEOF exception on end of
file, as dataI would. In contrast to mkInum, which gracefully
interprets IterEOF exceptions as an exit request, mkInumM by
default treats such exceptions as an Inum failure.
As previously mentioned, data is fed to the target Iter, which here
is of type , using Iter L.ByteString m aifeed. ifeed returns
a Bool that is when the TrueIter is no longer active. This
brings us to another point--there is no implicit looping or
repetition. We explicitly loop via a tail-recursive call to loop so
long as the eof flag is clear and ifeed returned
indicating the target FalseIter has not finished.
What happens when eof or done is set? One possibility is to do
nothing. This is often correct. Falling off the end of the InumM
do-block causes the Inum to return the current state of the Iter.
However, it may be that the Inum has been fused to the target
Iter, in which case any left-over residual data fed to, but not
consumed by, the target Iter will be discarded. We may instead want
to put the data back onto the input stream. The ipopresid function
extracts any left-over data from the target Iter, while ungetI
places data back in the input stream. Since here the input stream is
a list of L.ByteStrings, we have to place resid in a list. (After
doing this, the list element boundaries may be different, but all the
input bytes will be there.) Note that the version of inumConcat
implemented with mkInum at #mkInumExample does not have this
input-restoring feature.
The code above looks much clumsier than the version based on mkInum,
but several of these steps can be made implicit. There is an
AutoEOF flag, controlable with the setAutoEOF function, that
causes IterEOF exceptions to produce normal termination of the
Inum, rather than failure (just as mkInum handles such
exceptions). Another flag, AutoDone, is controlable with the
setAutoDone function and causes the Inum to exit immediately when
the underlying Iter is no longer active (i.e., the ifeed function
returns ). Both of these flags are set at once by the
TruemkInumAutoM function, which yields the following simpler
implementation of inumConcat:
inumConcat =mkInumAutoM$ doaddCleanup$ipopresid>>=ungetI. (: []) loop where loop = do t <-dataI-- AutoEOF flag will handle IterEOF errifeed$ L.concat t -- AutoDone flag will catch True result loop
The addCleanup function registers actions that should always be
executed when the Inum finishes. Here we use it to place residual
data from the target Iter back into the Inum's input stream.
Finally, there is a function irepeat that automatically sets the
AutoEOF and AutoDone flags and then loops forever on an InumM
computation. Using irepeat to simplify further, we have:
inumConcat=mkInumM$withCleanup(ipopresid>>=ungetI. (: [])) $irepeat$dataI>>=ifeed. L.concat
withCleanup, demonstrated here, is a variant of addCleanup that
cleans up after a particular action, rather than at the end of the
Inum's whole execution. (At the outermost level, as used here,
withCleanup's effects are identical to addCleanup's.)
In addition to ifeed, the ipipe function invokes a different
Inum from within the InumM monad, piping its output directly to
the target Iter. As an example, consider an Inum that processes a
mail message and appends a signature line, implemented as follows:
inumAddSig :: (Monad m) =>InumL.ByteString L.ByteString m a inumAddSig =mkInumM$ doipipeinumNopifeed$ L8.pack "\n--\nSent from my Haskell interpreter.\n"
Here we start by using inumNop to "pipe" all input to the target
Iter unmodified. On reading an end of file, inumNop returns, at
which point we use ifeed to append our signature.
A similar function irun runs an Onum (or Inum of a different
type) on the target Iter. For instance, to read the signature from
a file called ".signature", one could use:
inumAddSig :: (MonadIOm) =>InumL.ByteString L.ByteString m a inumAddSig =mkInumM$ doipipeinumNopirun$enumFile".signature"
Of course, these examples are a bit contrived. An even simpler implementation is:
inumAddSig =inumNop`cat`runI.enumFile".signature"
The . between runI and is because enumFileInums are
functions from Iters to IterRs; we want to apply runI to the
result of applying to an enumFile ".signature"Iter. Spelled
out, the type of is:
enumFile
enumFile :: (MonadIO m, ChunkData t, ListLikeIO t e) =>
FilePath
-> Iter t m a
-> Iter () m a (IterR t m a)
type InumM tIn tOut m a = Iter tIn (IterStateT (InumState tIn tOut m a) m)Source
A monad in which to define the actions of an . Note Inum tIn tOut m
aInumM tIn tOut m a is a Monad of kind * -> *, where
a is the (almost always parametric) return type of the Inum. A
fifth type argument is required for monadic computations of kind
*, e.g.:
seven :: InumM tIn tOut m a Int seven = return 7
Another important thing to note about the InumM monad, as
described in the documentation for mkInumM, is that you must call
twice to execute actions in monad liftm, and you must use
the liftI function to execute actions in monad .
Iter t m a
mkInumM :: (ChunkData tIn, ChunkData tOut, Monad m) => InumM tIn tOut m a b -> Inum tIn tOut m aSource
Build an Inum out of an InumM computation. If you run
mkInumM inside the monad (i.e., to create an
enumerator of type Iter tIn m), then the Inum tIn tOut m aInumM
computation will be in a Monad of type where Iter t tmtm is
a transformed version of m. This has the following two
consequences:
- If you wish to execute actions in monad
mfrom within yourInumMcomputation, you will have to applytwice (as inlift) rather than just once.lift$liftaction_in_m - If you need to execute actions in the
monad, you will have to lift them with theItert mliftIfunction.
The InumM computation you construct can feed output of type
tOut to the target Iter (which is implicitly contained in the
monad state), using the ifeed, ipipe, and irun functions.
mkInumAutoM :: (ChunkData tIn, ChunkData tOut, Monad m) => InumM tIn tOut m a b -> Inum tIn tOut m aSource
A variant of mkInumM that sets AutoEOF and AutoDone to
True by default. (Equivalent to calling as the first thing inside setAutoEOF True >>
setAutoDone TruemkInumM.)
setCtlHandler :: (ChunkData tIn, Monad m) => CtlHandler (Iter tIn m) tOut m a -> InumM tIn tOut m a ()Source
setAutoDone :: (ChunkData tIn, Monad m) => Bool -> InumM tIn tOut m a ()Source
Set the AutoDone flag within an InumM computation. When
, the TrueInum will immediately terminate as soon as the
Iter it is feeding enters a non-active state (i.e., Done or a
failure state). If this flag is (the default), the
FalseInumM computation will need to monitor the results of the
ifeed, ipipe, and irun functions to ensure the Inum
terminates when one of these functions returns .
False
addCleanup :: (ChunkData tIn, Monad m) => InumM tIn tOut m a () -> InumM tIn tOut m a ()Source
Add a cleanup action to be executed when the Inum finishes, or,
if used in conjunction with the withCleanup function, when the
innermost enclosing withCleanup action finishes.
Arguments
| :: (ChunkData tIn, Monad m) | |
| => InumM tIn tOut m a () | Cleanup action |
| -> InumM tIn tOut m a b | Main action to execute |
| -> InumM tIn tOut m a b |
Run an InumM with some cleanup action in effect. The cleanup
action specified will be executed when the main action returns,
whether normally, through an exception, because of the AutoDone
or AutoEOF flags, or because idone is invoked.
Note withCleanup also defines the scope of actions added by the
addCleanup function. In other words, given a call such as
withCleanup cleaner1 main, if main invokes , then both addCleanup
cleaner2cleaner1 and cleaner2 will be executed
upon main's return, even if the overall Inum has not finished
yet.
ifeed :: (ChunkData tIn, ChunkData tOut, Monad m) => tOut -> InumM tIn tOut m a BoolSource
Used from within the InumM monad to feed data to the target
Iter. Returns if the target FalseIter is still active and
if the iter has finished and the TrueInum should also
return. (If the autoDone flag is , then Trueifeed,
ipipe, and irun will never actually return , but
instead just immediately run cleanup functions and exit the
TrueInum when the target Iter stops being active.)
ifeed1 :: (ChunkData tIn, ChunkData tOut, Monad m) => tOut -> InumM tIn tOut m a BoolSource
A variant of ifeed that throws an exception of type IterEOF
if the data being fed is null. Convenient when reading input
with a function (such as Data.ListLike's hget) that returns 0
bytes instead of throwing an EOF exception to indicate end of file.
For instance, the main loop of could be implemented
as:
enumFile
irepeat$liftIO(LL.hGethdefaultChunkSize) >>=ifeed1
ipipe :: (ChunkData tIn, ChunkData tOut, Monad m) => Inum tIn tOut m a -> InumM tIn tOut m a BoolSource
Apply another Inum to the target Iter from within the InumM
monad. As with ifeed, returns when the TrueIter is
finished.
Note that the applied Inum must handle all control requests. (In
other words, ones it passes on are not caught by whatever handler
is installed by setCtlHandler, but if the Inum returns the
IterR in the IterC state, as inumPure does, then requests
will be handled.)
irun :: (ChunkData tAny, ChunkData tIn, ChunkData tOut, Monad m) => Inum tAny tOut m a -> InumM tIn tOut m a BoolSource