[Haskell-cafe] Iteratee, parsec & co.
Maciej Piechotka
uzytkownik2 at gmail.com
Tue Feb 9 04:03:46 EST 2010
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.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: This is a digitally signed message part
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20100209/23b30f9e/attachment.bin
More information about the Haskell-Cafe
mailing list