Algebraic Data Types

Lecture #3
Play with the lecture code on replit!
Complete the associated in-class exercises.

Table of Contents
module Lecture3 where

(Note: no strange imports this time. Plain old ghci should load this file just fine.)

1 Representing Data

What is a type? One way to think of it is as a set of values, structured in a way that helps you represent your data.

Haskell helps in two ways:

  1. guaranteeing what type of values you will work with at any program point. You know what type of data you are operating on; so, you know what you can do with that data.

  2. providing ways to assemble your own types to represent data of interest to you.

1.1 Enumerations

For example, your data may simply indicate one of a handful of cases:

Let’s start with the last one. To represent data like this in our programs, we might choose:

data TimsSize = ExtraSmall
              | Small
              | Medium
              | Large
              | ExtraLarge
  deriving (Eq, Show)

Note: the deriving statement at the end automatically makes it so we can compare TimsSizes for equality and convert them to Strings with show.

Now, we have a new type TimsSize. There are exactly five values in that type:

These values are called data constructors because they construct a value (data) of our new type.

The true/false and greater/equal/less scenarios are not so different. Here are GHC’s definitions for Bool and Ordering:

data Bool = True 
          | False 

data Ordering = LT
              | EQ 
              | GT

(Remember that qsort’s type was Ord a => [a] -> [a]? To be an instance of Ord, a type a needs to define compare :: a -> a -> Ordering, which in turn enables comparisons like <, >=, and so on.)

We can use data constructors for constructing values and for pattern-matching. Here’s two such functions; let’s finish the second together:

-- | Evaluates to the size in ounces of the given @TimsSize@
sizeOz :: TimsSize -> Int 
sizeOz ExtraSmall = 8
sizeOz Small = 10
sizeOz Medium = 14
sizeOz Large = 20
sizeOz ExtraLarge = 24

-- | Upsize the given size to be one larger (or the same for the largest size).
upsize :: TimsSize -> TimsSize
upsize _ = undefined

Your turn to work on creating a new data type and a function to operate on it.

(Next two exercises (on species)!)

1.2 Assembling Data from Other Data

Your data may also be made up of other data. For example, maybe you want to represent a person’s vaccination declaration status:

-- | Either declared whether they are vaccinated (True or False)
-- or not yet declared.
data VaccinationDeclaration = Declared Bool 
                            | Undeclared
  deriving (Eq, Show)

This creates two data constructors. One (Undeclared) is also a value of type VaccinationDeclaration as above. The other Declared is also a function. You give it a Bool, and it constructs a VaccinationDeclaration value.

We can use both data constructors in pattern matching. Let’s write a function to determine if a person needs to undergo regular testing given their vaccination status:

needsTesting :: VaccinationDeclaration -> Bool 
needsTesting = undefined

Or perhaps you want to store your ukulele’s four strings’ current tuning frequencies:

-- | Tuning in Hz (rounded) for the G, C, E, and A strings.
data UkeTune = UkeTune Int Int Int Int
  deriving (Eq, Show)

The type and the single data constructor share a name here. That’s allowed and even common, if sometimes confusing!

Here’s a handy UkeTune value:

perfectTune :: UkeTune
perfectTune = UkeTune 392 262 330 440

We can (of course?) assemble larger types out of our smaller types. The following isn’t particularly meaningful, but it shows how we can use everything we’ve learned so far as we create new types, including our own types, lists, tuples, and even functions. The first case just has a UkeTune value. The second has a list of VaccinationDeclarationes. The third has a tuple of two UkeTunes and a function from VaccinationDeclaration to UkeTune. (Which.. seems like an interesting function.)

data UkunationStatus = Uke UkeTune
                     | Vaxes [VaccinationDeclaration]
                     | ThisIsJustSilly (UkeTune, UkeTune) (VaccinationDeclaration -> UkeTune) 

Let’s do some exercises defining and using this sort of algebraic data type in Haskell!

(Next two exercises (on water supply)!)

1.3 Recursive Data Types

Where things get really exciting is when we define recursive data types. Imagine we want to represent a list of Doubles, but we expect most entries to be zeroes, and we don’t want to waste a bunch of space representing those. We might define a sparse list type.

A sparse list will represent a list of Doubles. It will have three cases:

Here is our data type:

-- | A well-defined SparseList has a positive number of zeroes
-- in SkipAndRest cases. If a zero or negative value appears,
-- treat it as as a 1.
data SparseList = Empty
                | OneAndRest Double SparseList
                | SkipAndRest Int SparseList
  deriving (Eq, Show)

Here’s are some lists:

emptyL, twoEltL, manyEltL :: [Double]
emptyL = []
twoEltL = [0, 0]
manyEltL = [2.5, 1, 0, 3.2, 0, 0, 0, 1]

Here they are as sparse lists:

slEmpty, slTwoElt, slManyElt :: SparseList
slEmpty = Empty
slTwoElt = SkipAndRest 2 Empty
slManyElt = OneAndRest 2.5 (OneAndRest 1 (SkipAndRest 1 (OneAndRest 3.2 (SkipAndRest 3 (OneAndRest 1 Empty)))))

1.4 Functions on Recursive Data Types

Let’s practice defining some recursive functions on sparse lists:

-- | Produces a regular list from a sparse list.
toList :: SparseList -> [Double]
toList = undefined
-- | Produces a sparse list, but doesn't bother compressing
-- sequences of zeroes down. Just uses a SkipAndRest 1 for them.
fromList :: [Double] -> SparseList
fromList = undefined

It would be great to define a toList that produced a nice, compact SparseList. It should never have a OneAndRest 0 ..., and it should never have two consecutive SparseList x (SparseList y ...), since those could just be replaced by SparseList (x+y) ....

Two exercises: Define the helper functions below. Think in cases! slZeroToSkip is easier than slCompact. You may assume that all SkipAndRest counts are positive.

slNormalize :: SparseList -> SparseList
slNormalize sl = slCompact (slZeroToSkip sl)
slZeroToSkip :: SparseList -> SparseList
slZeroToSkip = undefined
-- Hint: look at that nested SparseList above with the x and then y.
-- You CAN use something nested like that as a pattern!
-- But.. what happens if you give it three SparseLists in a row?
-- Can some creative recursion help?
slCompact :: SparseList -> SparseList
slCompact = undefined

There is one last exercise for you to practice defining a recursive data type.

P.S. You will want to know about case expressions and where clauses at some point. Now’s a good time!