diff --git a/docs/code/src/lec_10_10_23.hs b/docs/code/src/lec_10_10_23.hs index d07b050..92fded8 100644 --- a/docs/code/src/lec_10_10_23.hs +++ b/docs/code/src/lec_10_10_23.hs @@ -1,11 +1,39 @@ module Lec_10_10_23 where +import Data.Time.Format.ISO8601 (yearFormat) +-- >>> 1 + 2 +-- 3 + +-- >>> tails0 [1,2,3] -thing1 :: Integer -thing1 = 2 thing2 :: Double thing2 = 5.1 + 6.9 thing3 :: Bool thing3 = True + +thing4 :: Char +thing4 = 'c' + +ex0 = 5 > 4 + +thing1 :: Integer +thing1 = 2 * (5 + 6) + +-- quiz = if ex0 then thing1 else 20 + +-- Type_of_INPUT -> Type_of_OUTPUT + +quiz :: Bool -> Integer +quiz mickeymouse = if mickeymouse then thing1 else 0 + + +add3 :: Integer -> Integer -> Integer -> Integer +add3 x y z = x + y + z + +bob :: (Integer, Bool) +bob = (10 + 12, True) + +bob3 :: (Integer, Bool, Char) +bob3 = (10 + 12, True, 'd') diff --git a/docs/code/src/lec_10_12_23.hs b/docs/code/src/lec_10_12_23.hs new file mode 100644 index 0000000..464fc9f --- /dev/null +++ b/docs/code/src/lec_10_12_23.hs @@ -0,0 +1,263 @@ +module Lec_10_12_23 where +import Data.Time.Format.ISO8601 (yearFormat) + +-- >>> 1 + 2 +-- 3 + +-- >>> tails0 [1,2,3] + + +thing2 :: Double +thing2 = 5.1 + 6.9 + +thing3 :: Bool +thing3 = True + +thing4 :: Char +thing4 = 'c' + +ex0 = 5 > 4 + +thing1 :: Integer +thing1 = 2 * (5 + 6) + +-- quiz = if ex0 then thing1 else 20 + +-- Type_of_INPUT -> Type_of_OUTPUT + +quiz :: Bool -> Integer +quiz mickeymouse = if mickeymouse then thing1 else 0 + + +add3 :: Integer -> Integer -> Integer -> Integer +add3 x y z = x + y + z + +bob :: (Integer, Bool) +bob = (10 + 12, True) + +bob3 :: (Integer, Bool, Char) +bob3 = (10 + 12, True, 'd') + + +-- (e1, e2, e3) :: (T1, T2, T3) + +tup1 :: (Char, Integer) +tup1 = ('a', 5) + + +tup3 :: ((Int, Double), Bool) +tup3 = ((7, 5.2), True) + +blob :: Int +blob = 12 + + +getFst4 :: (a, b,c,d) -> a +getFst4 (x1, x2, x3, x4) = x1 + +getSnd4 :: (a, b, c, d) -> b +getSnd4 (x1, x2, x3, x4) = x2 + +-- >>> getSnd4 (1, "horse", 4.5, True) +-- "horse" + +tup2 :: (Char, Double, Int) +tup2 = ('a', 5.2, 7) + +snd3 :: (t1, t2, t3) -> t2 +snd3 (x1, x2, x3) = x2 + +{- + snd3 tup2 + => + snd3 ('a', 5.2, 7) + => + 5.2 + +-} + +chars :: [Char] +chars = ['a','b','c'] + -- ('a' : ('b' : ('c' : []))) + +bools :: [Bool] +bools = [True, True, False, False, True] + +l1 :: [Int] +l1 = [1,2,3] + +l2 :: [Int] +l2 = 1 : 2 : 3 : [] + + +-- >>> l1 == l2 +-- True + + + +-- oops = [True, False, 'c'] + +-- getNth :: Int -> [Stuff] -> Stuff +-- getNth l n = returns the 'nth' element of l + +{- +blobs :: [(Int, Int)] +blobs = [(1,2),(3,4),(5,6)] + +-} + + + +-- takes an input x and +-- returns a list with three copies of x + +copy3 :: t -> [t] +copy3 x = [x,x,x] + +-- >>> copy3 "cat" +-- ["cat","cat","cat"] + + +-- >>> clone 1 "dog" +-- ["dog"] + +-- >>> "wom" == ['w', 'o', 'm'] +-- True + +-- >>> getNth 100005 (clone (-1) "dog") +-- "dog" +{- + getNth 105 (clone (-1) "dog") + == + getNth 1 ("dog" : clone (-2) "dog") + == + getNth 1 ("dog" : "dog" : clone (-3) "dog") + == + getNth 1 ("dog" : "dog" : "dog" : clone (-4) "dog") + == + getNth 0 ( "dog" : "dog" : clone (-4) "dog") + == + "dog" + +-} + +-- (1) undefined? +-- (2) looping looping ... +-- (3) type error +-- (4) "dog" + +clone :: Int -> String -> [String] +clone 0 x = [] +clone n x = x : clone (n-1) x + +myHead :: [a] -> a +myHead [] = undefined +myHead (x:xs) = x + +-- getNth 0 (x:xs) = x +-- getNth n (x:xs) = getNth (n-1) xs + +-- getNth n (x:xs) = if n == 0 then x else getNth (n-1) xs + +getNth :: Int -> [a] -> a +getNth n (x:xs) + | n == 0 = x + | otherwise = getNth (n-1) xs + +-- >>> range 0 3 +-- [0,1,2,3] + +-- >>> sumList ['c', 'a', 't'] + +-- range 4 3 = [] +-- range 3 3 = 3 : [] +-- range 2 3 = 2 : 3 : [] +-- range 1 3 = 1 : 2 : 3 : [] +range :: Int -> Int -> [Int] +range lo hi + | lo > hi = [] + | otherwise = lo : range (lo+1) hi + + +mystery :: [a] -> Int +mystery [] = 0 +mystery (x:xs) = 1 + mystery xs + + +-- sumList :: Num a => [a] -> a +sumList [] = 0 +sumList (x:xs) = x + sumList xs + +{- mystery (10:20:30:[]) + = + 1 + mystery (20:30:[]) + = + 1 + (1 + mystery (30:[])) + = + 1 + (1 + (1 + mystery [])) + = + 1 + (1 + (1 + 0)) + = + 3 + +-} + +type Circle = (Double, Double, Double) + +circle0 :: Circle +circle0 = (0,0, 5) + +-- >>> circleArea circle0 +-- 78.53981633974483 + +circleArea :: Circle -> Double +circleArea (x, y, r) = pi * r * r + +type Cuboid = (Double, Double, Double) + +cub0 :: Cuboid +cub0 = (10, 20, 30) + +-- >>> cubVolume cub0 +-- 6000.0 + +cubVolume :: Cuboid -> Double +cubVolume (l, b, h) = l * b * h + +-- >>> cubVolume circle0 +-- 0.0 + +data CircleT = MkCircle Double Double Double + +cir1 :: CircleT +cir1 = c 0 0 5 + +-- >>> vol cir1 +-- Couldn't match expected type `CuboidT' with actual type `CircleT' +-- In the first argument of `vol', namely `cir1' +-- In the expression: vol cir1 +-- In an equation for `it_a3woO': it_a3woO = vol cir1 + +area :: CircleT -> Double +area (MkCircle x y r) = pi * r * r + +c :: Double -> Double -> Double -> CircleT +c x y r = MkCircle x y r + +data CuboidT = MkCuboid Double Double Double + +data CC = MkCC { len :: Double, br :: Double, ht :: Double } + +vol' :: CC -> Double +vol' c = len c * br c * ht c + +vol :: CuboidT -> Double +vol (MkCuboid l b h) = l * b * h + +cub1 :: CuboidT +cub1 = MkCuboid 10 20 30 + + +-- area' :: CircleT -> Double +-- area' a = case a of +-- MkCuboid x y r -> pi * r * r diff --git a/docs/code/src/lec_10_17_23.hs b/docs/code/src/lec_10_17_23.hs new file mode 100644 index 0000000..f7cdc5a --- /dev/null +++ b/docs/code/src/lec_10_17_23.hs @@ -0,0 +1,262 @@ +module Lec_10_17_23 where + +-- >>> 1 + 2 +-- 3 + +-- >>> tails0 [1,2,3] + + +thing2 :: Double +thing2 = 5.1 + 6.9 + +thing3 :: Bool +thing3 = True + +thing4 :: Char +thing4 = 'c' + +ex0 = 5 > 4 + +thing1 :: Integer +thing1 = 2 * (5 + 6) + +-- quiz = if ex0 then thing1 else 20 + +-- Type_of_INPUT -> Type_of_OUTPUT + +quiz :: Bool -> Integer +quiz mickeymouse = if mickeymouse then thing1 else 0 + + +add3 :: Integer -> Integer -> Integer -> Integer +add3 x y z = x + y + z + +bob :: (Integer, Bool) +bob = (10 + 12, True) + +bob3 :: (Integer, Bool, Char) +bob3 = (10 + 12, True, 'd') + + +-- (e1, e2, e3) :: (T1, T2, T3) + +tup1 :: (Char, Integer) +tup1 = ('a', 5) + + +tup3 :: ((Int, Double), Bool) +tup3 = ((7, 5.2), True) + +blob :: Int +blob = 12 + + +getFst4 :: (a, b,c,d) -> a +getFst4 (x1, x2, x3, x4) = x1 + +getSnd4 :: (a, b, c, d) -> b +getSnd4 (x1, x2, x3, x4) = x2 + +-- >>> getSnd4 (1, "horse", 4.5, True) +-- "horse" + +tup2 :: (Char, Double, Int) +tup2 = ('a', 5.2, 7) + +snd3 :: (t1, t2, t3) -> t2 +snd3 (x1, x2, x3) = x2 + +{- + snd3 tup2 + => + snd3 ('a', 5.2, 7) + => + 5.2 + +-} + +chars :: [Char] +chars = ['a','b','c'] + -- ('a' : ('b' : ('c' : []))) + +bools :: [Bool] +bools = [True, True, False, False, True] + +l1 :: [Int] +l1 = [1,2,3] + +l2 :: [Int] +l2 = 1 : 2 : 3 : [] + + +-- >>> l1 == l2 +-- True + + + +-- oops = [True, False, 'c'] + +-- getNth :: Int -> [Stuff] -> Stuff +-- getNth l n = returns the 'nth' element of l + +{- +blobs :: [(Int, Int)] +blobs = [(1,2),(3,4),(5,6)] + +-} + + + +-- takes an input x and +-- returns a list with three copies of x + +copy3 :: t -> [t] +copy3 x = [x,x,x] + +-- >>> copy3 "cat" +-- ["cat","cat","cat"] + + +-- >>> clone 1 "dog" +-- ["dog"] + +-- >>> "wom" == ['w', 'o', 'm'] +-- True + +-- >>> getNth 100005 (clone (-1) "dog") +-- "dog" +{- + getNth 105 (clone (-1) "dog") + == + getNth 1 ("dog" : clone (-2) "dog") + == + getNth 1 ("dog" : "dog" : clone (-3) "dog") + == + getNth 1 ("dog" : "dog" : "dog" : clone (-4) "dog") + == + getNth 0 ( "dog" : "dog" : clone (-4) "dog") + == + "dog" + +-} + +-- (1) undefined? +-- (2) looping looping ... +-- (3) type error +-- (4) "dog" + +clone :: Int -> String -> [String] +clone 0 x = [] +clone n x = x : clone (n-1) x + +myHead :: [a] -> a +myHead [] = undefined +myHead (x:xs) = x + +-- getNth 0 (x:xs) = x +-- getNth n (x:xs) = getNth (n-1) xs + +-- getNth n (x:xs) = if n == 0 then x else getNth (n-1) xs + +getNth :: Int -> [a] -> a +getNth n (x:xs) + | n == 0 = x + | otherwise = getNth (n-1) xs + +-- >>> range 0 3 +-- [0,1,2,3] + +-- >>> sumList ['c', 'a', 't'] + +-- range 4 3 = [] +-- range 3 3 = 3 : [] +-- range 2 3 = 2 : 3 : [] +-- range 1 3 = 1 : 2 : 3 : [] +range :: Int -> Int -> [Int] +range lo hi + | lo > hi = [] + | otherwise = lo : range (lo+1) hi + + +mystery :: [a] -> Int +mystery [] = 0 +mystery (x:xs) = 1 + mystery xs + + +-- sumList :: Num a => [a] -> a +sumList [] = 0 +sumList (x:xs) = x + sumList xs + +{- mystery (10:20:30:[]) + = + 1 + mystery (20:30:[]) + = + 1 + (1 + mystery (30:[])) + = + 1 + (1 + (1 + mystery [])) + = + 1 + (1 + (1 + 0)) + = + 3 + +-} + +type Circle = (Double, Double, Double) + +circle0 :: Circle +circle0 = (0,0, 5) + +-- >>> circleArea circle0 +-- 78.53981633974483 + +circleArea :: Circle -> Double +circleArea (x, y, r) = pi * r * r + +type Cuboid = (Double, Double, Double) + +cub0 :: Cuboid +cub0 = (10, 20, 30) + +-- >>> cubVolume cub0 +-- 6000.0 + +cubVolume :: Cuboid -> Double +cubVolume (l, b, h) = l * b * h + +-- >>> cubVolume circle0 +-- 0.0 + +data CircleT = MkCircle Double Double Double + +cir1 :: CircleT +cir1 = c 0 0 5 + +-- >>> vol cir1 +-- Couldn't match expected type `CuboidT' with actual type `CircleT' +-- In the first argument of `vol', namely `cir1' +-- In the expression: vol cir1 +-- In an equation for `it_a3woO': it_a3woO = vol cir1 + +area :: CircleT -> Double +area (MkCircle x y r) = pi * r * r + +c :: Double -> Double -> Double -> CircleT +c x y r = MkCircle x y r + +data CuboidT = MkCuboid Double Double Double + +data CC = MkCC { len :: Double, br :: Double, ht :: Double } + +vol' :: CC -> Double +vol' c = len c * br c * ht c + +vol :: CuboidT -> Double +vol (MkCuboid l b h) = l * b * h + +cub1 :: CuboidT +cub1 = MkCuboid 10 20 30 + + +-- area' :: CircleT -> Double +-- area' a = case a of +-- MkCuboid x y r -> pi * r * r diff --git a/docs/lectures.html b/docs/lectures.html index ac4c5af..22721b1 100644 --- a/docs/lectures.html +++ b/docs/lectures.html @@ -269,18 +269,28 @@

Topics, Notes and Code

10/10 Haskell Basics -html +[html][02-hs-basic] -code +code + + +10/12 +Algebraic Data Types +[html][03-hs-types] + +code + + +10/17 +Bottling patterns with HOFs +[html][07-patterns] + +code + + + + + + + + + + + + + + + + + + + + + + + + cse230 + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
+ +
+ +
+
+
+
+

Haskell Crash Course Part II

+ + + + +
+
+
+
+
+ + + + +
+
+
+
+

Recap: Haskell Crash Course II

+

+
    +
  • Core program element is an expression
  • +
  • Every valid expression has a type (determined at compile-time)
  • +
  • Every valid expression reduces to a value (computed at run-time)
  • +
+


+
+
+
+
+
+
+
+

+

Recap: Haskell

+

Basic values & operators

+
    +
  • Int, Bool, Char, Double
  • +
  • +, -, ==, /=
  • +
+

Execution / Function Calls

+
    +
  • Just substitute equals by equals
  • +
+

Producing Collections

+
    +
  • Pack data into tuples & lists
  • +
+

Consuming Collections

+
    +
  • Unpack data via pattern-matching
  • +
+


+
+
+
+
+
+
+
+

+

Next: Creating and Using New Data Types

+
    +
  1. type Synonyms: Naming existing types

  2. +
  3. data types: Creating new types

  4. +
+


+
+
+
+
+
+
+
+

+

Type Synonyms

+

Synonyms are just names (“aliases”) for existing types

+
    +
  • think typedef in C
  • +
+


+
+
+
+
+
+
+
+

+

A type to represent Circle

+

A tuple (x, y, r) is a circle with center at (x, y) and radius r

+
type Circle = (Double, Double, Double)
+


+
+
+
+
+
+
+
+
+

+

A type to represent Cuboid

+

A tuple (length, depth, height) is a cuboid

+
type Cuboid = (Double, Double, Double)
+

+


+
+
+
+
+
+
+
+

+

Using Type Synonyms

+

We can now use synonyms by creating values of the given types

+
circ0 :: Circle 
+circ0 = (0, 0, 100)  -- ^ circle at "origin" with radius 100
+
+cub0 :: Cuboid
+cub0 = (10, 20, 30)  -- ^ cuboid with length=10, depth=20, height=30 
+

And we can write functions over synonyms too

+
area :: Circle -> Double
+area (x, y, r) = pi * r * r  
+
+volume :: Cuboid -> Double
+volume (l, d, h) = l * d * h 
+

We should get this behavior

+
>>> area circ0 
+31415.926535897932
+
+>>> volume cub0
+6000
+


+
+
+
+
+
+
+
+

+

QUIZ

+

Suppose we have the definitions

+
type Circle = (Double, Double, Double)
+type Cuboid = (Double, Double, Double)
+
+circ0 :: Circle 
+circ0 = (0, 0, 100)  -- ^ circle at "origin" with radius 100
+
+cub0 :: Cuboid
+cub0 = (10, 20, 30)  -- ^ cuboid with length=10, depth=20, height=30 
+
+area :: Circle -> Double
+area (x, y, r) = pi * r * r  
+
+volume :: Cuboid -> Double
+volume (l, d, h) = l * d * h
+

What is the result of

+
>>> volume circ0
+

A. 0

+

B. Type error

+


+
+
+
+
+
+
+
+

+

Beware!

+

Type Synonyms

+
    +
  • Do not create new types

  • +
  • Just name existing types

  • +
+

And hence, synonyms

+
    +
  • Do not prevent confusing different values
  • +
+


+
+
+
+
+
+
+
+

+

Creating New Data Types

+

We can avoid mixing up by creating new data types

+
-- | A new type `CircleT` with constructor `MkCircle`
+data CircleT = MkCircle Double Double Double     
+
+-- | A new type `CuboidT` with constructor `MkCuboid`
+data CuboidT = MkCuboid Double Double Double
+

Constructors are the only way to create values

+
    +
  • MkCircle creates CircleT

  • +
  • MkCuboid creates CuboidT

  • +
+


+
+
+
+
+
+
+
+

+

QUIZ

+

Suppose we create a new type with a data definition

+
-- | A new type `CircleT` with constructor `MkCircle`
+data CircleT = MkCircle Double Double Double     
+

What is the type of the MkCircle constructor?

+

A. MkCircle :: CircleT

+

B. MkCircle :: Double -> CircleT

+

C. MkCircle :: Double -> Double -> CircleT

+

D. MkCircle :: Double -> Double -> Double -> CircleT

+

E. MkCircle :: (Double, Double, Double) -> CircleT

+


+
+
+
+
+
+
+
+

+

Constructing Data

+

Constructors let us build values of the new type

+
circ1 :: CircleT 
+circ1 = MkCircle 0 0 100  -- ^ circle at "origin" w/ radius 100
+
+cub1 :: Cuboid
+cub1 = MkCuboid 10 20 30  -- ^ cuboid w/ len=10, dep=20, ht=30 
+


+
+
+
+
+
+
+
+

+

QUIZ

+

Suppose we have the definitions

+
data CuboidT = MkCuboid Double Double Double     
+
+type Cuboid  = (Double, Double, Double)
+
+volume :: Cuboid -> Double
+volume (l, d, h) = l * d * h
+

What is the result of

+
>>> volume (MkCuboid 10 20 30)
+

A. 6000

+

B. Type error

+


+
+
+
+
+
+
+
+

+

Deconstructing Data

+

Constructors let us build values of new type … but how to use those values?

+

How can we implement a function

+
volume :: Cuboid -> Double
+volume c = ???
+

such that

+
>>> volume (MkCuboid 10 20 30)
+6000
+


+
+
+
+
+
+
+
+

+

Deconstructing Data by Pattern Matching

+

Haskell lets us deconstruct data via pattern-matching

+
volume :: Cuboid -> Double
+volume c = case c of
+             MkCuboid l d h -> l * d * h
+

case e of Ctor x y z -> e1 is read as as

+

IF +- e evaluates to a value that matches the pattern Ctor vx vy vz

+

THEN +- evaluate e1 after naming x := vx, y := vy, z := vz

+


+
+
+
+
+
+
+
+

+

Pattern matching on Function Inputs

+

Very common to do matching on function inputs

+
volume :: Cuboid -> Double
+volume c = case c of 
+            MkCuboid l d h -> l * d * h
+
+area :: Circle -> Double
+area a  = case a of 
+            MkCircle x y r -> pi * r * r
+

So Haskell allows a nicer syntax: patterns in the arguments

+
volume :: Cuboid -> Double
+volume (MkCuboid l d h) = l * d * h
+
+area :: Circle -> Double
+area (MkCircle x y r) = pi * r * r
+

Nice syntax plus the compiler saves us from mixing up values!

+


+
+
+
+
+
+
+
+

+

But … what if we need to mix up values?

+

Suppose I need to represent a list of shapes

+
    +
  • Some Circles
  • +
  • Some Cuboids
  • +
+

What is the problem with shapes as defined below?

+
shapes = [circ1, cub1]
+

Where we have defined

+
circ1 :: CircleT 
+circ1 = MkCircle 0 0 100  -- ^ circle at "origin" with radius 100
+
+cub1 :: Cuboid
+cub1 = MkCuboid 10 20 30  -- ^ cuboid with length=10, depth=20, height=30 
+


+
+
+
+
+
+
+
+

+

Problem: All list elements must have the same type

+

Solution???

+


+
+
+
+
+
+
+
+
+

+

QUIZ: Variant (aka Union) Types

+

Lets create a single type that can represent both kinds of shapes!

+


+
data Shape 
+  = MkCircle Double Double Double   -- ^ Circle at x, y with radius r 
+  | MkCuboid Double Double Double   -- ^ Cuboid with length, depth, height
+


+

What is the type of MkCircle 0 0 100 ?

+

A. Shape

+

B. Circle

+

C. (Double, Double, Double)

+


+
+
+
+
+

+

Each Data Constructor of Shape has a different type

+

When we define a data type like the below

+
data Shape 
+  = MkCircle  Double Double Double   -- ^ Circle at x, y with radius r 
+  | MkCuboid  Double Double Double   -- ^ Cuboid with length, depth, height
+

We get multiple constructors for Shape

+
MkCircle :: Double -> Double -> Double -> Shape
+MkCuboid :: Double -> Double -> Double -> Shape
+

Now we can create collections of Shape

+

Now we can define

+
circ2 :: Shape
+circ2 = MkCircle 0 0 100  -- ^ circle at "origin" with radius 100
+
+cub2 :: Shape 
+cub2 = MkCuboid 10 20 30  -- ^ cuboid with length=10, depth=20, height=30 
+

and then define collections of Shapes

+
shapes :: [Shape]
+shapes = [circ1, cub1]
+


+
+
+
+
+

+

EXERCISE

+

Lets define a type for 2D shapes

+
data Shape2D 
+  = MkRect Double Double -- ^ 'MkRect w h' is a rectangle with width 'w', height 'h'
+  | MkCirc Double        -- ^ 'MkCirc r' is a circle with radius 'r'
+  | MkPoly [Vertex]      -- ^ 'MkPoly [v1,...,vn]' is a polygon with vertices at 'v1...vn'
+
+type Vertex = (Double, Double)
+

Write a function to compute the area of a Shape2D

+
area2D :: Shape2D -> Double
+area2D s = ???
+

HINT

+
+Area of a polygon + +
+

You may want to use this helper that computes the area of a triangle at v1, v2, v3

+
areaTriangle :: Vertex -> Vertex -> Vertex -> Double
+areaTriangle v1 v2 v3 = sqrt (s * (s - s1) * (s - s2) * (s - s3))
+  where 
+      s  = (s1 + s2 + s3) / 2
+      s1 = distance v1 v2 
+      s2 = distance v2 v3
+      s3 = distance v3 v1
+
+distance :: Vertex -> Vertex -> Double
+distance (x1, y1) (x2, y2) = sqrt ((x2 - x1) ** 2 + (y2 - y1) ** 2)
+


+
+
+
+
+
+
+
+
+

+

Polymorphic Data Structures

+

Next, lets see polymorphic data types

+

which contain many kinds of values.

+


+
+
+
+
+
+
+
+
+

+

Recap: Data Types

+

Recall that Haskell allows you to create brand new data types

+
data Shape 
+  = MkRect  Double Double 
+  | MkPoly [(Double, Double)]
+


+
+
+
+
+
+
+
+
+

+

QUIZ

+

What is the type of MkRect ?

+
data Shape 
+  = MkRect  Double Double 
+  | MkPoly [(Double, Double)]
+

a. Shape

+

b. Double

+

c. Double -> Double -> Shape

+

d. (Double, Double) -> Shape

+

e. [(Double, Double)] -> Shape

+


+
+
+
+
+
+
+
+
+

+

Tagged Boxes

+

Values of this type are either two doubles tagged with Rectangle

+
>>> :type (Rectangle 4.5 1.2)
+(Rectangle 4.5 1.2) :: Shape
+

or a list of pairs of Double values tagged with Polygon

+
ghci> :type (Polygon [(1, 1), (2, 2), (3, 3)])
+(Polygon [(1, 1), (2, 2), (3, 3)]) :: Shape
+

Data values inside special Tagged Boxes

+
+Datatypes are Boxed-and-Tagged Values + +
+


+
+
+
+
+
+
+
+
+

+

Recursive Data Types

+

We can define datatypes recursively too

+
data IntList 
+  = INil                -- ^ empty list
+  | ICons Int IntList   -- ^ list with "hd" Int and "tl" IntList
+  deriving (Show)
+

(Ignore the bit about deriving for now.)

+


+
+
+
+
+
+
+
+
+

+

QUIZ

+
data IntList 
+  = INil                -- ^ empty list
+  | ICons Int IntList   -- ^ list with "hd" Int and "tl" IntList
+  deriving (Show)
+

What is the type of ICons ?

+

A. Int -> IntList -> List

+

B. IntList

+

C. Int -> IntList -> IntList

+

D. Int -> List -> IntList

+

E. IntList -> IntList

+


+
+
+
+
+
+
+
+
+

+

Constructing IntList

+

Can only build IntList via constructors.

+
>>> :type INil 
+INil:: IntList
+
+>>> :type ICons
+ICons :: Int -> IntList -> IntList
+


+
+
+
+
+
+
+
+
+

+

EXERCISE

+

Write down a representation of type IntList of the list of three numbers 1, 2 and 3.

+
list_1_2_3 :: IntList
+list_1_2_3 = ???
+

Hint Recursion means boxes within boxes

+
+Recursively Nested Boxes + +
+


+
+
+
+
+
+
+
+
+

+

Trees: Multiple Recursive Occurrences

+

We can represent Int trees like

+
data IntTree 
+   = ILeaf Int              -- ^ single "leaf" w/ an Int
+   | INode IntTree IntTree  -- ^ internal "node" w/ 2 sub-trees
+   deriving (Show)
+

A leaf is a box containing an Int tagged ILeaf e.g.

+
>>> it1  = ILeaf 1 
+>>> it2  = ILeaf 2
+

A node is a box containing two sub-trees tagged INode e.g. 

+
>>> itt   = INode (ILeaf 1) (ILeaf 2)
+>>> itt'  = INode itt itt
+>>> INode itt' itt'
+INode (INode (ILeaf 1) (ILeaf 2)) (INode (ILeaf 1) (ILeaf 2))
+


+
+
+
+
+
+
+
+
+

+

Multiple Branching Factors

+

e.g. 2-3 trees

+
data Int23T 
+  = ILeaf0 
+  | INode2 Int Int23T Int23T
+  | INode3 Int Int23T Int23T Int23T
+  deriving (Show)
+

An example value of type Int23T would be

+
i23t :: Int23T
+i23t = INode3 0 t t t
+  where t = INode2 1 ILeaf0 ILeaf0
+

which looks like

+
+Integer 2-3 Tree + +
+


+
+
+
+
+
+
+
+
+

+

Parameterized Types

+

We can define CharList or DoubleList +- versions of IntList for Char and Double as

+
data CharList 
+  = CNil
+  | CCons Char CharList
+  deriving (Show)
+
+data DoubleList 
+   = DNil
+   | DCons Char DoubleList
+   deriving (Show)
+


+
+
+
+
+
+
+
+
+

+

Don’t Repeat Yourself!

+

Don’t repeat definitions +- Instead reuse the list structure across all types!

+

Find abstract data patterns by

+
    +
  • identifying the different parts and
  • +
  • refactor those into parameters
  • +
+


+
+
+
+
+
+

+

A Refactored List

+

Here are the three types: What is common? What is different?

+
data IList = INil | ICons Int    IList
+
+data CList = CNil | CCons Char   CList
+
+data DList = DNil | DCons Double DList
+

Common: Nil/Cons structure

+

Different: type of each “head” element

+

Refactored using Type Parameter

+
data List a = Nil | Cons a  (List a)
+

Recover original types as instances of List

+
type IntList    = List Int
+type CharList   = List Char
+type DoubleList = List Double
+


+
+
+
+
+
+
+
+
+
+
+
+
+

+

Polymorphic Data has Polymorphic Constructors

+

Look at the types of the constructors

+
>>> :type Nil 
+Nil :: List a
+

That is, the Empty tag is a value of any kind of list, and

+
>>> :type Cons 
+Cons :: a -> List a -> List a
+

Cons takes an a and a List a and returns a List a.

+
cList :: List Char     -- list where 'a' = 'Char' 
+cList = Cons 'a' (Cons 'b' (Cons 'c' Nil))
+
+iList :: List Int      -- list where 'a' = 'Int' 
+iList = Cons 1 (Cons 2 (Cons 3 Nil))
+
+dList :: List Double   -- list where 'a' = 'Double' 
+dList = Cons 1.1 (Cons 2.2 (Cons 3.3 Nil))
+


+
+
+
+
+
+
+
+
+
+
+
+
+

+

Polymorphic Function over Polymorphic Data

+

Lets write the list length function

+
len :: List a -> Int
+len Nil         = 0
+len (Cons x xs) = 1 + len xs
+

len doesn’t care about the actual values in the list +- only “counts” the number of Cons constructors

+

Hence len :: List a -> Int

+
    +
  • we can call len on any kind of list.
  • +
+
>>> len [1.1, 2.2, 3.3, 4.4]    -- a := Double  
+4
+
+>>> len "mmm donuts!"           -- a := Char
+11
+
+>>> len [[1], [1,2], [1,2,3]]   -- a := ???
+3
+


+
+
+
+
+
+
+
+
+
+
+
+
+

+

Built-in Lists?

+

This is exactly how Haskell’s “built-in” lists are defined:

+
data [a]    = [] | (:) a [a]
+
+data List a = Nil | Cons a (List a)
+
    +
  • Nil is called []
  • +
  • Cons is called :
  • +
+

Many list manipulating functions e.g. in Data.List are polymorphic +- Can be reused across all kinds of lists.

+
(++) :: [a] -> [a] -> [a]
+head :: [a] -> a
+tail :: [a] -> [a]
+


+
+
+
+
+
+
+
+
+
+
+
+
+

+

Generalizing Other Data Types

+

Polymorphic trees

+
data Tree a 
+   = Leaf a 
+   | Node (Tree a) (Tree a) 
+   deriving (Show)
+

Polymorphic 2-3 trees

+
data Tree23 a 
+   = Leaf0  
+   | Node2 (Tree23 a) (Tree23 a)
+   | Node3 (Tree23 a) (Tree23 a) (Tree23 a)
+   deriving (Show)
+


+
+
+
+
+
+
+
+
+
+
+
+
+

+

Kinds

+

List a corresponds to lists of values of type a.

+

If a is the type parameter, then what is List?

+

A type-constructor that +- takes as input a type a +- returns as output the type List a

+

But wait, if List is a type-constructor then what is its “type”?

+
    +
  • A kind is the “type” of a type.
  • +
+
>>> :kind Int
+Int :: *
+>>> :kind Char
+Char :: *
+>>> :kind Bool
+Bool :: *
+

Thus, List is a function from any “type” to any other “type”, and so

+
>>> :kind List
+List :: * -> *
+


+
+
+
+
+
+
+
+
+
+
+
+
+

+

QUIZ

+

What is the kind of ->? That, is what does GHCi say if we type

+
>>> :kind (->) 
+

A. *

+

B. * -> *

+

C. * -> * -> *

+

We will not dwell too much on this now.

+

As you might imagine, they allow for all sorts of abstractions over data.

+

If interested, see this for more information about kinds.

+


+
+
+
+
+
+
+
+
+
+
+
+
+

+
+
+
+
+
+ +
+ + + + + + + + + + + + + + diff --git a/docs/lectures/04-hof.html b/docs/lectures/04-hof.html new file mode 100644 index 0000000..98dc8a5 --- /dev/null +++ b/docs/lectures/04-hof.html @@ -0,0 +1,974 @@ + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + cse230 + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
+ +
+ +
+
+
+
+

Bottling Computation Patterns

+ + + + +
+
+
+
+
+ + + + +
+
+
+
+

Polymorphism and Equational Abstractions are the Secret Sauce

+

Refactor arbitrary repeated code patterns …

+

… into precisely specified and reusable functions

+


+
+
+
+
+
+
+
+
+

+

EXERCISE: Iteration

+

Write a function that squares a list of Int

+
squares :: [Int] -> [Int]
+squares ns = ???
+

When you are done you should see

+
>>> squares [1,2,3,4,5]
+[1,4,9,16,25]
+


+
+
+
+
+
+
+
+
+

+

Pattern: Iteration

+

Next, lets write a function that converts a String to uppercase.

+
>>> shout "hello"
+"HELLO"
+

Recall that in Haskell, a String is just a [Char].

+
shout :: [Char] -> [Char]
+shout = ???
+

Hoogle to see how to transform an individual Char

+


+
+
+
+
+
+
+
+
+

+

Iteration

+

Common strategy: iteratively transform each element of input list

+

Like humans and monkeys, shout and squares share 93% of their DNA

+

Super common computation pattern!

+


+
+
+
+
+
+
+
+
+

+

Abstract Iteration “Pattern” into Function

+

Remember D.R.Y. (Don’t repeat yourself)

+

Step 1 Rename all variables to remove accidental differences

+
-- rename 'squares' to 'foo'
+foo []     = [] 
+foo (x:xs) = (x * x)     : foo xs
+
+-- rename 'shout' to 'foo'
+foo []     = [] 
+foo (x:xs) = (toUpper x) : foo xs
+

Step 2 Identify what is different

+
    +
  • In squares we transform x to x * x

  • +
  • In shout we transform x to Data.Char.toUpper x

  • +
+

Step 3 Make differences a parameter

+
    +
  • Make transform a parameter f
  • +
+
foo f []     = [] 
+foo f (x:xs) = (f x) : foo f xs
+

Done We have bottled the computation pattern as foo (aka map)

+
map f []     = [] 
+map f (x:xs) = (f x) : map f xs
+

map bottles the common pattern of iteratively transforming a list:

+
+Fairy In a Bottle + +
+


+
+
+
+
+
+
+
+
+

+

QUIZ

+

What is the type of map ?

+
map :: ???
+map f []     = [] 
+map f (x:xs) = (f x) : map f xs
+

A. (Int -> Int) -> [Int] -> [Int]

+

B. (a -> a) -> [a] -> [a]

+

C. [a] -> [b]

+

D. (a -> b) -> [a] -> [b]

+

E. (a -> b) -> [a] -> [a]

+


+
+
+
+
+
+
+
+
+

+

The type precisely describes map

+
>>> :type map
+map :: (a -> b) -> [a] -> [b]
+

That is, map takes two inputs

+
    +
  • a transformer of type a -> b
  • +
  • a list of values [a]
  • +
+

and it returns as output

+
    +
  • a list of values [b]
  • +
+

that can only come by applying f to each element of the input list.

+


+
+
+
+
+
+
+

+

Reusing the Pattern

+

Lets reuse the pattern by instantiating the transformer

+

shout

+
-- OLD with recursion
+shout :: [Char] -> [Char]
+shout []     = []
+shout (x:xs) = Char.toUpper x : shout xs
+
+-- NEW with map
+shout :: [Char] -> [Char]
+shout xs = map (???) xs
+

squares

+
-- OLD with recursion
+squares :: [Int] -> [Int]
+squares []     = []
+squares (x:xs) = (x * x) : squares xs
+
+-- NEW with map
+squares :: [Int] -> [Int]
+squares xs = map (???) xs 
+


+
+
+
+
+
+
+

+

EXERCISE

+

Suppose I have the following type

+
type Score = (Int, Int) -- pair of scores for Hw0, Hw1
+

Use map to write a function

+
total :: [Score] -> [Int]
+total xs = map (???) xs 
+

such that

+
>>> total [(10, 20), (15, 5), (21, 22), (14, 16)]
+[30, 20, 43, 30]
+


+
+
+
+
+
+
+
+
+
+
+
+
+
+
+

+

The Case of the Missing Parameter

+

Note that we can write shout like this

+
shout :: [Char] -> [Char]
+shout = map Char.toUpper
+

Huh. No parameters? Can someone explain?

+


+
+
+
+
+
+
+
+
+
+

+

The Case of the Missing Parameter

+

In Haskell, the following all mean the same thing

+

Suppose we define a function

+
add :: Int -> Int -> Int
+add x y = x + y
+

Now the following all mean the same thing

+
plus x y = add x y
+plus x   = add x
+plus     = add 
+

Why? equational reasoning! In general

+
foo x = e x
+
+-- is equivalent to 
+
+foo   = e
+

as long as x doesn’t appear in e.

+

Thus, to save some typing, we omit the extra parameter.

+


+
+
+
+
+
+
+
+
+
+

+

Pattern: Reduction

+

Computation patterns are everywhere lets revisit our old sumList

+
sumList :: [Int] -> Int
+sumList []     = 0
+sumList (x:xs) = x + sumList xs
+

Next, a function that concatenates the Strings in a list

+
catList :: [String] -> String
+catList []     = "" 
+catList (x:xs) = x ++ (catList xs)
+


+
+
+
+
+
+
+
+
+
+

+

Lets spot the pattern!

+

Step 1 Rename

+
foo []     = 0
+foo (x:xs) = x + foo xs
+
+foo []     = "" 
+foo (x:xs) = x ++ foo xs
+

Step 2 Identify what is different

+
    +
  1. ???

  2. +
  3. ???

  4. +
+

Step 3 Make differences a parameter

+
foo p1 p2 []     = ???
+foo p1 p2 (x:xs) = ???
+


+
+
+
+
+
+
+
+
+
+

+

EXERCISE: Reduction/Folding

+

This pattern is commonly called reducing or folding

+
foldr :: (a -> b -> b) -> b -> [a] -> b
+foldr op base []     = base
+foldr op base (x:xs) = op x (foldr op base xs)
+

Can you figure out how sumList and catList are just instances of foldr?

+
sumList :: [Int] -> Int
+sumList xs = foldr (?op) (?base) xs
+
+catList :: [String] -> String 
+catList xs = foldr (?op) (?base) xs
+


+
+
+
+
+
+
+
+
+
+

+

Executing foldr

+

To develop some intuition about foldr lets “run” it a few times by hand.

+
foldr op b (a1:a2:a3:a4:[])
+==> 
+  a1 `op` (foldr op b (a2:a3:a4:[]))
+==> 
+  a1 `op` (a2 `op` (foldr op b (a3:a4:[])))
+==> 
+  a1 `op` (a2 `op` (a3 `op` (foldr op b (a4:[]))))
+==> 
+  a1 `op` (a2 `op` (a3 `op` (a4 `op` foldr op b [])))
+==> 
+  a1 `op` (a2 `op` (a3 `op` (a4 `op` b)))
+

Look how it mirrors the structure of lists!

+
    +
  • (:) is replaced by op
  • +
  • [] is replaced by base
  • +
+

So

+
foldr (+) 0 (x1:x2:x3:x4:[])
+==> x1 + (x2 + (x3 + (x4 + 0))
+


+
+
+
+
+
+
+
+
+
+

+

Typing foldr

+
foldr :: (a -> b -> b) -> b -> [a] -> b
+foldr op base []     = base
+foldr op base (x:xs) = op x (foldr op base xs)
+

foldr takes as input

+
    +
  • a reducer function of type a -> b -> b
  • +
  • a base value of type b
  • +
  • a list of values to reduce [a]
  • +
+

and returns as output

+
    +
  • a reduced value b
  • +
+


+
+
+
+
+
+
+
+
+
+

+

QUIZ

+

Recall the function to compute the len of a list

+
len :: [a] -> Int
+len []     = 0
+len (x:xs) = 1 + len xs
+

Which of these is a valid implementation of Len

+

A. len = foldr (\n -> n + 1) 0

+

B. len = foldr (\n m -> n + m) 0

+

C. len = foldr (\_ n -> n + 1) 0

+

D. len = foldr (\x xs -> 1 + len xs) 0

+

E. All of the above

+


+
+
+
+
+
+
+
+
+
+

+

The Missing Parameter Revisited

+

We wrote foldr as

+
foldr :: (a -> b -> b) -> b -> [a] -> b
+foldr op base []     = base
+foldr op base (x:xs) = op x (foldr op base xs)
+

but can also write this

+
foldr :: (a -> b -> b) -> b -> [a] -> b
+foldr op base  = go 
+  where
+     go []     = base
+     go (x:xs) = op x (go xs)
+

Can someone explain where the xs went missing ?

+


+
+
+
+
+
+
+
+
+
+

+

Trees

+

Recall the Tree a type from last time

+
data Tree a 
+  = Leaf 
+  | Node a (Tree a) (Tree a)
+

For example here’s a tree

+
tree2 :: Tree Int
+tree2 = Node 2 Leaf Leaf
+
+tree3 :: Tree Int
+tree3 = Node 3 Leaf Leaf
+
+tree123 :: Tree Int
+tree123 = Node 1 tree2 tree3 
+


+
+
+
+
+
+
+
+
+
+

+

Some Functions on Trees

+

Lets write a function to compute the height of a tree

+
height :: Tree a -> Int
+height Leaf         = 0
+height (Node x l r) = 1 + max (height l) (height l)
+

Here’s another to sum the leaves of a tree:

+
sumTree :: Tree Int -> Int
+sumTree Leaf         = ???
+sumTree (Node x l r) = ???
+

Gathers all the elements that occur as leaves of the tree:

+
toList :: Tree a -> [a] 
+toList Leaf         = ??? 
+toList (Node x l r) = ???
+

Lets give it a whirl

+
>>> height tree123
+2 
+
+>>> sumTree tree123
+6
+
+>>> toList tree123
+[1,2,3]
+


+
+
+
+
+
+
+
+
+
+

+

Pattern: Tree Fold

+

Can you spot the pattern? Those three functions are almost the same!

+

Step 1: Rename to maximize similarity

+
-- height
+foo Leaf         = 0
+foo (Node x l r) = 1 + max (foo l) (foo l)
+
+-- sumTree
+foo Leaf         = 0
+foo (Node x l r) = foo l + foo r
+
+-- toList
+foo Leaf         = []
+foo (Node x l r) = x : foo l ++ foo r
+

Step 2: Identify the differences

+
    +
  1. ???
  2. +
  3. ???
  4. +
+

Step 3 Make differences a parameter

+
foo p1 p2 Leaf         = ???
+foo p1 p2 (Node x l r) = ???
+


+
+
+
+
+
+
+
+
+
+

+

Pattern: Folding on Trees

+
tFold op b Leaf         = b 
+tFold op b (Node x l r) = op x (tFold op b l) (tFold op b r)
+

Lets try to work out the type of tFold!

+
tFold :: t_op -> t_b -> Tree a -> t_out
+


+
+
+
+
+
+
+
+

+

QUIZ

+

Suppose that t :: Tree Int.

+

What does tFold (\x y z -> y + z) 1 t return?

+

a. 0

+

b. the largest element in the tree t

+

c. the height of the tree t

+

d. the number-of-leaves of the tree t

+

e. type error

+


+
+
+
+
+
+
+
+

+

EXERCISE

+

Write a function to compute the largest element in a tree +or 0 if tree is empty or all negative.

+
treeMax :: Tree Int -> Int
+treeMax t = tFold f b t 
+  where 
+     f    = ??? 
+     b    = ???
+


+
+
+
+
+
+
+
+

+

Map over Trees

+

We can also write a tmap equivalent of map for Trees

+
treeMap :: (a -> b) -> Tree a -> Tree b
+treeMap f (Leaf x)   = Leaf (f x)
+treeMap f (Node l r) = Node (treeMap f l) (treeMap f r)
+

which gives

+
>>> treeMap (\n -> n * n) tree123     -- square all elements of tree
+Node 1 (Node 4 Leaf Leaf) (Node 9 Leaf Leaf)
+


+
+
+
+
+
+
+
+

+

EXERCISE

+

Recursion is HARD TO READ do we really have to use it ?

+

Lets rewrite treeMap using tFold !

+
treeMap :: (a -> b) -> Tree a -> Tree b
+treeMap f t = tFold op base t 
+  where 
+     op     = ??? 
+     base   = ??? 
+

When you are done, we should get

+
>>> animals = Node "cow" (Node "piglet" Leaf Leaf) (Leaf "hippo" Leaf Leaf)
+>>> treeMap reverse animals
+Node "woc" (Node "telgip" Leaf Leaf) (Leaf "oppih" Leaf Leaf)
+


+
+
+
+
+
+
+
+

+

Examples: foldDir

+
data Dir a 
+  = Fil a             -- ^ A single file named `a`
+  | Sub a [Dir a]     -- ^ A sub-directory name `a` with contents `[Dir a]`
+
+data DirElem a 
+  = SubDir a          -- ^ A single Sub-Directory named `a`
+  | File a            -- ^ A single File named `a` 
+
+foldDir :: ([a] -> r -> DirElem a -> r) -> r -> Dir a -> r
+foldDir f r0 dir = go [] r0 dir  
+  where
+      go stk r (Fil a)    = f stk r (File a)  
+      go stk r (Sub a ds) = L.foldl' (go stk') r' ds                          
+        where 
+            r'   = f stk r (SubDir a)  
+            stk' = a:stk
+

foldDir takes as input

+
    +
  • an accumulator f of type [a] -> r -> DirElem a -> r

    +
      +
    • takes as input the path [a] , the current result r, the next DirElem [a]

    • +
    • and returns as output the new result r

    • +
  • +
  • an initial value of the result r0 and

  • +
  • directory to fold over dir

  • +
+

And returns the result of running the accumulator over the whole dir.

+


+
+
+
+
+
+
+
+

+

Examples: Spotting Patterns In The “Real” World

+

These patterns in “toy” functions appear regularly in “real” code

+
    +
  1. Start with beginner’s version riddled with explicit recursion.

  2. +
  3. Spot the patterns and eliminate recursion using HOFs.

  4. +
  5. Finally refactor the code to “swizzle” and “unswizzle” without duplication.

  6. +
+

Try it yourself

+
    +
  • Rewrite the code that swizzles Char to use the Map k v type in Data.Map
  • +
+


+
+
+
+
+
+
+
+

+

Which is more readable? HOFs or Recursion

+

At first, recursive versions of shout and squares are easier to follow

+
    +
  • fold takes a bit of getting used to!
  • +
+

With practice, the higher-order versions become easier

+
    +
  • only have to understand specific operations

  • +
  • recursion is lower-level & have to see “loop” structure

  • +
  • worse, potential for making silly off-by-one errors

  • +
+

Indeed, HOFs were the basis of map/reduce and the big-data revolution

+
    +
  • Can parallelize and distribute computation patterns just once

  • +
  • Reuse across hundreds or thousands of instances!

  • +
+
+
+
+
+
+ +
+ + + + + + + + + + + + + + diff --git a/docs/lectures/05-io.html b/docs/lectures/05-io.html new file mode 100644 index 0000000..b4434cd --- /dev/null +++ b/docs/lectures/05-io.html @@ -0,0 +1,917 @@ + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + cse230 + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
+ +
+ +
+
+
+
+

Haskell Crash Course Part III

+ + + + +
+
+
+
+
+ + + + +
+
+
+
+

Writing Applications

+

Lets write the classic “Hello world!” program.

+

For example, in Python you may write:

+
def main():
+    print "hello, world!"
+
+main()
+

and then you can run it:

+
$ python hello.py
+hello world!
+


+
+
+
+
+
+
+
+
+
+

+

Haskell is a Pure language.

+

Not a value judgment, but a precise technical statement:

+

The “Immutability Principle”:

+
    +
  • A function must always return the same output for a given input

  • +
  • A function’s behavior should never change

  • +
+


+
+
+
+
+
+
+

+

No Side Effects

+

+

Haskell’s most radical idea: expression =*> value

+
    +
  • When you evaluate an expression you get a value and

  • +
  • Nothing else happens

  • +
+

Specifically, evaluation must not have an side effects

+
    +
  • change a global variable or

  • +
  • print to screen or

  • +
  • read a file or

  • +
  • send an email or

  • +
  • launch a missile.

  • +
+


+
+
+
+
+
+
+

+

But… how to write “Hello, world!”

+

But, we want to …

+
    +
  • print to screen
  • +
  • read a file
  • +
  • send an email
  • +
+

Thankfully, you can do all the above via a very clever idea: Recipe

+


+
+
+
+
+
+
+

+

Recipes

+

This analogy is due to Joachim Brietner

+

Haskell has a special type called IO – which you can think of as Recipe

+
type Recipe a = IO a
+

A value of type Recipe a

+
    +
  • is a description of a computation that can have side-effects

  • +
  • which when executed performs some effectful I/O operations

  • +
  • to produce a value of type a.

  • +
+


+
+
+
+
+
+
+

+

Recipes have No Side Effects

+

A value of type Recipe a is

+
    +
  • A description of a computation that can have side-effects
  • +
+
+Cake vs. Recipe + +
+

(L) chocolate cake, (R) a sequence of instructions on how to make a cake.

+

They are different (Hint: only one of them is delicious.)

+

Merely having a Recipe Cake has no effects! The recipe

+
    +
  • Does not make your oven hot

  • +
  • Does not make your your floor dirty

  • +
+


+
+
+
+
+
+
+

+

Only One Way to Execute Recipes

+

Haskell looks for a special value

+
main :: Recipe ()
+

The value associated with main is handed to the runtime system and executed

+
+Baker Aker + +
+

The Haskell runtime is a master chef who is the only one allowed to cook!

+


+
+
+
+
+
+
+

+

How to write an App in Haskell

+

Make a Recipe () that is handed off to the master chef main.

+
    +
  • main can be arbitrarily complicated

  • +
  • composed of smaller sub-recipes

  • +
+


+
+
+
+
+
+
+

+

A Recipe to Print to Screen

+
putStrLn :: String -> Recipe ()
+

The function putStrLn

+
    +
  • takes as input a String
  • +
  • returns as output a Recipe ()
  • +
+

putStrLn msg is a Recipe () +- when executed prints out msg on the screen.

+
main :: Recipe ()
+main = putStrLn "Hello, world!"
+

… and we can compile and run it

+
$ ghc --make hello.hs
+$ ./hello
+Hello, world!
+


+
+
+
+
+
+
+

+

QUIZ: How to Print Multiple Things?

+

Suppose I want to print two things e.g.

+
$ ghc --make hello.hs
+$ ./hello2
+Hello! 
+World!
+

Can we try to compile and run this:

+
main = (putStrLn "Hello!", putStrLn "World!")
+

A. Yes!

+

B. No, there is a type error!

+

C. No, it compiles but produces a different result!

+


+
+
+
+
+
+
+

+

A Collection of Recipes

+

Is just … a collection of Recipes!

+
recPair :: (Recipe (), Recipe ())
+recPair = (putStrLn "Hello!", putStrLn "World!")
+
+recList :: [Recipe ()]
+recList = [putStrLn "Hello!", putStrLn "World!"]
+

… we need a way to combine recipes!

+


+
+
+
+
+
+
+

+

Combining? Just do it!

+

We can combine many recipes into a single one using a do block

+
foo :: Recipe a3
+foo = do r1       -- r1 :: Recipe a1
+         r2       -- r2 :: Recipe a2
+         r3       -- r3 :: Recipe a3
+

(or if you prefer curly braces to indentation)

+
foo = do { r1;    -- r1 :: Recipe a1
+           r2;    -- r2 :: Recipe a2
+           r3     -- r3 :: Recipe a3
+         }
+

The do block combines sub-recipes r1, r2 and r3 into a new recipe that

+
    +
  • Will execute each sub-recipe in sequence and
  • +
  • Return the value of type a3 produced by the last recipe r3
  • +
+


+
+
+
+
+
+
+

+

Combining? Just do it!

+

So we can write

+
main = do putStrLn "Hello!"
+          putStrLn "World!"
+

or if you prefer

+
main = do { putStrLn "Hello!"; 
+            putStrLn "World!" 
+          }
+


+
+
+
+
+
+
+

+

EXERCISE: Combining Many Recipes

+

Write a function called sequence that

+
    +
  • Takes a non-empty list of recipes [r1,...,rn] as input and
  • +
  • Returns a single recipe equivalent to do {r1; ...; rn}
  • +
+
sequence :: [Recipe a] -> Recipe a
+sequence rs = ???
+

When you are done you should see the following behavior

+
-- Hello.hs
+
+main = sequence [putStrLn "Hello!", putStrLn "World!"] 
+

and then

+
$ ghc --make Hello.hs
+$ ./hello
+Hello! 
+World!
+


+
+
+
+
+
+
+

+

Using the Results of (Sub-) Recipes

+

Suppose we want a function that asks for the user’s name

+
$ ./hello
+What is your name? 
+Ranjit             # <<<<< user enters
+Hello Ranjit!
+

We can use the following sub-recipes

+
-- | read and return a line from stdin as String
+getLine  :: Recipe String       
+
+-- take a string s, return a recipe that prints  s 
+putStrLn :: String -> Recipe () 
+

But how to

+
    +
  • Combine the two sub-recipes while
  • +
  • Passing the result of the first sub-recipe to the second.
  • +
+


+
+
+
+
+
+
+

+

Naming Recipe Results via “Assignment”

+

You can write

+
x <- recipe
+

to name the result of executing recipe

+
    +
  • x can be used to refer to the result in later code
  • +
+


+
+
+
+
+
+
+

+

Naming Recipe Results via “Assignment”

+

Lets, write a function that asks for the user’s name

+
main = ask 
+
+ask :: Recipe ()
+ask = do name <- getLine; 
+         putStrLn ("Hello " ++ name ++ "!")
+

Which produces the desired result

+
$ ./hello
+What is your name? 
+Ranjit             # user enters
+Hello Ranjit!
+


+
+
+
+
+
+
+

+

EXERCISE

+

Modify the above code so that the program repeatedly +asks for the users’s name until they provide a non-empty string.

+
-- Hello.hs 
+
+main = repeatAsk
+
+repeatAsk :: Recipe ()
+repeatAsk = _fill_this_in
+
+
+isEmpty :: String -> Bool
+isEmpty s = length s == 0
+

When you are done you should get the following behavior

+
$ ghc --make hello.hs
+
+$ ./hello
+What is your name? 
+# user hits return
+What is your name? 
+# user hits return
+What is your name? 
+# user hits return
+What is your name? 
+Ranjit  # user enters
+Hello Ranjit!
+


+
+
+
+
+
+
+

+

EXERCISE

+

Modify your code to also print out a count in the prompt

+
$ ghc --make hello.hs
+
+$ ./hello
+(0) What is your name? 
+                          # user hits return
+(1) What is your name? 
+                          # user hits return
+(2) What is your name? 
+                          # user hits return
+(3) What is your name? 
+Ranjit                    # user enters
+Hello Ranjit!
+

That’s all about IO

+

You should be able to implement build from Directory.hs

+

Using these library functions imported at the top of the file

+
import System.FilePath   (takeDirectory, takeFileName, (</>))
+import System.Directory  (doesFileExist, listDirectory)
+

The functions are

+
    +
  • takeDirectory
  • +
  • takeFileName
  • +
  • (</>)
  • +
  • doesFileExist
  • +
  • listDirectory
  • +
+

hoogle the documentation to learn about how to use them.

+


+
+
+
+
+
+
+

+ +
+
+
+
+
+ +
+ + + + + + + + + + + + + + diff --git a/docs/static/code/cse230-code.cabal b/docs/static/code/cse230-code.cabal index 49a942d..5284e74 100644 --- a/docs/static/code/cse230-code.cabal +++ b/docs/static/code/cse230-code.cabal @@ -1,4 +1,4 @@ -cabal-version: 2.4 +cabal-version: 2.4 name: cse230-code version: 0.1.0.0 @@ -19,6 +19,8 @@ source-repository head library other-modules: Lec_10_10_23 + Lec_10_12_23 + Lec_10_17_23 hs-source-dirs: src build-depends: @@ -44,7 +46,7 @@ executable stm Paths_cse230_code hs-source-dirs: src - ghc-options: -threaded -rtsopts -with-rtsopts=-N + ghc-options: -Wall -threaded -rtsopts -with-rtsopts=-N build-depends: HTTP , QuickCheck diff --git a/lectures.md b/lectures.md index 54ab0ba..6e52963 100644 --- a/lectures.md +++ b/lectures.md @@ -14,12 +14,10 @@ The lectures will be recorded and available on [CANVAS](https://canvas.ucsd.edu/ | *9/28* | Intro | [pdf][00-intro] | | | | | Lambda Calculus | [html][01-lambda] | | | | *10/10* | Haskell Basics | [html][02-hs-basic] | | [code][code-10-10] +| *10/12* | Algebraic Data Types | [html][03-hs-types] | | [code][code-10-12] | +| *10/17* | Bottling patterns with HOFs | [html][07-patterns] | | [code][code-10-17] |