]> git.rkrishnan.org Git - yorgey.git/commitdiff
hw5: exercise 5
authorRamakrishnan Muthukrishnan <ram@rkrishnan.org>
Sun, 21 Dec 2014 15:58:07 +0000 (21:28 +0530)
committerRamakrishnan Muthukrishnan <ram@rkrishnan.org>
Sun, 21 Dec 2014 15:58:07 +0000 (21:28 +0530)
hw5/Calc.hs

index 3d8dd9bca09076a422a4fa66a890568997151402..edc01791b0cad0bc69cb1dadc31805c5b9d336c3 100644 (file)
@@ -1,35 +1,40 @@
+{-# LANGUAGE TypeSynonymInstances #-}
+{-# LANGUAGE FlexibleInstances #-}
 {-# OPTIONS_GHC -Wall #-}
 
+
 module Calc where
 
-import ExprT
+import qualified ExprT as E
 import Parser
+import StackVM
+
 
-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 :: ExprT -> ExprT
+reify :: E.ExprT -> E.ExprT
 reify = id
 
 instance Expr Integer where
@@ -56,3 +61,12 @@ 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