I've got an example from documentation for Text.Parsec.Expr
.
expr = buildExpressionParser table term
<?> "expression"
term = parens expr
<|> natural
<?> "simple expression"
table = [ [prefix "-" negate, prefix "+" id ]
, [postfix "++" (+1)]
, [binary "*" (*) AssocLeft, binary "/" (div) AssocLeft ]
, [binary "+" (+) AssocLeft, binary "-" (-) AssocLeft ]
]
I'd tried to add postfix --
operation and changed the second line for table to
, [postfix "++" (+1), postfix "--" (subtract 1)]
Now
runParser expr () "expr" "1--"
give me Right 1
in ghci.
Why I got it and how to provide postfix (--
)?
"--1"
gets parsed as [prefix "-", prefix "-", number 1]
and evaluated as negate (negate 1)
which yields 1.
To get a postfix (--)
, does runParser expr () "expr" "1--"
not give you a postfix --
?
The parse seems to not consume the entire input. I can't tell why, though,
module ExParse where
import Text.Parsec
import Text.Parsec.Expr
parens p = do
char '('
e <- p
char ')'
return e
reservedOp s = do
string s
notFollowedBy letter
natural = fmap read $ many1 digit
expr = buildExpressionParser table term
<?> "expression"
term = parens expr
<|> natural
<?> "simple expression"
table = [ [prefix "-" negate, prefix "+" id ]
, [postfix "++" (+1), postfix "--" (subtract 1)]
, [binary "*" (*) AssocLeft, binary "/" (div) AssocLeft ]
, [binary "+" (+) AssocLeft, binary "-" (-) AssocLeft ]
]
binary name fun assoc = Infix (do{ reservedOp name; return fun }) assoc
prefix name fun = Prefix (do{ reservedOp name; return fun })
postfix name fun = Postfix (do{ reservedOp name; return fun })
res = runParser expr () "expr" "1--"
yields
*ExParse> res
Right 0
as desired here.
The problem with natural = P.natural lexer
is that it is defined as
natural = lexeme nat
and
lexeme p = do
x <- p
whiteSpace
return x
where comments count as whitespace. Now, the line comments in Haskell start with --
, hence with natural = P.natural lexer
, the natural
consumes the entire string "1--"
. To make --
usable as a postfix operator, you have to choose a language definition where that is not a comment starter. For example, you can modify haskellDef
per
lexer = P.makeTokenParser (haskellDef{P.commentLine = "//"})
or redefine the whiteSpace
parser.