On Tue, Feb 9, 2010 at 4:03 AM, Maciej Piechotka <uzytkownik2@gmail.com> wrote:
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