[Haskell-beginners] parser for expressions
Stephen Tetley
stephen.tetley at gmail.com
Sun Dec 27 15:07:45 EST 2009
Hi John
Whilst this won't have the learning value of working through parser
combinators yourself, here's code that uses Parsec 2 to do want you
want. Its the code from page 12 of Daan Leijen's Parsec manual [1]
except it builds a syntax tree of the expression rather than evaluates
it. I modified it for a query on Haskell cafe today, but only posted
it off list. Some formatting might get "lost in the mail" of course.
[1] http://research.microsoft.com/en-us/um/people/daan/download/parsec/parsec.pdf
Best wishes
Stephen
module ExprSyn where
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Expr
runExpr :: String -> IO ()
runExpr str = case runParser expr () "nofile" str of
Left err -> putStrLn "Error:" >> print err
Right val -> print val
demo1 = runExpr "1+1"
data Expr = Mul Expr Expr
| Div Expr Expr
| Add Expr Expr
| Sub Expr Expr
| Val Integer
deriving (Eq,Show)
expr :: Parser Expr
expr = buildExpressionParser table factor
<?> "expression"
table :: [[Operator Char st Expr]]
table = [[op "*" Mul AssocLeft, op "/" Div AssocLeft]
,[op "+" Add AssocLeft, op "-" Sub AssocLeft]
]
where
op s f assoc
= Infix (do{ string s; return f}) assoc
factor :: Parser Expr
factor = do{ char '('
; x <- expr
; char ')'
; return x
}
<|> number
<?> "simple expression"
number :: Parser Expr
number = do{ ds <- many1 digit
; return (Val $ read ds)
}
<?> "number"
More information about the Beginners
mailing list