
Hi , Havent used haskell in a while can someone explain just whats happening here. I know what it does, I just can't workout how it does it. Only need to explain how the red area works and I can work out the rest myself Regards John module Rollback where data Expression = Val Double | Add Expression Expression | Subtract Expression Expression | Multiply Expression Expression | Divide Expression Expression deriving Show demo1 = (Add(Multiply(Divide(Subtract(Val 25)(Val 5))(Val 10))(Val 7))(Val 30)) evalStep :: Expression -> Expression evalStep (Val x)= (Val x) evalStep (Add x y) = case x of (Val a) -> case y of (Val b) -> Val (a+b) left -> Add x (evalStep y) right -> Add (evalStep x)y evalStep (Subtract x y) = case x of (Val a) -> case y of (Val b) -> Val (a-b) left -> Subtract x (evalStep y) right -> Subtract (evalStep x)y evalStep (Multiply x y) = case x of (Val a) -> case y of (Val b) -> Val (a*b) left -> Multiply x (evalStep y) right -> Multiply (evalStep x)y evalStep (Divide x y) = case x of (Val a) -> case y of (Val b) -> Val (a/b) left -> Divide x (evalStep y) right -> Divide (evalStep x)y type Stack = [Expression] evaluate :: Expression -> IO () evaluate exp = do stk <- evalWithStack exp [exp] putStrLn "End of Equation" evalWithStack :: Expression -> Stack -> IO Stack -- Base case evalWithStack (Val a) stk = return stk -- Recursive case evalWithStack e stk = do putStrLn "Evaluating one more step" let e' = (evalStep e) putStrLn ("Result is "++(show e')) putStrLn "Do another step (y/n) or rollback (r)? :" c <- getLine case c of "y" -> evalWithStack e' (e':stk) "r" -> let (a,stk') = stackBack stk in evalWithStack a stk' "n" -> do { putStrLn ("Ok you said :" ++ show c ++ "so that's it " ++ "You went as deep as " ++ show (getCount stk) ++" levels") ; return (e': stk) } stackBack :: Stack -> (Expression,Stack) stackBack [a] = (a,[a]) stackBack (a:as) = (a,as) stackBack [] = error "Nothing there" getCount :: Stack -> Int getCount stk = length stk

On 1 Dec 2010, at 19:34, John Moore wrote:
Hi , Havent used haskell in a while can someone explain just whats happening here. I know what it does, I just can't workout how it does it. Only need to explain how the red area works and I can work out the rest myself
The red block says... in order to figure out the value of two expressions added together, you must find out if you have values either side of the add sign... If you do, simply add them together. If you do not, evaluate one side or the other. It's a bit odd to use small-step semantics here though, the code could be much much neater if it used a denotational aproach: eval :: Expression -> Double eval (Val x) = x eval (Add x y) = (eval x) + (eval y) eval (Subtract x y) = (eval x) - (eval y) eval (Multiply x y) = (eval x) * (eval y) eval (Divide x y) = (eval x) / (eval y) Bob

Hi,
See inline comments
On Wed, Dec 1, 2010 at 9:34 PM, John Moore
<snip>
data Expression = Val Double | Add Expression Expression | Subtract Expression Expression | Multiply Expression Expression | Divide Expression Expression deriving Show
evalStep :: Expression -> Expression evalStep (Val x)= (Val x)
We can pattern match to a constructor. Val is a constructor for Expression, our evalStep receives an Expression as input and produces another one, presumably the evaluated input. In the above case, we know that if we try to evaluate a value (that's what Val stands for) we obtain the exact same value back.
evalStep (Add x y) = case x of (Val a) -> case y of (Val b) -> Val (a+b) left -> Add x (evalStep y) right -> Add (evalStep x)y <snip>
This case is a little more complicated. We want to do a single step of evaluation for expressions like 2+3 and 2+3+4 (expressed in our format, they would be Add (Double 2) (Double 3) and Add (Double 2) (Add (Double 3) (Double 4)) or Add (Add (Double 2) (Double 3)) (Double 4)). because the later case in ambiguous, we have two imbricated cases instead of only one. Each of the cases must look to see if we can narrow down x or y to (Val something) because this will make the evaluation progress. Hope it's useful, -- MM

On Wednesday 01 December 2010 20:34:31, John Moore wrote:
Hi , Havent used haskell in a while can someone explain just whats happening here. I know what it does, I just can't workout how it does it. Only need to explain how the red area works and I can work out the rest myself
Regards
John
module Rollback where
data Expression = Val Double
| Add Expression Expression | Subtract Expression Expression | Multiply Expression Expression | Divide Expression Expression
deriving Show demo1 = (Add(Multiply(Divide(Subtract(Val 25)(Val 5))(Val 10))(Val 7))(Val 30))
evalStep reduces the Expression one step unless it's a Val, which is irreducible.
evalStep :: Expression -> Expression evalStep (Val x)= (Val x)
Can't reduce a Val, so leave it as is.
evalStep (Add x y)
For a non-atomic Expression (here Add), look at the first component/left branch (an Expression is a binary tree with Vals at the leaves and arithmetic operations at the branch nodes).
= case x of (Val a) -> case y of
If the left branch is irreducible, look at the right
(Val b) -> Val (a+b)
If that is also irreducible, add the values and return the irreducible Expression
left -> Add x (evalStep y)
otherwise reduce the right branch one step (recur).
right -> Add (evalStep x)y
If the left branch is reducible, reduce it one step (recur), leaving the right unchanged.
evalStep (Subtract x y) = case x of (Val a) -> case y of (Val b) -> Val (a-b) left -> Subtract x (evalStep y) right -> Subtract (evalStep x)y evalStep (Multiply x y) = case x of (Val a) -> case y of (Val b) -> Val (a*b) left -> Multiply x (evalStep y) right -> Multiply (evalStep x)y
evalStep (Divide x y) = case x of (Val a) -> case y of (Val b) -> Val (a/b) left -> Divide x (evalStep y) right -> Divide (evalStep x)y type Stack = [Expression] evaluate :: Expression -> IO () evaluate exp = do stk <- evalWithStack exp [exp] putStrLn "End of Equation"
evalWithStack :: Expression -> Stack -> IO Stack -- Base case evalWithStack (Val a) stk = return stk -- Recursive case evalWithStack e stk = do putStrLn "Evaluating one more step" let e' = (evalStep e) putStrLn ("Result is "++(show e')) putStrLn "Do another step (y/n) or rollback (r)? :" c <- getLine case c of "y" -> evalWithStack e' (e':stk) "r" -> let (a,stk') = stackBack stk in evalWithStack a stk' "n" -> do { putStrLn ("Ok you said :" ++ show c ++ "so that's it " ++ "You went as deep as " ++ show (getCount stk) ++" levels") ; return (e': stk) }
stackBack :: Stack -> (Expression,Stack) stackBack [a] = (a,[a]) stackBack (a:as) = (a,as) stackBack [] = error "Nothing there"
getCount :: Stack -> Int getCount stk = length stk
participants (4)
-
Daniel Fischer
-
John Moore
-
Mihai Maruseac
-
Thomas Davie