Parsec : Problems with operator precedence

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. Any clues as to what I'm doing wrong here? Cheers, Erik -- ----------------------------------------------------------------- Erik de Castro Lopo ----------------------------------------------------------------- BSD: A psychoactive drug, popular in the 80s, probably developed at UC Berkeley or thereabouts. Similar in many ways to the prescription-only medication called "System V", but infinitely more useful. (Or, at least, more fun.) The full chemical name is "Berkeley Standard Distribution".

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

Daniel Fischer wrote:
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.
I've did try a 'try' but that didn't help. Erik -- ----------------------------------------------------------------- Erik de Castro Lopo ----------------------------------------------------------------- "Whenever the C++ language designers had two competing ideas as to how they should solve some problem, they said, "OK, we'll do them both". So the language is too baroque for my taste." -- Donald E Knuth

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

Erik de Castro Lopo wrote:
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
Replacing reservedOp above with: reservedOpNf :: String -> CharParser st () reservedOpNf name = try (reservedOp name >> notFollowedBy (oneOf "|&=")) fixed the problem. Cheers, Erik -- ----------------------------------------------------------------- Erik de Castro Lopo ----------------------------------------------------------------- "If dolphins are so smart, why do they live in igloos?" -Eric Cartman

Erik de Castro Lopo wrote:
Replacing reservedOp above with:
reservedOpNf :: String -> CharParser st () reservedOpNf name = try (reservedOp name >> notFollowedBy (oneOf opChars))
fixed the problem.
Just for the sake of completeness and the google archive, the above fixed the main problem but left another problem in parsing something like: if (whatever == -1) which resulted in a error at uninary minus sign. The problem was that the reservedOp combinator as used above chews up any trailing whitespace so that the notFollowedBy was triggered by the minus. The solution was to use the string combinator instead of reservedOp, then use the notFollowedBy and finally chew up trailing whitespace as follows: reservedOpNf :: String -> CharParser st () reservedOpNf name = try (string name >> notFollowedBy (oneOf "|&=") >> whiteSpace) Erik -- ----------------------------------------------------------------- Erik de Castro Lopo ----------------------------------------------------------------- Is God willing to prevent evil, but not able? Then he is not omnipotent. Is he able, but not willing? Then he is malevolent. Is he both able and willing? Then whence cometh evil? Is he neither able nor willing? Then why call him God? -- Epicurus, Greek philosopher, BC 341-270

Erik de Castro Lopo schrieb:
Erik de Castro Lopo wrote:
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
Replacing reservedOp above with:
reservedOpNf :: String -> CharParser st () reservedOpNf name = try (reservedOp name >> notFollowedBy (oneOf "|&="))
fixed the problem.
Hi Erik, There is an easy, better solution, modifying the lexer:
lexer = makeTokenParser $ emptyDef { L.reservedOpNames = words "&& || & | ^" } reservedOp = P.reservedOp lexer identifier = P.identifier lexer ...
I'd try to avoid 'try', if possible. benedikt

Benedikt Huber wrote:
There is an easy, better solution, modifying the lexer:
lexer = makeTokenParser $ emptyDef { L.reservedOpNames = words "&& || & | ^" } reservedOp = P.reservedOp lexer identifier = P.identifier lexer ...
I'd try to avoid 'try', if possible.
Hi Benedikt, I did try that (reservedOpNames as a list of operators as strings) but that interferred rather badly with another part of the parser which handles raw inline XML like this (yes, utterly horrid): var xdata = <xml>sucks</xml> ; Because I had the XML parsing working when I hit the operator precedence problem I worked towards a solution that didn't break the XML rather than do the right thing to fix the operator precedence and then have to fix the XML part. Erik -- ----------------------------------------------------------------- Erik de Castro Lopo ----------------------------------------------------------------- "how am I expected to quit smoking if I have to deal with NT every day" -- Ben Raia
participants (4)
-
Benedikt Huber
-
Daniel Fischer
-
Erik de Castro Lopo
-
Lorenz Pretterhofer