Lecture 11

Administrivia

Please note that the midterm exam will be a week from Friday, on October 31st.

Functor instances

Last time, we motivated the Functor typeclass by observing that functors are just automorphisms (homomorphisms with the same domain and range) on the category Hask, and so are natural from a mathematical point of view. The purpose of today's lecture is to provide many examples of Functor instances, which are interesting in their own right, but also motivate that Functor is a natural programming idea, as well.

Recall,

class Functor f where fmap :: (a -> b) -> f a -> f b

satisfying

fmap id = id fmap (f . g) = fmap f . fmap g

The instances of Functor defined in the Prelude and elsewhere in the standard Haskell modules all satisfy this law, and yours should too.

Let's look at a few simple instances of Functor.

Identity

The Identity type can be defined as follows:

data Identity a = Identity a deriving (Show)

A value of Identity type is simply a box that holds a value of another type. The functor instance is extremely simple: take something out of the box, hit it with the function, and put the result back in a box:

instance Functor Identity where fmap f (Identity x) = Identity (f x)

and this works pretty much as you'd expect:

> fmap (1+) $ Identity 2 Identity 3

It would seem that there's not much to say about Identity, nor that it's very useful. Neither of these are true. The Identity monad plays an important role in the theory and practice of monad transformers, a topic for later in the quarter. As for something to say, the actual definition of Identity in Data.Functor.Identity is:

newtype Identity a = Identity { runIdentity :: a }

OK, that's mysterious. Let's take a little digression and understand what's going on here.

The first thing to understand is that Haskell has two distinct syntaxes for type-theoretic sums. The first is the positional syntax we already learned, the second introduces names for the components, and is known as “record syntax,” e.g.,

data Complex = Complex { real :: Double , imag :: Double } deriving (Show)

Types defined this way can still take advantage of positional pattern matching, e.g.,

instance Num Complex where (Complex ar ai) + (Complex br bi) = Complex (ar + br) (ai + bi)

still works. But we gain accessor functions real and imag that extract the relevant component from the type, e.g.,

> real (Complex 1 2) 1.0

keyword based construction

> Complex { real = 1, imag = 3 } Complex {real = 1.0, imag = 3.0}

keyword based copy-mutation

> let a = Complex 1 2 > let b = a { real = 3 } > b Complex {real = 3.0, imag = 2.0}

and even keyword based pattern matching

conjugate :: Complex -> Complex conjugate (c@Complex{imag=im}) = c { imag = -im }

That's one mystery.

The other restriction on typeclasses: only types, not type aliases, can be instances of a typeclass. The new keyword newtype is a limited form of data that applies only to unary monomorphic types, i.e., data declarations in which there's only a single type constructor, and it takes only a single argument. We can think of such types has having only one kind of "box" carrying only one value, and so box itself gives us no advantages. As such, newtype indicates that the box can be omitted at run time, i.e., the boxing and unboxing functions can be replaced by the identity function. The boxes are virtual!

Now, the use of named record syntax for Identity may seem like overkill, but it's done that way for consistency with more complicated examples. Moreover, it permits a particularly pleasing definition of the Functor instance:

instance Functor Identity where fmap f = Identity . f . runIdentity

Unbox the argument, whack it with f, and box it back up. And of course, because we defined Identity via newtype, both the runIdentity accessors and the Identity constructor are just id, so this amounts to

fmap f = f

i.e., fmap is a special case of the identity function, although we can't write it that way because it doesn't typecheck.

Maybe

The Maybe type is a standard Prelude type:

data Maybe a = Nothing | Just a deriving (Eq, Ord)

Intuitively, a Maybe object is a box that contains either zero or one value. The Maybe class gets used in contexts where errors can occur, and we want to deal with them in a principled way. Maybe types arise naturally in the context of partial-functions, or calculations that may fail. For example, consider looking up a key in a dictionary. What do we do if the key isn't there? One possibility is to throw an exception, another is to return default “sentinel” value. Maybe enables us to do this in a principled way, as Nothing becomes that sentinal.

The Functor Maybe instance is pretty simple:

instance Functor Maybe where fmap f Nothing = Nothing fmap f (Just x) = Just (f x)

This shows a common (but not universal) pattern for functors: copy a data structure, applying f to the objects of the argument type that are encountered along the way.

BTW, Maybe a is an instance of Show if a is:

instance Show a => Show (Maybe a) where show (Nothing) = "Nothing" show (Just a) = "Just " ++ show a

Exercise 11.1

Write a different version of fmap in the Maybe instance that does typecheck but does not satisfy the Functor laws. Why is this version undesirable?

Note that Apple is pushing the newly-developed language Swift, which includes many ideas from the functional programming community generally and Haskell specifically, including polymorphic types. One of the so-called “modern” features of Swift is its use of ”optional types,” but this just Haskell's Maybe type, coupled with some special-purpose syntax. There'a a morals here: if you love Haskell, but can't find employment programming in Haskell, there's likely a lot of money to be made programming in Swift. And you'll be a heck of a lot better prepared for the language than folks who have come up to it from C++ or Java. This is part of a general trend, it's common for languages to “borrow” features that first appear in other languages, and this is generally a good thing. A very good reasons to learn Haskell is that borrowings from it are common, whereas it rarely finds an advantage in borrowing from other languages. Whatever language you'll using in ten or twenty years, learning Haskell now is very likely the best thing you can do now to prepare yourself for it. It is the language of the future, available today.

Either

The Either type is a standard Prelude type similar to the Maybe class, but we allow the Nothing-like alternative to carry along arbitrary information:

data Either a b = Left a | Right b deriving (Eq, Ord) instance Functor (Either a) where fmap _ (Left x) = Left x fmap f (Right y) = Right (f y)

Here we think of Left as the Nothing-like alternative, and Right (which functions as a pun [and what's a pun but a type error turned into a joke?]: positionally as regards the declaration, and normatively in the "non-error value" sense) is analogous to Just. Note that Either has kind * -> * -> *, but for any type s of kind *, Either a is a type of kind * -> *, which is the kind of Functor instances.

It's slightly amusing here that we can't write:

fmap _ e@(Left _) = e

and the error message that you get when you try to only makes sense after you understand the error, and so isn't actually helpful. The problem here is that in the correct definition above, the types of Left on the left-hand and right-hand side of the equation have different types, so using e as in the wrong definition results in the right-hand side having the wrong type, even though the structure is “right.”

Lists

We now have a Functor instance for a type (Identity) that packages up exactly one element of an underlying type, and functor for a couple of types (Maybe, Either s) that contain zero or one element, What about a functor for a data structure that contains an arbitrary number of values of a given type, say a list?

instance Functor [] where fmap f [] = [] fmap f (a:as) = f a : fmap f as

Unfortunately, we can't easily test this code, as it's not really possible to hide an instance declaration. Of course, this definition should look familiar, it's just map! So it suffices to define:

instance Functor [] where fmap = map

and that is exactly how it is defined.

*Exercise 11.2

Consider the following type for a non-empty binary tree that contains values at its leaves, and create a Functor instance:

data BinaryTree a = Leaf a | Node (BinaryTree a) (BinaryTree a) deriving (Show)

Pairs

Remember that we can write the ordered pair type (a,b) as (,) a b. This allows us to make ordered pairs an instance of functor, by having fmap act on the second coordinate:

instance Functor ((,) a) where fmap f (a,b) = (a,f b)

For example

> fmap (+1) ("one",1) ("one",2)

Exercise 11.3

The Functor instance for pairs might make the first components of pairs jealous: why should the second components get all the attention?

We might try to be clever and use our knowledge of type aliases to rearrange the type variables and provide the following additional instance declaration:

type Pair a b = (,) b a instance Functor (Pair b) where fmap f (x, y) = (f x, y)

This makes Haskell very angry, however. What error does Haskell report and why?

Association Lists

Association lists are lists of key-value pairs, and have long been used in functional programming languages to represent finite functions. In Haskell, we can represent association lists very cleanly:

newtype Assoc a b = Assoc [(a,b)] apply :: Eq a => Assoc a b -> a -> Maybe b apply (Assoc ps) k = iter ps where iter [] = Nothing iter ((a,b):ps) | a == k = Just b | otherwise = iter ps

Note here that Assoc generalizes the Dict type we considered earlier by abstracting out the type of the key. We can make Assoc into a Functor as follows:

instance Functor (Assoc a) where fmap f (Assoc ps) = Assoc (map (fmap f) ps)

Now, at this point, if you’re as crazy as your instructor, you might think to yourself that Assoc is in some sense a mashup of (,) and [], which are themselves functors, and it ought to be possible to somehow take advantage of this. And it is, although it is a bit of a walk on the wild side. We start by defining:

newtype PairT m a b = PairT { runPairT :: m (a,b) }

Note that the kind of PairT is (* -> *) -> * -> * -> *, our first type of higher-order kind, so we start off pretty deep in the weeds. We then define a Functor instance for PairT m a which relies on its first argument also being a Functor:

instance (Functor m) => Functor (PairT m a) where fmap f (PairT mp) = PairT $ fmap (\(a,b) -> (a,f b)) mp

or even, because there’s no fun in titrating crazy,

instance (Functor m) => Functor (PairT m a) where fmap f = PairT . fmap (\(a,b) -> (a,f b)) . runPairT

or even

instance (Functor m) => Functor (PairT m a) where fmap f = PairT . fmap (fmap f) . runPairT

These are a bit tricky, because the fmap on the right-hand side is m’s fmap. But this actually works, and allows us to define:

type Pair = PairT Identity type Assoc = PairT []

and now Pair and Assoc are functors for free, because they come with derived functor instances, and these declarations of Pair and Assoc function just like the old definitions. And now we can answer the question we deferred at the beginning of the lecture. Building a meta-language of type construction that includes derived instances enables typeclasses of the base types to be reflected in automatically generated instances of the derived types, bringing in a lot of free functionality.

Now to be clear here, I don’t expect you to write code like this. It’s arguably a bridge too far for you to understand now, let alone write. But we will see similar examples later, and I want to prepare you before I pull this rabbit out of my hat later in the quarter.

Exercise 11.4

A slightly saner approach to defining Assoc builds on the Compose idea we had above. To make this work, we have to defined Compose using newtype rather than type as follows:

newtype Compose g f a = Compose { runCompose :: g (f a) }

Complete the instance definition

instance (Functor g, Functor f) => Functor (Compose g f) where fmap h = ...

and illustrate that your code works by defining

type Assoc = Compose [] ((,) String)

and show that

> runCompose . fmap (+1) . Compose $ [("one",1),("two",2)] [("one",2),("two",3)]

Functions

We can think of functions f :: a -> b as being containers of b's, indexed by a's. As such it is easy to turn ordinary functions into Functors:

instance Functor ((->) a) where fmap = (.)

This is surprising, but in a way, argues for the naturalness of what we're doing, as the fmap function can be thought of as a simultaneous generalization of map and (.).

Note that this particular instance implementation is quite different from the early instance implementations, in that the effect of composition is to build a “shim” around our original function, and to apply f as values are extracted through that shim. The point here is that we have considerable flexibility in implementation, what matters is that the fmap is implemented in such a way as to satisfy the functor laws.

*Exercise 11.5

What is the type of fmap in the ((->) a) instance? (Hint: it may help to first write out the type of fmap in the other instances above.)