[Haskell-cafe] Re: Haskell-Cafe Digest, Vol 78, Issue 14

John Lato jwlato at gmail.com
Tue Feb 9 11:41:31 EST 2010


Edward's reply was quite good.  I'll just try to fill in a few items
he didn't address.

> From: Maciej Piechotka <uzytkownik2 at gmail.com>
>
> I read a lot about iteratee IO and it seemed very interesting
> (Unfortunately it lacks tutorial). Especially features like 'no input
> yet' in network programming (with lazy IO + parsec I run into problems
> as it tried to evaluate the first response character before sending
> output).
>
> I decided first write a simple program and then attempt write a Stream
> implementation for parsec.
>
>> {-# LANGUAGE FlexibleInstances #-}
>> {-# LANGUAGE MultiParamTypeClasses #-}
>> import Data.Iteratee
>> import Text.Parse
>>
>> data Buffer a = Buffer
>> instance Monad m => Stream (Buffer a) (IterateeG [] a m) a where
>>     uncons Buffer = IterateeG loop
>>                     where loop (Chunk [])     =
>>                               return $! Cont (IterateeG loop) Nothing
>>                           loop (Chunk (x:xs)) =
>>                               return $! Done (Just (x, Buffer))
>>                                              (Chunk xs)
>>                           loop (EOF Nothing)  =
>>                               return $! Done Nothing (EOF Nothing)
>>                           loop (EOF (Just e)) =
>>                               return $! throwErr e
>
>
> 2. Is there any package which contains this stream definition?

I believe this Stream instance is incorrect. According to the parsec-3.0.1 docs,
"A Stream instance is responsible for maintaining the 'position within
the stream' in the stream state s. This is trivial unless you are
using the monad in a non-trivial way."

This is necessary for referential integrity.  That is, "uncons s"
needs to always evaluate to the same result for the same 's'.  Your
Stream instance doesn't preserve this.  As an example,

> testIter = let b = Buffer in uncons b >> uncons b

should be an iteratee that returns a "Maybe (t, buffer)" where t is
the first element in the enumeration, but with your instance it will
return the second.

See http://inmachina.net/~jwlato/haskell/ParsecIteratee.hs for a valid
Stream instance using iteratee.  Also Gregory Collins recently posted
an iteratee wrapper for Attoparsec to haskell-cafe.  To my knowledge
these are not yet in any packages, but hackage is vast.

>
> 3. Why Seek FileOffset is error message?

Version 3 of iteratee is somewhat experimental, one of the ideas on
trial is that of resumable exceptions.  This framework is perfectly
suited to handle control messages as well, which is why Seek is
included as an error message.

I don't want to make a major release just to fix this, but both error
handling and control messages will undergo a substantial cleanup in
the next major version.  Included in this will be a proper separation
between control messages and true exceptions, most likely based upon
the extensible-exceptions framework.

Cheers,
John


More information about the Haskell-Cafe mailing list