I haven't really used the expr parser combinator recently, but it does
sound like the parser with higher precedence is failing after reading
characters when processing the earlier "|" operator.
You could try using (try (reservedOp name)) in the definition of
binaryOp, which should prevent the operator from causing the error to
propagate out of the expression parser. Then the more general "||"
parser should be able to get to it.
Otherwise it will probably be necessary to use a follow set approach and
test of any further operator characters in the parser for the operator.
From the error message it sounds that's already being done though.
Hope this helps.
-- Lorenz
Daniel Fischer wrote:
Am Montag, 29. Dezember 2008 10:27 schrieb Erik de Castro Lopo:
Hi all,
I'm using Text.ParserCombinators.Parsec.Expr to parse expressions for
a Javascript like language. This language has C-like logical operators
('&&' and '||') and bitwise operators ('&' and '|'). Furthermore, the
language definition states that bitwise operators have a higher precedence
than the logical ones.
I therefore have the following (trimmed):
import qualified Text.ParserCombinators.Parsec.Expr as E
opTable :: [[ E.Operator Char st Expression ]]
opTable = [
-- Operators listed from highest precedence to lowest precedence.
{- snip, snip -}
[ binaryOp "&" BinOpBinAnd E.AssocLeft ],
[ binaryOp "^" BinOpBinXor E.AssocLeft ],
[ binaryOp "|" BinOpBinOr E.AssocLeft ],
[ binaryOp "&&" BinOpLogAnd E.AssocLeft ],
[ binaryOp "||" BinOpLogOr E.AssocLeft ]
]
binaryOp :: String -> (SourcePos -> a -> a -> a) -> E.Assoc ->
E.Operator Char st a binaryOp name con assoc =
E.Infix (reservedOp name >>
getPosition >>=
return . con) assoc
but I still get the following parse error:
unexpected "|"
expecting end of "|" or term
on the line:
if (name == null || value == null)
If I change the above from a logical to a bitwise OR, the parser
accepts it quite happily.
The problem is that "|" is a prefix of "||" and it gets the first bite. So
when the parser gets to "||" it first tries to parse a bitwise or. That
succeeds. Then the parser is looking for an operand, but it finds the second
- unexpected - "|". I don't remember how Parsec's expression parsers work,
maybe you can add a "try" some parser(s) to make it work.
Any clues as to what I'm doing wrong here?
Cheers,
Erik
_______________________________________________
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