[Haskell-cafe] Parsec lookahead and <|>
Daniel Fischer
daniel.is.fischer at web.de
Thu Aug 20 12:04:02 EDT 2009
Am Donnerstag 20 August 2009 13:44:15 schrieb Martijn van Steenbergen:
> Goedemiddag café,
>
> Consider the following function, using parsec-3.0.0:
> > la :: Parsec String () (Maybe Char)
> > la = lookAhead (optionMaybe anyChar)
>
> *Lookahead> parseTest (char 'a' <|> char 'b') "a"
> 'a'
> *Lookahead> parseTest (char 'a' <|> char 'b') "b"
> 'b'
> *Lookahead> parseTest (la *> char 'a' <|> char 'b') "a"
> 'a'
> *Lookahead> parseTest (la *> char 'a' <|> char 'b') "b"
> parse error at (line 1, column 2):
> unexpected "b"
> expecting "a"
>
> The first three work fine and as expected, but the fourth example fails
> where I would expect success. I know <|> won't try the rhs if the lhs
> consumed input, but lookAhead's documentation promises not to consume
> any input. Is this a bug in Parsec or am I missing something?
Bad bug in Parsec (from the beginning, the same happens in parsec-2), I'd say.
Desugared, we have
lookAhead p = getParserState >>= \st -> p >>= \r -> setParserState st >>= \_ -> return r
Due to the (>>=), whenever p consumes input, lookAhead will return (Consumed _) and
there's no way to get rid of it, so (la *> char 'a') returns Consumed (Error something) on
the input "b" and (<|>) doesn't try char 'b'.
The code for lookAhead should look something like (parsec-2, to avoid 'returns' cluttering
the code):
lookAhead p = Parser $ \st -> case parserReply $ runP p st of
Ok x s err -> Empty (Ok x st err)
Error err -> Empty (Error err)
Since exporting an 'unconsume' function wouldn't be desirable, lookAhead would have to
move to Text.Parse(rCombinators.Parse)c.Prim.
(not necessary in parsec-3 yet, since that exports all top level definitions from all
modules so far).
>
> Thanks,
>
> Martijn.
More information about the Haskell-Cafe
mailing list