[Haskell-beginners] Clearing Parsec error messages

Daniel Fischer daniel.is.fischer at web.de
Sat Jun 6 07:36:33 EDT 2009


Am Samstag 06 Juni 2009 02:05:13 schrieb Giuliano Vilela:
> Hi all,
>
> In a Parsec project I used the *fail* parser, wanting to show a message to
> the user and halt the parsing process. That's okay, but the error message
> showed included some other "unexpected" and "expecting" messages that did
> not seem related to the fail.

I suppose your parser is not

do return 'a'
   fail "No dice"

but rather something like

do commonPreamble
   foo <|> bar <|> baz <|> fail message

and fail is only called if none of the possibilities succeed?

Then each of the failing parsers foo, bar and baz may add messages what input would have 
allowed them to proceed:
---------------------------------
module FailTest where

import Text.ParserCombinators.Parsec

pa = char 'a'

pb = char 'b'

pc = char 'c'

parser1 = pa <|> pb <|> pc <|> fail "Sorry, no parse"

test1 = parse parser1 "test1" "d'oh"

------------------------------------------------------------

*FailTest> test1
Left "test1" (line 1, column 1):
unexpected "d"
expecting "a", "b" or "c"
Sorry, no parse

That's probably the kind of output you get. But I'd say the messages are very much related 
to the fail, most likely it's better to keep them.

But if you absolutely want to get rid of them, you need a custom fail that consumes some 
input to remove the earlier expect messages. To avoid breaking the actual input or falling 
afoul of end of input, first inject a dummy token into the input, then consume that, and 
only thereafter fail:
-----------------------------------------------------------------

myfail msg = do
    inp <- getInput
    setInput ('x':inp)
    anyToken
    fail msg

parser2 = pa <|> pb <|> pc <|> myfail "sorry, doesn't parse"

test2 = parse parser2 "test2" "d'oh"
--------------------------------------------------------------------------

*FailTest> test2
Left "test2" (line 1, column 1):
sorry, doesn't parse

But that probably does more harm than good.
>
> My guess is that Parsec keeps these messages in an internal state, to use
> them whenever needed. My question is, how can I clear those error messages
> and only show the string I pass to fail?



More information about the Beginners mailing list