
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