Lecture 10: Applicative

Functors are very nice. They give us a uniform mechanism for "lifting" functions defined at a simple type to act on complicated types that are parameterized by that type, For example, if F is a Functor, and f :: A -> B, then fmap f :: F A -> F B.

But what happens if f isn't unary? Consider a hypothetical f :: A -> B -> C. Intuitively, we might hope fmap f :: F A -> F B -> F C, but it doesn't work that way. We've already defined fmap so that fmap f :: F A -> F (B -> C), i.e., the result of the first application is to produce a function in an F box, rather than a function that takes boxed values, and returns a boxed value. We could work with this if F had a mechanism for applying boxed functions to boxed arguments, returning boxed results.

The Applicative type class addresses this issue.

class Functor f => Applicative f where pure :: a -> f a (<*>) :: f (a -> b) -> f a -> f b ...

A type f is Applicative if it is a Functor that, additionally, comes with two members: an infix operator (<*>) (pronounced "ap") that takes a boxed function of type f (a -> b), applies it to a boxed argument of type f a, and produces a boxed result of type f b; and a function pure of type a -> f a that "lifts" simple values into boxed ones. There are more functions in the Applicative type class than these, but the pair pure and (<*>) are both minimally complete for, and the most commonly used functions of, the Applicative type class.

Once we have this, we can "factor" fmap:

fmap f appA = pure f <*> appA

Or, for those who like to play with η-reduction:

fmap = (<*>) . pure

Recall that (<$>) is an often used infix version of fmap. Indeed, (<$>) is especially useful in applicative contexts, as we saw in Lecture 5.

In addition to the Functor laws involving fmap, every Applicative must satisfy the following laws:

We're not going to dwell on these laws now, but in time, they'll seem obvious.

Maybe

Our handling of Maybe in Lecture 5 was intended to anticipate and motivate our discussion of Applicative and other category theoretic type classes. Recall that we defined

justMaybe :: a -> Maybe a justMaybe = Just applyMaybe :: Maybe (a -> b) -> Maybe a -> Maybe b applyMaybe (Just f) (Just a) = Just $ f a applyMaybe _ _ = Nothing

These functions had exactly the types and roles that we need for an Applicative instance of Maybe, and so,

instance Applicative Maybe where pure = Just (Just f) <*> (Just x) = Just (f x) _ <*> _ = Nothing

The definition of (<*>) in Control.Applicative is a bit different, but produces the same values.

The effect of these definitions is to enable a very general mechanism for dealing with computations that may result in errors, in which the usual evaluation mechanism is adjusted to allow errors to propagate through the usual evaluation process, and so requires no other special handling.

Recall, for the moment, our Maybe arithmetic, not from Lecture 5, but from Lecture 3, where we created a derived instance

-- | Derived instance definition for Num (Maybe n) given Num n. instance Num n => Num (Maybe n) where Just a + Just b = Just $ a + b _ + _ = Nothing Just a - Just b = Just $ a - b _ - _ = Nothing Just a * Just b = Just $ a * b _ * _ = Nothing negate (Just a) = Just $ negate a negate _ = Nothing abs (Just a) = Just $ abs a abs _ = Nothing signum (Just a) = Just (signum a) signum _ = Nothing fromInteger i = Just $ fromInteger i

We can use Applicative to substantially simplify this definition. First, we introduce the function liftA2, which is actually a part of the full definition of the Applicative type class, but you have to include Control.Applicative to get it:

class Functor f => Applicative f where ... liftA2 :: (a -> b -> c) -> f a -> f b -> f c liftA2 f a b = f <$> a <*> b

With this in hand, we can write:

instance Num n => Num (Maybe n) where (+) = liftA2 (+) (-) = liftA2 (-) (*) = liftA2 (*) negate = fmap negate signum = fmap signum abs = fmap abs fromInteger = pure . fromInteger

Which is both amazingly more concise, but also, clearer once you gestalt/grok Applicative. Note that fmap can be thought of as liftA1, and indeed, there is a legacy liftA function from the dark days of 2015 and earlier, before all instances of Applicative were required to be instances of Functor, that is exactly that. There's also a liftA3, but surprisingly, no liftA4. If you need it, you'll have to write it. But returning to liftA1/liftA: an emerging Haskell convention that when essentially the same function is defined in two related type classes, to prefer the name associated with the more general type class, hence fmap above.

Exercise 10.1

In the spirit of the liftA* functions, implement the following to lift an unboxed function and apply it to a boxed list of arguments.

liftAN :: Applicative f => ([a] -> b) -> f [a] -> f b

How useful is this function?

Exercise 10.2 Unsurprisingly, there is also an instance of Applicative for Either a. Provide an instance definition, and compare it to the definition in the Haskell sources.

*Exercise 10.3 Perhaps surprisingly, given the foregoing, there is not an Applicative instance for (,) a. Why not?

List

It is sometimes useful to think of a function f :: A -> [B] as a non-deterministic function of type f :: A -> B, i.e., a function that can have zero or more return values. In this case, it may help to think of the [] type constructor as a "computational context" rather than a "box" of values. From such a perspective, the effect of "applying" a list of functions to a list of arguments ought to be to non-deterministically select a function, and apply it to a non-deterministically selected argument, i.e., to form the list of all the ways we can apply functions to arguments. Thus,

instance Applicative [] where pure x = [x] fs <*> xs = [f x | f <- fs, x <- xs]

Thus,

> [] <*> [2,3] <*> [4,5] [] > [(+)] <*> [2,3] <*> [4,5] [6,7,7,8] > [(+),(*)] <*> [2,3] <*> [4,5] [6,7,7,8,8,10,12,15]

Note that the resulting list for the last expression above is [2+4,2+5,3+4,3+5,2*4,2*5,3*4,3*5], in precisely this order.

Exercise 10.4

Write an expression in applicative style that computes the same result as:

[ (x,y,z) | x <- [1..3], y <- [1..3], z <- [1..3] ]

ZipList

It turns out that there's a second, natural way to implement a list as an Applicative. The idea is to represent parallel (rather than non-deterministic) computation, i.e., that the i-th element of the result list comes from applying the i-th operation to the i-th operand. As we are well aware by now, however, a type can be an instance of a type class in only one way, and therefore we need to use newtype to create a (virtual) distinct type for the purpose of driving type class instance selection:

newtype ZipList a = ZipList { getZipList :: [a] }

Thus, a ZipList a is just a [a] inside a (virtual) ZipList box.

Of course, we do this to provide a distinctive Applicative instance, but we have to provide a Functor instance as well. We'll use what is essentially the standard definition of fmap for lists, acting within the box:

instance Functor Ziplist where fmap f (Ziplist xs) = ZipList (fmap f xs)

Note here that the fmap on the right hand side of the definition is []'s fmap, i.e., our old friend map. We now define the following:

instance Applicative ZipList where (ZipList fs) <*> (ZipList xs) = ZipList (zipWith id fs xs)

This requires a bit of explanation, because it's probably not what you'd expect. Certainly, I'd expect something like a binary function that performs application (e.g., \f x -> f x). But...

\f x -> f x = \f -> \x -> f x = \f -> (\x -> f x) = \f -> f = id

Or, to put this same pun differently,

id f x = (id f) x = f x

So we didn't need to "roll up" a special purpose binary application function. We already had one, in the identity function. Weird.

The alert reader/listener will have noticed that I haven't yet provided a definition of pure for Applicative ZipList. This takes a bit of thought... Let's think about what we want:

> id <$> ZipList [1] ZipList {getZipList = [1]} > id <$> ZipList [1,2] ZipList {getZipList = [1,2]} > id <$> ZipList [1,2,3] ZipList {getZipList = [1,2,3]}

Hmm. So pure id has to be a function that contains id in every coordinate of a list of indeterminate length. Haskell's laziness bails us out here. Lists are not necessarily finite, and we can perform useful computations using infinite lists (as long as finiteness comes from somewhere else)

A standard Haskell function is

repeat :: a -> [a] repeat a = a :: repeat a

In effect, repeat describes a computational process for building a potentially infinite list.

instance Applicative ZipList where pure x = ZipList (repeat x)

Of course, this definition of pure has implications for arguments as well as functions, cf.

> (+) <$> pure 3 <*> ZipList [1..4] ZipList {getZipList = [4,5,6,7]}

*Exercise 10.5

Consider the following two, very similar looking calculations:

> [(+),(*)] <*> pure 2 <*> pure 3 [5,6] > ZipList [(+),(*)] <*> pure 2 <*> pure 3 ZipList {getZipList = [5,6]}

The results of these computations (modulo syntactic noise around ZipList) are identical, but the computational patterns that produce these results are quite different. Explain the difference.

Exercise 10.6

There are several additional operators defined to improve readability when writing programs in applicative style:

(<$) :: Functor f => a -> f b -> f a (*>) :: Applicative f => f a -> f b -> f b (<*) :: Applicative f => f a -> f b -> f a (<**>) :: Applicative f => f a -> f (a -> b) -> f b

We won't often use them in our examples. But, similar to our discussion of foldMap and foldr last time, it can be helpful to think about how to implement such polymorphic functions based only on their types and what we know about the type classes that are mentioned in their constraints.

Try implementing these functions before peeking at them in the libraries.

Functions

We saw last time an Functor instance for (->) a, i.e., functions that have domain type a. There is also an Applicative instance, and it's worth working through.

We begin by considering pure. Let's suppose that b :: tb, and consider pure b. This has to be a function of type a -> tb, which leaves us with the conundrum of what to do with the argument, and what to provide as a result. The only plausible answers are to (a) ignore the argument, and (b) to return b, as it's the only value of type tb available to us! Thus,

pure b = \a -> b

This is actually a predefined function,

const :: a -> b -> a const a _ = a

Next, we need to implement (<*>), which in this context will have type (a -> b -> c) -> (a -> b) -> (a -> c). There's pretty much only one thing we can do:

f <*> b = \a -> f a (b a)

We can apply both sides to a, reduce, and get

(<*>) f b a = f a (b a)

Thus,

instance Applicative ((->) a) where pure = const (<*>) f b a = f a (b a)

Surprisingly, this sort of thing can be useful. Let's suppose, for the sake of argument, we want to compute the sum of all of the integers from 1 to 100 which are divisible by either 2 or 3. We can do this:

divisibleBy :: Int -> Int -> Bool divisibleBy d n = n `rem` d == 0 result1 = sum . filter (\x -> divisibleBy 2 x || divisibleBy 3 x) $ [1..100]

That's not terrible, but at some point in your development as a programmer, you'll decide that the expression \x -> divisibleBy 2 x || divisibleBy 3 x is too low level an approach to building the “or” of two predicates. It should be possible to take the ”or” more directly. At this point, you might define

orf :: (a -> Bool) -> (a -> Bool) -> (a -> Bool) orf f g a = f a || g a result2 = sum . filter (divisibleBy 2 `orf` divisibleBy 3) $ [1..100]

After all, all you're doing is lifting or. At some point, this language will remind you that there are already type classes for dealing with lifted types, and a light goes on. You didn't need to define orf at all. Like Dorothy and the ruby red slippers, you already had what you needed:

result3 = sum . filter ((||) <$> divisibleBy 2 <*> divisibleBy 3) $ [1..100]

or,

result4 = sum . filter (liftA2 (||) (divisibleBy 2) (divisibleBy 3)) $ [1..100]

There's no place like home.