Module 02: Algebraic data types and pattern matching

XXX FOR NEXT TIME: build in some places for reporting out

For this module, the person whose birthday is latest in the year should start out as the driver. The person sitting to their left (wrapping around if necessary) is the reporter. The module will indicate points when you should rotate roles (each role rotates left).

Remember, you should make sure that everyone on your team is understanding everything, regardless of their prior amount of Haskell experience.

> {-# LANGUAGE GADTs #-}

The above {-# LANGUAGE #-} thingy turns on a Haskell language extension called “GADTs”, which stands for “Generalized Algebraic Data Types”. You need not worry about what that means for now; it will enable us to use some nice syntax.

Enumerations

> data Color where
>   Red   :: Color
>   Green :: Color
>   Blue  :: Color
>   deriving Show
> 
> colorChar :: Color -> Char
> colorChar Red   = 'r'
> colorChar Green = 'g'
> colorChar Blue  = 'b'
> 
> isRed :: Color -> Bool
> isRed Red   = True
> isRed Green = False
> isRed Blue  = False

More general ADTs

ROTATE ROLES

> data MaybeInteger where
>   No  :: MaybeInteger
>   Yes :: Integer -> MaybeInteger
>   deriving Show
> 
> mi1, mi2 :: MaybeInteger
> mi1 = No
> mi2 = Yes 6
> 
> unMaybe :: MaybeInteger -> Integer
> unMaybe No = 0
> unMaybe (Yes 6) = 249
> unMaybe (Yes n) = n
> 
> data Record where
>   NameAndAge      :: String -> Integer -> Record
>   AddressAndEmail :: String -> String -> Record
>   TopSecret       :: Integer -> Bool -> (Char, Integer) -> Record
>   deriving Show
> 
> record1, record2, record3 :: Record
> record1 = NameAndAge "McGrew" 6
> record2 = AddressAndEmail "55 Ridge Avenue" "mcgrew@mcgrew.com"
> record3 = TopSecret 17 False ('x',10)
> 
> recordAge :: Record -> Integer
> recordAge (NameAndAge _ age)          = age
> recordAge (AddressAndEmail _ _)       = 0
> recordAge (TopSecret age True _)      = age
> recordAge (TopSecret _ False (_,age)) = age
> 
> recordAge2 :: Record -> Integer
> recordAge2 r =
>   case r of
>     (NameAndAge _ age)          -> age
>     (AddressAndEmail _ _)       -> 0
>     (TopSecret age True _)      -> age
>     (TopSecret _ False (_,age)) -> age
> 
> foo :: Record -> Integer
> foo r = 3 * (case r of
>                 NameAndAge _ age -> age
>                 _                -> 7
>             )
>         + 2

You should write your function definition below, using bird tracks (greater-than signs) in front of your code, just like the rest of the code in this module. Be sure to :reload the module in GHCi to test your code.

Recursive ADTs

ROTATE ROLES

> data Nat where
>   Z :: Nat
>   S :: Nat -> Nat
>   deriving Show
> 
> three :: Nat
> three = S (S (S Z))
> 
> natToInteger :: Nat -> Integer
> natToInteger Z     = 0
> natToInteger (S n) = 1 + natToInteger n
> 
> natPlus :: Nat -> Nat -> Nat
> natPlus Z     n = n
> natPlus (S m) n = S (natPlus m n)
> 
> data IntList where
>   Empty :: IntList
>   Cons  :: Integer -> IntList -> IntList
>   deriving Show
> 
> intListLength :: IntList -> Integer
> intListLength Empty       = 0
> intListLength (Cons _ xs) = 1 + intListLength xs

Feedback