Polymorphism and Higher-Order Functions
Complete the associated in-class exercises.
module Lecture4 where
import Data.Char (toUpper)
1 Abstracting Behaviour and Data
Let’s revisit SparseList
, our data type for representing lists of Double
s without explicitly representing potentially long sequences of zeroes.
1.1 Review of SparseList
There’s nothing new in this section.
-- | 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:
mightySparseL :: [Double]
emptyL, twoEltL, manyEltL,= []
emptyL = [0, 0]
twoEltL = [2.5, 1, 0, 3.2, 0, 0, 0, 1]
manyEltL = [0, 0, 0, 0, 0, 0, 0, 0, 0, 0] mightySparseL
Here they are as sparse lists:
slMightySparse :: SparseList
slEmpty, slTwoElt, slManyElt,= Empty
slEmpty = SkipAndRest 2 Empty
slTwoElt = OneAndRest 2.5
slManyElt OneAndRest 1
(SkipAndRest 1
(OneAndRest 3.2
(SkipAndRest 3
(OneAndRest 1 Empty)))))
(= SkipAndRest 10 Empty slMightySparse
Here are functions to convert to/from sparse lists:
-- | Produces a regular list from a sparse list.
toList :: SparseList -> [Double]
Empty = []
toList OneAndRest d rest) = d : toList rest
toList (SkipAndRest n rest)
toList (| n <= 1 = 0 : toList rest
| otherwise = 0 : toList (SkipAndRest (n-1) rest)
-- | Produces a sparse list, but doesn't bother compressing
-- sequences of zeroes down. Just uses a SkipAndRest 1 for them.
fromList :: [Double] -> SparseList
= Empty
fromList [] :ds) | d == 0 = SkipAndRest 1 (fromList ds)
fromList (d| otherwise = OneAndRest d (fromList ds)
-- Skip past the definitions of slZeroToSkip and slCompact to slNormalize!
-- Adding normalization of i < 1 here.
slZeroToSkip :: SparseList -> SparseList
Empty = Empty
slZeroToSkip OneAndRest 0.0 rest) = SkipAndRest 1 (slZeroToSkip rest)
slZeroToSkip (OneAndRest d rest) = OneAndRest d (slZeroToSkip rest)
slZeroToSkip (SkipAndRest i rest) = SkipAndRest (max i 1) (slZeroToSkip rest) slZeroToSkip (
slCompact :: SparseList -> SparseList
Empty = Empty
slCompact SkipAndRest x (SkipAndRest y rest)) = slCompact (SkipAndRest (x + y) rest)
slCompact (SkipAndRest i rest) = SkipAndRest i (slCompact rest)
slCompact (OneAndRest d rest) = OneAndRest d (slCompact rest) slCompact (
1.2 A Couple of Concrete Functions
Now, let’s define two functions: slDouble
doubles each element of a sparse list, slSquare
squares each element of a sparse list. So, for example, doubling our sparse list that represents [2.5, 1, 0, 3.2, 0, 0, 0, 1]
should result in [5.0, 2, 0, 6.4, 0, 0, 0, 2]
, whereas squaring it should result in [6.25, 1, 0, 10.24, 0, 0, 0, 1]
. (Actually, because of the way Double
arithmetic works, the result is off by a little bit, as in the test below.)
-- >>> slDouble Empty
-- Empty
-- >>> toList (slDouble slManyElt)
-- [5.0,2.0,0.0,6.4,0.0,0.0,0.0,2.0]
slDouble :: SparseList -> SparseList
= undefined slDouble _
-- >>> slSquare Empty
-- Empty
-- >>> toList (slSquare slManyElt)
-- [6.25,1.0,0.0,10.240000000000002,0.0,0.0,0.0,1.0]
slSquare :: SparseList -> SparseList
= undefined slSquare _
1.3 Abstracting Behaviour
Those two functions are very similar. Let’s abstract out the common behaviour into a function. Basically, where the functions have common behavior, we’ll keep it. Where they differ, we’ll build that difference into a function.
Think carefully as you go as well to see if we’re missing anything!
slMap :: SparseList -> SparseList
= undefined slMap _
Now, let’s redefine slDouble
and slSquare
:
slDouble' :: SparseList -> SparseList
= undefined slDouble'
slSquare' :: SparseList -> SparseList
= undefined slSquare'
1.4 Catching All the Cases
What about this function:
-- | Adds 1 to each element of a SparseList.
add1SL :: SparseList -> SparseList
= undefined add1SL _
Will our slMap
function handle it correctly? If not, what do we need to change?
Let’s go change it together. Then, I’ll have you define slFilter
as an exercise.
(Two exercises!)
1.5 The Benefits of Abstraction
We can abstract out many common behaviours. Perhaps the most common are applying a function to each element of the list (mapping) and selecting only the elements of the list that pass some test (filtering, like grabbing only the positive elements or all the integer-valued ones).
Doing so:
- makes it easier for us to create new functions,
- focuses designers’ attention on making a small set of powerful abstract functions correct, efficient, and useful,
- refocuses our attention on the high-level task we want to solve rather than the details of its implementation, and
- makes it easier to adjust for different priorities in the future (like parallelism) .
Limiting side effects also makes it less likely that implementation details will “leak through” our abstractions.
Haskell supports a lot of abstraction!
2 Parametric Polymorphism
Our SparseList
s really only work on numbers.1
But for regular lists, map
and filter
are defined in the Haskell Prelude for any type of list at all.
map :: (a -> b) -> [a] -> [b]
: takes a function and applies it to each element of a list, collecting the results into a new list. Its type is alsomap :: (a -> b) -> ([a] -> [b])
: taking a function on elements and turning it into a function on lists!filter :: (a -> Bool) -> [a] -> [a]
: takes a test (Boolean-valued function) and a list and produces only the list elements that pass the test.
Let’s rewrite some of our assignment functions to use abstract functions instead!
(Two exercises!)
3 Function Composition: Putting a Period on slNormalize
There is a less obvious pattern that we may want to abstract. Think back to slNormalize
. We defined it as:
slNormalize :: SparseList -> SparseList
= slCompact (slZeroToSkip sl) slNormalize sl
In other words, slNormalize
is:
- Convert zeroes to skips
- Compact chains of skips
Let’s look at another function with a similar pattern:
-- | @getInitial name@ gets the first initial of a non-empty
-- name: the uppercase letter at the start of the name.
getInitial :: [Char] -> Char
= toUpper (head name) getInitial name
Getting the initial from a name is:
- Get the first letter of the name
- Convert it to uppercase
So, these both happen in steps, but what’s the pattern to abstract here? Maybe we can see it more clearly with one more function:
-- Not necessarily an efficient way to do this, but it works! 😁
getFirstDigit :: Integer -> Integer
= read (return (head (show (abs n)))) getFirstDigit n
Getting the first digit of a number can work like:
- Take its absolute value
- Convert the result to a string
- Take the first letter of the string
- Convert that back to a string.2
- Convert that string to a number.
In each of these cases, we “chain” together functions. So, we’re interested in abstracting out the operation that puts f
and g
together so that their combination applied to x
acts just like applying one and then the next: f (g x)
.
Let’s call that “function composition” operation dot .
and figure out its type. It takes two functions and produces a new function:
(.) :: (? -> ?) -> (? -> ?) -> (? -> ?)
. g) x = f (g x) (f
(I intentionally wrote parentheses around the last piece of the type above to emphasize that we commonly think of (f . g)
as an expression that returns a function. Because of the associativity of ->
those last parentheses aren’t necessary and the exercise leaves them out.)
(Exercise)
Now, let’s rewrite the functions above using .
:
-- Chain slCompact onto slZeroToSkip:
slNormalize :: SparseList -> SparseList
= slCompact . slZeroToSkip slNormalize
Is this definition easier to write? Clearer? Does it communicate the idea of chaining a series of functions together to build a new function?
You try rewriting getInitial
and getFirstDigit
!3
(Two exercises for now and two more to work on your own as practice!)
3.1 Polymorphic Types
It’s not just functions that we might abstract, but types as well! In fact, a list is already a polymorphic type. Its data constructors ([]
or “empty” and :
or “cons”) can operate on any element type.
Let’s define our own. Imagine you wanted to redesign Haskell so that it maintained the “provenance” of all the values it computed: where they came from. You could create a data type that attached a textual description to each value, maybe allowing for both “commented values” and “plain values” that don’t yet have provenance attached.
For Double
s only, that might look like:
-- | A "provenance value" for doubles, in two cases:
-- a commented value with a string comment describing provenance, and
-- a plain value with no provenance.
data ProValD = CVD Double String
| PVD Double
But we want to be able to represent any Haskell type. That means we don’t need a type like ProValD
, we need something like a function that takes a type of value we want to represent and constructs a version of it that carries provenance around: a type constructor:
-- | A "provenance value", in two cases:
-- a commented value with a string comment describing provenance,
-- and a plain value with no provenance.
data ProVal a = CV a String
| PV a
This time, the first argument of each of our constructors can be any type!
The type ProVal Double
behaves like ProValD
above. When we define a polymorphic type, we list out its arguments (lowercase identifiers) and use them on the right to describe data constructors just like any type.
Here are some example values:
plainInt :: ProVal Int
= PV 7
plainInt
commentedDouble :: ProVal Double
= CV 3.1415926525 "From IHOP"
commentedDouble
proListOfString :: ProVal [String]
= CV ["Four", "score", "and", "seven"] "Being raised in the US"
proListOfString
proProInt :: ProVal (ProVal Int)
= CV (CV 42 "The answer") "What do you get when you multiply.." proProInt
Let’s define functions on ProVal
s. (Or, technically, functions that operate on actual types, like ProVal a
, ProVal b
, or ProVal Char
.)
(Three exercises!)
3.2 More Practice with Making/Using Types
Finally, we have a few more questions in the exercises to give you more practice with types.
4 Readings
- Work through CIS 194 Lecture 3
- Read about operator sections
- You may also want to read some of CIS 194 Lecture 4, particularly up to and including function composition
Actually, we might imagine that they work well on anything with a particular “zero element”. Haskell has several abstractions to help programmers work with “stuff with zero elements”. The mempty and mzero values in
Monoid
andMonadPlus
are perhaps the most likely to match what we might want here!↩︎Why does
return
do that? Let’s talk about that later when we discuss Monads!↩︎Definitely read about operator sections!↩︎