FP Laboratory 9

From Marek Běhálek Wiki
Jump to navigation Jump to search
This page contains changes which are not marked for translation.

User defined data types and type classes

Video logo.png

Consider following representation of expressions

data Expr = Num Int
          | Add Expr Expr
          | Sub Expr Expr
          | Mul Expr Expr
          | Div Expr Expr
          | Var Char
	  deriving (Eq)
  • Create function eval that evaluates expresions.
Video logo.png
eval :: Expr -> Int
*Main> eval (Add (Num 1) (Num 2))
3
*Main> eval (Mul (Add (Num 1) (Num 2)) (Num 3))
9
eval :: Expr -> Int
eval (Num x) = x
eval (Add l r) =  (eval l) + (eval r)
eval (Sub l r) =  (eval l) - (eval r)
eval (Mul l r) =  (eval l) * (eval r)
eval (Div l r) =  (eval l) `div` (eval r)
Try it!
  • Create function showExpr that shows expression as a String.
Video logo.png
showExpr :: Expr -> String
*Main> showExpr (Add (Num 1) (Num 2))
"1+2"
*Main> showExpr (Mul (Add (Num 1) (Num 2)) (Num 3))
"(1+2)*3"
*Main> showExpr (Mul (Add (Num 1) (Mul (Num 2) (Var 'x'))) (Mul (Num 3) (Var 'x')))
"(1+2*x)*3*x"
*Main> showExpr (Mul (Num 2) (Mul (Var 'x') (Var 'x')))                            
"2*x*x"
showExpr :: Expr -> String
showExpr expr = showExpr' expr NoOp

data Operation = Hi | HiDiv | Lo | LoSub | NoOp deriving (Eq)

showExpr' :: Expr -> Operation -> String
showExpr' (Num x) _ = show x
showExpr' (Var x) _ =  [x]
showExpr' (Add l r) op = let
  x = showExpr' l Lo ++"+"++showExpr' r Lo
  in if op == Hi || op == HiDiv || op==LoSub 
     then "(" ++ x ++")"
     else x
showExpr' (Sub l r) op = let
  x = showExpr' l Lo ++"-"++showExpr' r LoSub
  in if op == Hi || op == HiDiv || op==LoSub 
     then "(" ++ x ++")"
     else x     
showExpr' (Mul l r) op = let
  x = showExpr' l Hi ++"*"++showExpr' r Hi
  in if op == HiDiv
     then "(" ++ x ++")"
     else x
showExpr' (Div l r) op = let
  x = showExpr' l Hi ++"/"++showExpr' r HiDiv
  in if op == HiDiv
     then "(" ++ x ++")"
     else x
Try it!
  • Extend class Show to be usable with our expressions.
Video logo.png
*Main> Add (Num 1) (Num 2)
"1+2"
*Main> Mul (Add (Num 1) (Num 2)) (Num 3)
"(1+2)*3"
*Main> Mul (Add (Num 1) (Mul (Num 2) (Var 'x'))) (Mul (Num 3) (Var 'x'))
"(1+2*x)*3*x"
*Main> Mul (Num 2) (Mul (Var 'x') (Var 'x'))           
"2*x*x"
instance (Show Expr) where
  show = showExpr
Try it!
  • Create function derivation representing symbolic derivation of a given expression.
deriv :: Expr -> Char -> Expr
*Main> deriv (Add (Num 1) (Num 2)) 'x'
0+0
*Main> deriv (Mul (Num 2) (Mul (Var 'x') (Var 'x'))) 'x'
0*x*x+2*(1*x+x*1)
*Main> deriv (Mul (Num 2) (Mul (Var 'x') (Var 'x'))) 'x'
0*x*x+2*(1*x+x*1)
deriv :: Expr-> Char -> Expr
deriv (Num _) _ = (Num 0)     
deriv (Var x) y | x==y = (Num 1)
                | otherwise = (Num 0)
deriv (Add l r) x = Add (deriv l x) (deriv r x)                
deriv (Sub l r) x = Sub (deriv l x) (deriv r x)
deriv (Mul l r) x = Add (Mul (deriv l x) r) (Mul l (deriv r x))
deriv (Div l r) x = 
   Div
    (Sub (Mul (deriv l x) r) (Mul l (deriv r x)))
    (Mul r r)
Try it!

Additional exercises

  • Define a function that counts the number of operators in an expression.
size :: Expr -> Int
*Main> size (Add (Num 1) (Num 2))
1
*Main> size (Mul (Add (Num 1) (Mul (Num 2) (Var 'x'))) (Mul (Num 3) (Var 'x')))
4
  • It is possible to extend the type Expr so that it contains conditional expressions. Consider the following representation of boolean expressions:
data BExpr = Val Bool
        | And BExpr BExpr
        | Not BExpr 
        | Equal Expr Expr
        | Greater Expr Expr
    deriving (Eq)
  • Define a function that evaluates boolean expressions.
bEval :: BExpr -> Bool
*Main> bEval (And (Equal (Num 4) (Num 5)) (Greater (Num 5) (Num 1))) 
False
*Main> bEval (And (Equal (Add (Num 1) (Num 4)) (Num 5)) (Greater (Num 5) (Num 1)))
True
  • Define a function that shows a boolean expression as a string. Use symbols "/\","!","=",">" for logical conjunction, negation, equality, and comparison respectively.
showBExpr :: BExpr -> String
*Main> showBExpr((And (Val True) (Not (Greater (Num 5) (Num 1)))))
"(True/\\!(5>1))"
*Main> showBExpr(And (Equal (Add (Num 1) (Num 4)) (Num 5)) (Greater (Num 5) (Num 1)))
"(((1+4)=5)/\\(5>1))"
  • Extend class Show to be usable with our boolean expressions.
*Main> (And (Val True) (Not (Greater (Num 5) (Num 1))))
(True/\!(5>1))
*Main> And (Equal (Add (Num 1) (Num 4)) (Num 5)) (Greater (Num 5) (Num 1))
(((1+4)=5)/\(5>1))
  • Extend the Expr type with the If-Then-Else statement as follows:
data Expr = Num Int
          | Add Expr Expr
          | Sub Expr Expr
          | Mul Expr Expr
          | Div Expr Expr
          | If BExpr Expr Expr
 deriving (Eq)
  • Modify function eval to evaluate If-Then-Else statements.
*Main> eval (If (Greater (Num 5)(Num 1)) (Num 5) (Num 6))     
5
*Main> eval (Mul (If (Greater (Add (Num 0) (Num 1))(Num 1)) (Num 5) (Num 6)) (Num 7))
42
  • Modify function showExpr to show If-Then-Else statements as a string.
*Main> showExpr (If (Greater (Num 5)(Num 1)) (Num 5) (Num 6)) 
"(If (5>1) then 5 else 6)"
*Main> showExpr (Mul (If (Greater (Add (Num 0) (Num 1))(Num 1)) (Num 5) (Num 6)) (Num 7))
"((If ((0+1)>1) then 5 else 6)*7)"