
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
1. I'm not quite sure what Cursor was suppose to do from A Parsing Trifecta presentation. 2. Is there any package which contains this stream definition? 3. Why Seek FileOffset is error message? Regards PS. I guess iteratee does qualify as cafe but if beginner would be more appropriate group then I'm sorry - I'll remember next time.

Am Dienstag 09 Februar 2010 10:03:46 schrieb Maciej Piechotka: Sorry, I haven't looked at iteratees at all, so I can't answer your questions.
PS. I guess iteratee does qualify as cafe but if beginner would be more appropriate group then I'm sorry - I'll remember next time.
It's not that one kind of question is for the beginners list and only more advanced questions are to be posted in the cafe, the distinction is - the beginners list is lower traffic, so your questions are less likely to be overlooked there (though it's unlikely to be overlooked in the cafe either) - questions on beginners are less likely to get answers involving terms like "zygohistomorphic prepromorphism" So it's more a decision of "what kind of answer do you want" where to post your question. Another aspect is that your question and the answers are more visible on beginners (especially to beginners), so if you think your question is something many beginners would wrestle with, that's a reason to post it on beginners (or both lists), so other beginners may profit more from it.

On Tue, Feb 9, 2010 at 4:03 AM, Maciej Piechotka
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
1. I'm not quite sure what Cursor was suppose to do from A Parsing Trifecta presentation.
Note that my parsing trifecta Iteratee differs from the iteratees defined by Oleg et al; it has access to the entire input so far (accumulated in a fingertree). The Cursor is the index into that finger tree, and is tracked as the 'remaining input' by Parsec, allowing backtracking. The presentation up to that point centers on the changes necessary to Iteratee to make this possible. 2. Is there any package which contains this stream definition?
Not that I'm aware of, but I hardly qualify as an expert in the mainline Iteratee implementation. 3. Why Seek FileOffset is error message?
I'm not quite sure what you're asking here. -Edward Kmett

| 3. Why Seek FileOffset is error message? Are you talking about John Lato's implementation [1]? Well, `Seek' is not an error message. It is one of constructors for ErrMsg, and ErrMsg is [2]
-- -- a message to the stream producer (e.g., to rewind the stream) -- or an error indication.
You know the overall idea behind Seek, don't you? It is an instrument to implement random IO [3]. Compare Oleg's code [4]
data SeekException = SeekException FileOffset deriving Show
instance Typeable SeekException where typeOf _ = mkTyConApp (mkTyCon "SeekException") []
instance Exception SeekException
and [2]
type ErrMsg = SomeException data Stream el = EOF (Maybe ErrMsg) | Chunk [el] deriving Show
with John Lato's implementation [1]:
data StreamG c el = EOF (Maybe ErrMsg) | Chunk (c el)
data ErrMsg = Err String | Seek FileOffset deriving (Show, Eq)
John makes Err and Seek to be the distinct constructors of ErrMsg. Errors (Err) in `iteratee' package are always Strings. Oleg's ErrMsg is SomeException. One of its instances (SeekException) is a ``rewind the stream'' message to the stream producer. And the user is free to have as many different ErrMsg'es as he needs to do the job. [1] http://inmachina.net/~jwlato/haskell/iteratee/src/Data/Iteratee/Base.hs [2] http://okmij.org/ftp/Haskell/Iteratee/IterateeM.hs [3] http://okmij.org/ftp/Streams.html#random-bin-IO [4] http://okmij.org/ftp/Haskell/Iteratee/RandomIO.hs -- vvv
participants (4)
-
Daniel Fischer
-
Edward Kmett
-
Maciej Piechotka
-
Valery V. Vorotyntsev