[Haskell-cafe] Re: Problem with lazy IO
Maciej Piechotka
uzytkownik2 at gmail.com
Sun Jul 19 11:06:05 EDT 2009
Maciej Piechotka <uzytkownik2 <at> gmail.com> writes:
>
> Hello.
>
> I've tried to combine lazy IO and parsec. The hole process is done by
> network.
>
> Currently I have implemented 'short parsers' so I enter them on need. To
> update state I have following code:
> parser2nntp :: Monad m => NntpParser m a -> NntpT m a
> parser2nntp p = do s <- NntpT (gets $ input . connection)
> e <- runParserT (do v <- p
> i <- getInput
> return (v, i)) () "" s
> case e of
> Left er -> error $ show er
> Right (v, i') -> (NntpT (modify (pNI i')) >> return
> v)
> where pNI :: Monad m => ByteString ->NntpState m ->
> NntpState m
> pNI i s = s {connection = (connection s) {input =
> i}}
>
> However the 4 line (i <- getInput) blocks the execution as trace
> indicated. String returned have no input available so it should block on
> evaluation - and here I pass only a reference to it (or rather I think
> so). What's wrong?
>
> PS. Full code is in darsc nntp repository http://code.haskell.org/nntp/
> - please note that it seems to require network compiled against parsec 3
> - not 2.
>
>
This code seems to work:
parser2nntp :: Monad m => NntpParser m a -> NntpT m a
parser2nntp p = do s <- NntpT (gets $ input . connection)
r <- parserRep =<< runParsecT p (State s (initialPos "") ())
case r of
Ok v (State i _ _) _ -> NntpT (modify $ pNI i) >> return v
Error e -> error $ show e
where parserRep (Consumed x) = x
parserRep (Empty x) = x
pNI i s = s {connection = (connection s) {input = i}}
Regards
More information about the Haskell-Cafe
mailing list