I have a parser with a prefix "-" and an infix "=". When I try to
parse "x=-1", it fails. Does anyone know how to fix this?
I stripped my code down as much as possible. It parses "x=1" and
"-1", but fails for "x=-1".
import Text.Parsec
import qualified Text.Parsec.Expr as PE
import qualified Text.Parsec.Language as L
import qualified Text.Parsec.Token as T
lexer = T.makeTokenParser L.emptyDef {T.reservedOpNames = ["=", "-"]}
reservedOp = T.reservedOp lexer
integer = T.integer lexer >> return ""
symbol = T.identifier lexer
expression = PE.buildExpressionParser table (integer <|> symbol)
where
table = [ [ PE.Prefix (reservedOp "-" >> return (\x-> "")) ],
[ PE.Infix (reservedOp "=" >> return (\x-> \y->""))
PE.AssocRight ] ]
input = do
e <- expression
eof
return e
testParse s = case (parse input "(unknown)" s) of
Left f -> putStrLn $ s ++ "\n" ++ show f
Right f -> putStrLn s
main = do
testParse "x=1"
testParse "-1"
testParse "x=-1"
_________________________________________________________________
Hotmail: Free, trusted and rich email service.
http://clk.atdmt.com/GBL/go/201469228/direct/01/
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell