[Haskell] Parsec operator issue
Greg Fitzgerald
garious at gmail.com
Tue Feb 16 17:48:05 EST 2010
Hi Adam,
> parse "x=-1", it fails. Does anyone know how to fix this?
This issue is in using the 'reservedOp' combinator which rejects '='
when followed by '-'.
reservedOp name =
lexeme $ try $
do{ string name
; notFollowedBy (opLetter languageDef) <?> ("end of " ++ show name)
}
If you change:
reservedOp "="
to:
char '='
then your test passes.
-Greg
On Tue, Feb 16, 2010 at 2:10 PM, Adam Crume <adamcrume at hotmail.com> wrote:
> 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. Get it now.
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>
>
More information about the Haskell
mailing list