module Calc where import ExprT import Parser -- Exercise 1 eval :: ExprT -> Integer eval (Lit n) = n eval (Add l r) = eval l + eval r eval (Mul l r) = eval l * eval r -- Exercise 2 evalStr :: String -> Maybe Integer evalStr s = case parseExp Lit Add Mul s of Nothing -> Nothing Just t -> Just (eval t) -- Exercise 3 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 reify :: ExprT -> ExprT reify = id -- Exercise 4 instance Expr Integer where lit x = x add l r = eval (Add (Lit l) (Lit r)) mul l r = eval (Mul (Lit l) (Lit r)) instance Expr Bool where lit x | x <= 0 = False | otherwise = True add = (||) mul = (&&) newtype MinMax = MinMax Integer deriving (Eq, Show) newtype Mod7 = Mod7 Integer deriving (Eq, Show) instance Expr MinMax where lit = MinMax add (MinMax l) (MinMax r) = MinMax (max l r) mul (MinMax l) (MinMax r) = MinMax (min l r) instance Expr Mod7 where lit x = Mod7 (mod x 7) add (Mod7 l) (Mod7 r) = Mod7 (mod (l + r) 7) mul (Mod7 l) (Mod7 r) = Mod7 (mod (l * r) 7) testExp :: Expr a => Maybe a testExp = parseExp lit add mul "(3 * -4) + 5" testInteger = testExp :: Maybe Integer testBool = testExp :: Maybe Bool testMM = testExp :: Maybe MinMax testSat = testExp :: Maybe Mod7