Yeah, that's weird.  I played around with la and it seems to only cause
problems when the parser passed into lookAhead succeeds, which seem to go
directly against it's stated purpose.

lookAhead isn't  consuming, (hence the unexpected "b") but still prevents
<|> from doing it's thing.

Seems like a bug to me...

My off the hip fix is a modified form of the ugly try:

lookAhead (ParsecT p)
    = ParsecT $ \s@(State _ pos _) -> do
        res <- p s
        case res of
          Consumed rep -> do r <- rep
                             case r of
                               Error err -> return $ Empty $ return $ Error
(setErrorPos pos err)
                               Ok a state err -> return $ Empty $ return $
Ok a s err
          empty        -> return $ empty


The only potential annoyance with this fix that I can see, is that the error
messages can be confusing if you are doing dumb things with your lookAhead
parsers. For example:

la :: Parsec String () (Char)
la = lookAhead' (char 'r')

*Main> parseTest ((la >> char 'a') <|> char 'b') "a"
parse error at (line 1, column 1):
unexpected "a"
expecting "r" or "b"
*Main> parseTest ((la >> char 'a') <|> char 'b') "r"
parse error at (line 1, column 2):
unexpected "r"
expecting "a" or "b"

But for the most part it behaves as expected.

- Job

(sorry for the double post Martijn, forgot to reply to all)

On Thu, Aug 20, 2009 at 7:44 AM, Martijn van Steenbergen <
mart...@van.steenbergen.nl> wrote:

> 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?
>
> Thanks,
>
> Martijn.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to