[Haskell-cafe] [iteratee] empty chunk as special case of input

John Lato jwlato at gmail.com
Thu Jul 14 02:15:56 CEST 2011


Hi Sergey,

iteratee (the package) uses a null chunk to signify that no further
stream data is available within the iteratee, that is, at some point
the stream has been entirely consumed.  Therefore, if any of the
composed iteratees haven't run to completion, they need to get more
data from an enumerator.  Thus 'bindIteratee' has the nullC guard in
the definition as an optimization; there's no need to send the null
chunk to bound iteratees because in most cases they won't be able to
do anything with it.

I've recently considered removing this, but at present when I take it
out some unit tests fail and I haven't had time to explore further.
Since this would have other benefits I would like to do so provided it
doesn't strongly impact performance.  Rather than simply removing the
case I could add a null case to the Stream type, but that could cause
some extra work for users.

Also, one rule for writing iteratees is that they shouldn't put
elements into the stream.  Doing so may cause various transformers to
behave incorrectly.  If you want to modify a stream rather than simply
consuming elements, the correct approach is to create an enumeratee
(stream transformer).

John L.

On Wed, Jul 13, 2011 at 11:00 PM, Sergey Mironov <ierton at gmail.com> wrote:
> Hi community, hi John. I find myself reading bindIteratee[1] function
> for a several days.. there is something that keeps me away from
> completely understanding of the concept. The most noticeble thing is
> \nullC\ guard in the definition. To demonstate the consequences of
> this solution, let me define an iterator like
>
> myI = Iteratee $ \onDone _ -> onDone 'a' (Chunk "xyz")
>
> It is a bit unusial, since myI substitutes real stream with a fake one
> (xyz). Now lets define two actions producing different results in
> unusual manner:
>
> printI i = enumPure1Chunk ['a'..'g'] i >>= run >>= print
>
> i1 = (return 'b' >> myI >> I.head)  -- myI substitutes the stream,
> last /I.head/ produces 'x', OK
> i2 = (I.head >> myI >> I.head) -- produces 'b'!  I expected another
> 'x' here but myI's stream was ignored by >>=
>
> Well, I understand that this is probably an expected behaviour, but
> what is it for? Why we can't handle null input like non-null? Iterator
> may just stay in it's current state in that case.
>
> Thanks in advance
> Sergey
>
> --
> [1] - bindIteratee (basically, >>=) code from Data.Iteratee.Base.hs
>
> bindIteratee :: (Monad m, Nullable s)
>    => Iteratee s m a
>    -> (a -> Iteratee s m b)
>    -> Iteratee s m b
> bindIteratee = self
>    where
>        self m f = Iteratee $ \onDone onCont ->
>             let m_done a (Chunk s)
>                   | nullC s      = runIter (f a) onDone onCont
>                 m_done a stream = runIter (f a) (const . flip onDone
> stream) f_cont
>                   where f_cont k Nothing = runIter (k stream) onDone onCont
>                         f_cont k e       = onCont k e
>             in runIter m m_done (onCont . (flip self f .))
>



More information about the Haskell-Cafe mailing list