
Hi, I'm using buildExpressionParser, and I'd like to use alphanumeric operator characters. I get an (unexpected "a") error though. With a test string like "-a" if "a" is used in any of the "reservedOpNames". I'm aiming for the Fortran operators like ".and.". The listing below may be helpful. It's taken from the Haskell wiki's "Parsing expressions and statements" article (minus the statement part).I've added an ":a:" operator. The article uses "~" as a unary operator (I'm heading for +/-). It can be tested with: $ parseTest exprparser "~a" -- code begins module Main where import Control.Monad(liftM) import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec.Expr import Text.ParserCombinators.Parsec.Token import Text.ParserCombinators.Parsec.Language data Expr = Var String | Con Bool | Uno Unop Expr | Duo Duop Expr Expr deriving Show data Unop = Not deriving Show data Duop = And | Iff deriving Show data Stmt = Nop | String := Expr | If Expr Stmt Stmt | While Expr Stmt | Seq [Stmt] deriving Show def = emptyDef{ commentStart = "{-" , commentEnd = "-}" , identStart = letter , identLetter = alphaNum , opStart = oneOf "~&=:" , opLetter = oneOf "~&=:a" , reservedOpNames = ["~", "&", "=", ":=", ":a:"] , reservedNames = ["true", "false", "nop", "if", "then", "else", "fi", "while", "do", "od"] } TokenParser{ parens = m_parens , identifier = m_identifier , reservedOp = m_reservedOp , reserved = m_reserved , semiSep1 = m_semiSep1 , whiteSpace = m_whiteSpace } = makeTokenParser def exprparser :: Parser Expr exprparser = buildExpressionParser table term > "expression" table = [ [Prefix (m_reservedOp "~" >> return (Uno Not))] , [Infix (m_reservedOp "&" >> return (Duo And)) AssocLeft] , [Infix (m_reservedOp "=" >> return (Duo Iff)) AssocLeft] , [Infix (m_reservedOp ":a:" >> return (Duo Iff)) AssocLeft] ] term = m_parens exprparser <|> liftM Var m_identifier <|> (m_reserved "true" >> return (Con True)) <|> (m_reserved "false" >> return (Con False)) play :: String -> IO () play inp = case parse exprparser "" inp of { Left err -> print err ; Right ans -> print ans } -- code ends Cheers, Paul Keir Research Student University of Glasgow Department of Computing Science pkeir@dcs.gla.ac.uk