iteratee Strange behaviour eneeCheckIfDone

Michael Baikov manpacket at gmail.com
Thu Jul 7 03:59:11 BST 2011


First let's import some things, which will be used later

> import Data.Iteratee as I
> import Data.Iteratee.Char as I
> import Data.Iteratee.IO as I
> import Control.Monad.IO.Class
> import Control.Monad.Trans.Class
> import Control.Exception
> import Control.Monad (when)
> import Data.Char (toUpper)


And then let's define some Iteratees

This one just dumps all it gets from input

> dump = printLinesUnterminated

This one performs one seek and then dumps everything else

> dumpAndSeek = I.seek 6 >> dump

Let's define some Enumeratees

This one - using regular mapChunks (and eneeCheckIfDone) (actually we
can use streamMap, but mapChunks's  type signature looks better)

> upStream :: Enumeratee String String IO a
> upStream = mapChunks (map toUpper)

This one - with my mapChunks (and modified eneeCheckIfDone)

> upStream' :: Enumeratee String String IO a
> upStream' = mapChunks' (map toUpper)

And it's time to do some test. File "hello.txt" contains message
"Hello world!!!!\n\n"

> test1 = enumFileRandom 1 "hello.txt" dump

As expected: Hello world!!!!

> test2 = enumFileRandom 1 "hello.txt" dumpAndSeek

world!!!!

> test3 = enumFileRandom 1 "hello.txt" (joinI $ upStream dump)

HELLO WORLD!!!!

> test4 = enumFileRandom 1 "hello.txt" (joinI $ upStream dumpAndSeek)

throwErr in eneeCheckIfDone - so it just hangs forever.
Unexpected behaviour.

> test5 = enumFileRandom 1 "hello.txt" (joinI $ upStream' dumpAndSeek)

And with modified version - it works fine.
WORLD!!!!

> test6 = enumFileRandom 1 "hello.txt" (joinI $ upStream (I.seek 6 >> stream2list)) >>= run >>= print

hangs forever

> test7 = enumFileRandom 1 "hello.txt" (joinI $ upStream' (I.seek 6 >> stream2list)) >>= run >>= print

"WORLD!!!!\n\n"

I don't see why it must behave differently when I am applying a simple
transformation to the stream.
And if I am misunderstanding something - what is the proper way to
dump file contents from 6'th byte
to the and while applying map upCase to it. With iteratees.

And my modified implementation - it uses
eneeCheckIfDonePass (icont . step)
instead of
eneeCheckIfDone (liftI . go)

> mapChunks' :: (Monad m, NullPoint s) => (s -> s') -> Enumeratee s s' m a
> mapChunks' f = eneeCheckIfDonePass (icont . step)
>     where
>         step k (Chunk xs)     = eneeCheckIfDonePass (icont . step) . k . Chunk $ f xs
>         step k str@(EOF mErr) = idone (k $ EOF mErr) str


eneeCheckIfDonePass - does not tries to handle any exceptions, just
passes them to
the parent Enumeratee/Enumerator


> eneeCheckIfDonePass :: (Monad m, NullPoint elo) =>
>     ((Stream eli -> Iteratee eli m a) -> Maybe SomeException -> Iteratee elo m (Iteratee eli m a))
>     -> Enumeratee elo eli m a
> eneeCheckIfDonePass f inner = Iteratee $ \od oc ->
>     let onDone x s = od (idone x s) (Chunk empty)
>         onCont k e = runIter (f k e) od oc
>     in runIter inner onDone onCont

eneeCheckIfDoneHandle - Has a separate handler for exception, so user
can decide if
he wants to handle the exception or pass it to the partent.

> eneeCheckIfDoneHandle :: (Monad m, NullPoint elo) =>
>     ((Stream eli -> Iteratee eli m a) -> Maybe SomeException -> Iteratee elo m (Iteratee eli m a))
>     -> ((Stream eli -> Iteratee eli m a) -> SomeException -> Iteratee elo m (Iteratee eli m a))
>     -> Enumeratee elo eli m a
> eneeCheckIfDoneHandle f h inner = Iteratee $ \od oc ->
>     let onDone x s = od (idone x s) (Chunk empty)
>         onCont k Nothing = runIter (f k Nothing) od oc
>         onCont k (Just e) = runIter (h k e)      od oc
>     in runIter inner onDone onCont

eneeCheckIfDoneIgnore - Ignores all exceptions

> eneeCheckIfDoneIgnore :: (Monad m, NullPoint elo) =>
>     ((Stream eli -> Iteratee eli m a) -> Maybe SomeException -> Iteratee elo m (Iteratee eli m a))
>     -> Enumeratee elo eli m a
> eneeCheckIfDoneIgnore f inner = Iteratee $ \od oc ->
>     let onDone x s = od (idone x s) (Chunk empty)
>         onCont k _ = runIter (f k Nothing) od oc
>     in runIter inner onDone onCont



More information about the Iteratee mailing list