[Haskell-beginners] let expression

John Moore john.moore54 at gmail.com
Wed Feb 10 15:16:31 EST 2010


Hi All,
         Trying to get this to work, keeps telling me there a parse error on
right in the let expression. Can anyone see where the problem is and be able
to explain it to me.

import Maybe
data Expression = Val Double
               | Add Expression Expression
               | Subtract Expression Expression
               | Multiply Expression Expression
               | Divide Expression Expression
        | Var String
        | Let String Expression Expression
        deriving Show
demo1 = (Add(Multiply(Divide(Subtract(Val 25)(Val 5))(Val 10))(Val 7))(Val
30))
type Dict =[(String,Expression)]
emptyDict :: Dict
emptyDict = []
addEntry :: String->Expression ->Dict -> Dict
addEntry n e d = (n,e): d
lookupEntry :: String -> Dict -> Maybe Expression
lookupEntry n [] = Nothing
lookupEntry n (x:xs) = if (n == k)
   then (Just v)
                else lookupEntry n xs
   where (k,v) = x
evalStep :: Dict -> Expression ->  Expression
evalStep d(Val x)=   (Val x)

evalStep d(Add x y)
  = case x of
      (Val a) -> case y of
                   (Val b) ->  Val (a+b)
                   left -> Add x (evalStep d y)
      right -> Add (evalStep d x)y
evalStep d(Subtract x y)
  = case x of
      (Val a) -> case y of
                   (Val b) -> Val (a-b)
                   left -> Subtract x (evalStep d y)
      right -> Subtract (evalStep d x)y
evalStep d(Multiply x y)
  = case x of
      (Val a) -> case y of
                   (Val b) -> Val (a*b)
                   left -> Multiply x (evalStep d y)
      right -> Multiply (evalStep d x)y
evalStep d (Divide x y)
  = case x of
      (Val a) -> case y of
                   (Val b) -> Val (a/b)
                   left -> Divide x (evalStep d y)
      right -> Divide (evalStep d x)y
evalStep d (Let n e1 e2)
   = case e1 of
       (Val a) -> case e2 of
  (Val b)-> Val (Let e1 e2)
         left -> Let e1 (evalStep d e2)
      right -> Let (evalStep d e1) e2


evaluate :: Dict-> [Expression] -> Expression -> IO()
evaluate d(x:xs) e = do
     putStrLn (show e)
     putStrLn "Do another step (y/n) or rollback (r)? :"
     c <- getLine
     case c of
       "y" -> let e'= (evalStep d e)in evaluate d (e:x:xs) e'-- build up
history

       "r" ->  case (x:xs) of
  (x:xs)-> evaluate d xs x
  []-> do { putStrLn "Empty"
   ;evaluate d(x:xs) e
  }
       "n"  ->  putStrLn $ "Ok you said no :" ++ c


John
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20100210/512a91cc/attachment.html


More information about the Beginners mailing list