
Dear Haskellers, I am new to programming in haskell, recently I came up with an task to write an simple arithemtic evaluator in haskell. I try to write it using Text.Parsec, it can handle binary operation and some unary operation, but will give information of parsing error in some case. The following is my code import Text.Parsec import Text.Parsec.Expr import Text.Parsec.Combinator import Data.Functor data Exp = Num Int | Add Exp Exp | Sub Exp Exp | Mul Exp Exp | Div Exp Exp | Pos Exp | Neg Exp expr = buildExpressionParser table factor table = [[op "*" (Mul) AssocRight, op "/" (Div) AssocRight] ,[op "+" (Add) AssocLeft, op "-" (Sub) AssocLeft] ,[prefix "-" (Neg), prefix "+" (Pos)]] where op s f assoc = Infix (f <$ string s) assoc prefix s f = Prefix (f <$ string s) factor = between (char '(') (char ')') expr <|> (Num . read <$> many1 digit) eval :: (Num a, Integral a) => Exp -> a eval e = case e of Num x -> fromIntegral x Pos a -> eval a Neg a -> negate $ eval a Add a b -> eval a + eval b Sub a b -> eval a - eval b Mul a b -> eval a * eval b Div a b -> eval a `div` eval b solution :: (Num a, Integral a) => String -> a solution = either (const (error "Did not parse")) eval . parse expr "" The following is some test, *Main> solution "-4/(2+3)" 0 *Main> solution "-4/(2-3)" 4 *Main> solution "-4/-2" *** Exception: Did not parse *Main> solution "16/-4" *** Exception: Did not parse *Main> solution "-16/4" -4 *Main> Can anyone teach me how to solve this? Thanks in advanced. --m00nlight

On Mon, Mar 30, 2015 at 02:22:20PM +0800, m00nlight wrote:
I am new to programming in haskell, recently I came up with an task to write an simple arithemtic evaluator in haskell. I try to write it using Text.Parsec, it can handle binary operation and some unary operation, but will give information of parsing error in some case. The following is my code
[..] Can anyone teach me how to solve this? Thanks in advanced.
Hello, first things first, I slightly modified your `solution` function, so it can fail with meaningful error messages solution :: (Num a, Integral a) => String -> a solution = either (error . show) eval . parse expr "" Then I added to `<?>` operators at the end of your parsing expression (again, for easier diagnostic). factor = between (char '(') (char ')') expr <|> (Num . read <$> many1 digit) <?> "factor" expr = buildExpressionParser table factor <?> "expr" Now the error message is: λ> solution "-4/-2" *** Exception: (line 1, column 4): unexpected "-" expecting factor So Parsec was expecting a "factor" element but found itself with '-'. The first alternative of factor is not what we want (an expression surrounded by parentheses). The second part should be it (a 'number'). Now it is easy to recognise the problem: `digit` only accepts digits and not '-' as a prefix. When parsing stuff, <?>, small functions and early testing (with hspec[1]) saved me much time and pain debugging. [1] http://hspec.github.io/

Hi Francesco,
Thanks for your explaination, so how can I modify the parser to handle this case?
Can you give me some more details of how to modify it?
Thanks in advanced.
--m00nlight
在2015年03月30 15时05分, "Francesco Ariis"
I am new to programming in haskell, recently I came up with an task to write an simple arithemtic evaluator in haskell. I try to write it using Text.Parsec, it can handle binary operation and some unary operation, but will give information of parsing error in some case. The following is my code
[..] Can anyone teach me how to solve this? Thanks in advanced.
Hello, first things first, I slightly modified your `solution` function, so it can fail with meaningful error messages solution :: (Num a, Integral a) => String -> a solution = either (error . show) eval . parse expr "" Then I added to `<?>` operators at the end of your parsing expression (again, for easier diagnostic). factor = between (char '(') (char ')') expr <|> (Num . read <$> many1 digit) <?> "factor" expr = buildExpressionParser table factor <?> "expr" Now the error message is: λ> solution "-4/-2" *** Exception: (line 1, column 4): unexpected "-" expecting factor So Parsec was expecting a "factor" element but found itself with '-'. The first alternative of factor is not what we want (an expression surrounded by parentheses). The second part should be it (a 'number'). Now it is easy to recognise the problem: `digit` only accepts digits and not '-' as a prefix. When parsing stuff, <?>, small functions and early testing (with hspec[1]) saved me much time and pain debugging. [1] http://hspec.github.io/

On Mon, Mar 30, 2015 at 04:10:18PM +0800, m00nlight wrote:
Hi Francesco,
Thanks for your explaination, so how can I modify the parser to handle this case? Can you give me some more details of how to modify it?
Thanks in advanced.
Can't now, but take a look at Parsec.Token.reservedOp! You might want to read what it does and use it instead of `string`
participants (2)
-
Francesco Ariis
-
m00nlight