PFP Laboratory 4

From Marek Běhálek Wiki
Revision as of 10:25, 29 September 2022 by Beh01 (talk | contribs) (Created page with "== List of lists == <div style="float: right"> 80px|link=https://youtu.be/voiTk64SaQM</div> Consider following type representing picture: <syntaxhigh...")
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search

List of lists

Video logo.png

Consider following type representing picture:

type Pic = [String]

If you want to print this picture you can use:

pp :: Pic -> IO ()
pp x = putStr (concat (map (++"\n") x))

Picture example:

pic :: Pic
pic = [ "....#....",
        "...###...",
        "..#.#.#..",
        ".#..#..#.",
        "....#....",
        "....#....",
        "....#####"]
*Main> pp pic
....#....
...###...
..#.#.#..
.#..#..#.
....#....
....#....
....#####

Create functions that:

  • Flips picture veriticaly and horizontally.
flipV :: Pic -> Pic
flipH :: Pic -> Pic
*Main> pp(flipV pic)
....#....
...###...
..#.#.#..
.#..#..#.
....#....
....#....
#####....
*Main> pp(flipH pic)
....#####
....#....
....#....
.#..#..#.
..#.#.#..
...###...
....#....
flipV :: Pic -> Pic
flipV = map reverse 

flipV' :: Pic -> Pic
flipV' xs = [reverse x|x<-xs]

flipH :: Pic -> Pic
flipH = reverse
Try it!
  • Place one picture above another.
above :: Pic -> Pic -> Pic
*Main> pp(above pic pic)
....#....
...###...
..#.#.#..
.#..#..#.
....#....
....#....
....#####
....#....
...###...
..#.#.#..
.#..#..#.
....#....
....#....
....#####
above :: Pic -> Pic -> Pic
above x y = x ++ y
Try it!
  • Place two pictures side by side (consider, that they have the same height).
sideBySide :: Pic -> Pic -> Pic
*Main> pp(sideBySide pic pic)
....#........#....
...###......###...
..#.#.#....#.#.#..
.#..#..#..#..#..#.
....#........#....
....#........#....
....#####....#####
sideBySide :: Pic -> Pic -> Pic
sideBySide xs ys = map (\(x,y) -> x ++ y)(zip xs ys) 

sideBySide':: Pic -> Pic -> Pic
sideBySide' (x:xs) (y:ys) = (x ++ y) : sideBySide' xs ys
sideBySide' _ _ = []

sideBySide'' :: Pic -> Pic -> Pic
sideBySide'' = zipWith (++)
Try it!
  • Rotate picture to the left and to the right.
Video logo.png
rotateR :: Pic -> Pic
rotateL :: Pic -> Pic
*Main> pp(rotateR pic)       
.......
...#...
....#..
.....#.
#######
#....#.
#...#..
#..#...
#......
*Main> pp(rotateL pic)
......#
...#..#
..#...#
.#....#
#######
.#.....
..#....
...#...
.......
toRow :: String -> Pic
toRow xs = map (\x -> [x]) xs -- [[x]|x<-xs]

rotateR :: Pic -> Pic
rotateR [x] = toRow x
rotateR (x:xs) = (rotateR xs) `sideBySide` (toRow x)

rotateR' :: Pic -> Pic
rotateR' x = foldl1 sideBySide (reverse (map toRow x))


rotateL :: Pic -> Pic
rotateL [x] = reverse(toRow x)
rotateL (x:xs) = reverse(toRow x) `sideBySide` (rotateL xs)

rotateL' :: Pic -> Pic
rotateL' x = foldl1 sideBySide (map (reverse.toRow) x)
Try it!

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!