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

Sergey Mironov ierton at gmail.com
Thu Jul 14 00:00:00 CEST 2011


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