]> git.rkrishnan.org Git - yorgey.git/blobdiff - hw5/Calc.hs
hw12: exercise 4
[yorgey.git] / hw5 / Calc.hs
index 46f782018c617ae69a0bb440c77af5a753d1cbed..0e50663d146dfbd2b852ac09c83dd24f8976a48d 100644 (file)
+{-# LANGUAGE TypeSynonymInstances #-}
+{-# LANGUAGE FlexibleInstances #-}
 {-# OPTIONS_GHC -Wall #-}
 
+
 module Calc where
 
-import ExprT
+import qualified ExprT as E
 import Parser
+import StackVM
+import qualified Data.Map as M
 
-eval :: ExprT -> Integer
 
 -- exercise 1
-eval (Lit n) = n
-eval (Add e1 e2) = eval e1 + eval e2
-eval (Mul e1 e2) = eval e1 * eval e2
+eval :: E.ExprT -> Integer
+eval (E.Lit n) = n
+eval (E.Add e1 e2) = eval e1 + eval e2
+eval (E.Mul e1 e2) = eval e1 * eval e2
 
 -- exercise 2
 evalStr :: String -> Maybe Integer
 -- evalStr s = case (parseExp Lit Add Mul s) of
 --               Just e -> Just (eval e)
 --              Nothing -> Nothing
-evalStr s = fmap eval (parseExp Lit Add Mul s)
+evalStr s = fmap eval (parseExp E.Lit E.Add E.Mul s)
 
 class Expr a where
   lit :: Integer -> a
   add :: a -> a -> a
   mul :: a -> a -> a
 
-instance Expr ExprT where
-  lit = Lit
-  add = Add
-  mul = Mul
+instance Expr E.ExprT where
+  lit = E.Lit
+  add = E.Add
+  mul = E.Mul
+
+reify :: E.ExprT -> E.ExprT
+reify = id
+
+instance Expr Integer where
+  lit = id
+  add = (+)
+  mul = (-)
+
+instance Expr Bool where
+  lit x | x <= 0 = False
+        | otherwise = True
+  add = (||)
+  mul = (&&)
+
+newtype MinMax = MinMax Integer deriving (Show, Eq)
+
+instance Expr MinMax where
+  lit = MinMax
+  add (MinMax x) (MinMax y) = MinMax (max x y)
+  mul (MinMax x) (MinMax y) = MinMax (min x y)
+
+newtype Mod7 = Mod7 Integer deriving (Show, Eq)
+
+instance Expr Mod7 where
+  lit x = Mod7 (x `mod` 7)
+  add (Mod7 x) (Mod7 y) = Mod7 ((x+y) `mod` 7)
+  mul (Mod7 x) (Mod7 y) = Mod7 ((x*y) `mod` 7)
+
+-- exercise 5
+instance Expr Program where
+  lit x = [PushI x]
+  add x y = x ++ y ++ [Add]
+  mul x y = x ++ y ++ [Mul]
+
+compile :: String -> Maybe Program
+compile = parseExp lit add mul
+
+-- exercise 6
+data VarExprT = VarLit Integer
+              | VarAdd VarExprT VarExprT
+              | VarMul VarExprT VarExprT
+              | Var String
+  deriving (Show, Eq)
+
+class HasVars a where
+  var :: String -> a
+
+instance Expr VarExprT where
+  lit = VarLit
+  add = VarAdd
+  mul = VarMul
+
+instance HasVars VarExprT where
+  var = Var
+
+instance HasVars  (M.Map String Integer -> Maybe Integer) where
+  var x = M.lookup x
+
+instance Expr (M.Map String Integer -> Maybe Integer) where
+  lit x = \_ -> Just x
+  add x y = \m -> case (x m) of
+                    Just xv -> case (y m) of
+                                 Just yv -> Just (xv + yv)
+                                 Nothing -> Nothing
+                    Nothing -> Nothing
+  mul x y = \m -> case (x m) of
+                    Just xv -> case (y m) of
+                                 Just yv -> Just (xv * yv)
+                                 Nothing -> Nothing
+                    Nothing -> Nothing
+
+withVars :: [(String, Integer)]
+         -> (M.Map String Integer -> Maybe Integer)
+         -> Maybe Integer
+withVars vs exp = exp $ M.fromList vs