Lecture 18 — 2015-11-09

Functor and Applicative

This lecture is written in literate Haskell; you can download the raw source.

A few words on abstraction and why we bother.

A lot of this material is borrowed/based on two resources written by Brent Yorgey: his Haskell course from Spring 2013 and his Typeclassopedia. I encourage you to go read these excellent resources!

{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
module Lec18 where

import Prelude hiding (map)
import Lec17

import Control.Applicative
import Data.Char

import System.Environment
import System.Exit

import qualified Data.Map as Map
import Data.Map (Map, (!))

map :: (a -> b) -> [a] -> [b]
map f = foldr ((:) . f) []

data BinTree a = BTEmpty | BTNode (BinTree a) a (BinTree a) deriving Show

treeMap f BTEmpty = BTEmpty
treeMap f (BTNode l v r) = BTNode (treeMap f l) (f v) (treeMap f r)

maybeMap f Nothing = Nothing
maybeMap f (Just x) = Just (f x)
class Functor f where
  fmap :: (a -> b) -> f a -> f b

Here f is a ‘container’, or, more broadly, a computational context.

instance Functor BinTree where
  fmap = treeMap

add1 :: (Functor f, Num a) => f a -> f a
add1 = fmap (+1)

What other instances can we find for Functor?

Well, the Listlike type class we saw might do…

instance Listlike f => Functor f where
  fmap = each

…but this leads to undecidability. What if f already has its own instance of Functor? We can use newtype to resolve this issue.

newtype AsList f a = AsList { getList :: f a } deriving Show

instance Listlike f => Functor (AsList f) where
  fmap f = AsList . each f . getList

l1 = add1 (AsList [1..10])

l2 = add1 (AsList (foldr cons nil [1..10] :: UnionTree Int))

What about other types? Let’s try pairs.

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

…nope! The kinds aren’t even right… Functor applies to types of kind * -> *, but (,) has kind * -> * -> *. So we’ll need to apply (,) to a type to make it work.

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

Okay… why does the left stay fixed? Because here fmap : (a -> b) -> (e,a) -> (e,b).

We could, if we liked define pairs of values of the same type, as in:

data Pair a = Pair a a deriving Show

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

Okay, so much for pairs. What about sum types?

instance Functor Either where
  fmap f (Left a)  = Left  $ f a
  fmap f (Right a) = Right $ f a

Hmm… nope. The kinds don’t check out. We can do this, though:

instance Functor (Either e) where
  fmap f (Left e)  = Left e
  fmap f (Right a) = Right $ f a

Again, we choose the left side out of convenience. We could define something similar to Pair, if we wanted:

data Choice a = ColumnA a | ColumnB a

instance Functor Choice where
  fmap f (ColumnA a) = ColumnA $ f a
  fmap f (ColumnB a) = ColumnB $ f a

At first, I said that a type constructor f that is a Functor could be thought of as a container: fmap :: (a -> b) -> f a -> f b runs a function on the contents of a container. Thinking of functors as containers isn’t a bad intuition, but it’s slightly inadequate.

More broadly, a functor is a computational context, not just a container. That is, functors may not always be traversible the way that code is.

instance Functor ((->) e) where
  fmap f g = \e -> f (g e)

That is:

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

The Applicative type class

type Name = String

data Employee = Employee { name    :: Name
                         , phone   :: String }
                deriving Show

maybeEmployee :: (Name -> String -> Employee) -> 
                 (Maybe Name -> Maybe String -> Maybe Employee)
maybeEmployee f (Just n) (Just p) = Just $ f n p 
maybeEmployee _ _ _ = Nothing

listEmployee :: (Name -> String -> Employee) -> 
                ([Name] -> [String] -> [Employee])
listEmployee f n p = zipWith f n p

listEmployee' :: (Name -> String -> Employee) -> 
                 ([Name] -> [String] -> [Employee])
listEmployee' f n p = map (\(name,phone) -> f name phone) allPairs
  where allPairs = Prelude.concat (map (\name -> map (\phone -> (name,phone)) p) n)
  -- map (uncurry f) $ concatMap (\name -> map (\phone -> (name,phone)) p) n

funEmployee :: (Name -> String -> Employee) -> 
               (e -> Name) -> (e -> String) -> (e -> Employee)
funEmployee f mkName mkPhone = \e -> f (mkName e) (mkPhone e)

Can we use Functor to do this? The type above looks like fmap, but with two arguments instead of one. Can we write a different function fmap2?

fmap2 :: Functor f => (a -> b -> c) -> f a -> f b -> f c
fmap2 f a b = undefined 
  where fa = fmap f a -- where do we go from here?

Functor is a fine type class, but it only lets us operate opaquely. Once a function is trapped in Functor, we can’t get it out!

A different type class, Applicative, solves this problem.

class Functor f => Applicative f where
  pure  :: a -> f a
  (<*>) :: f (a -> b) -> f a -> f b -- pronounced 'ap'
fmap2' :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
fmap2' f a b = (fmap f a) <*> b
pure  :: a             -> f a
fmap  :: (a -> b)      -> f a -> f b
fmap2 :: (a -> b -> c) -> f a -> f b -> f c

Note that to be an Applicative, you must be a Functor. Can we write fmap using the <*>?

fmap' :: Applicative f => (a -> b) -> f a -> f b
fmap' f a = pure f <*> a

In fact, using fmap with Applicatives is so common that we have the definition <$> = fmap.

fmap2Best :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
fmap2Best f a b = f <$> a <*> b -- note left associativity

Finally, let’s note that this function is defined as liftA2 in the module Control.Applicative.

Let’s write some Applicative instances and work with it more.

instance Applicative Pair where
  pure a = Pair a a
  (Pair f1 f2) <*> (Pair a1 a2) = Pair (f1 a1) (f2 a2)

instance Applicative Choice where
  pure a = ColumnA a

  ColumnA f <*> a = fmap f a
  ColumnB f <*> a = fmap f a

How else could we have done it? Well, it turns out there are laws that should hold for Functor and Applicative. In particular:

fmap id == id fmap (f . g) == fmap f . fmap g fmap f x === pure f <*> x
instance Applicative BinTree where
  pure a = BTNode BTEmpty a BTEmpty

  BTEmpty <*> _ = BTEmpty
  BTNode _ _ _ <*> BTEmpty = BTEmpty
  BTNode lf f rf <*> BTNode la a ra = BTNode (lf <*> la) (f a) (rf <*> ra)

Does that law hold for the above? No, not considering what we defined as Functor BinTree above! We would need something like:

instance Applicative BinTree where
  pure a = BTNode BTEmpty a BTEmpty

  BTEmpty <*> _ = BTEmpty
  BTNode _ f _ <*> t = treeMap f t

Let’s look at the Applicative instance for Maybe.

instance Applicative Maybe where
  pure              = Just
  Nothing <*> _     = Nothing
  _ <*> Nothing     = Nothing
  Just f <*> Just x = Just (f x)
m_name1, m_name2 :: Maybe Name
m_name1 = Nothing
m_name2 = Just "Brent"

m_phone1, m_phone2 :: Maybe String
m_phone1 = Nothing
m_phone2 = Just "555-1234"

ex01 = Employee <$> m_name1 <*> m_phone1
ex02 = Employee <$> m_name1 <*> m_phone2
ex03 = Employee <$> m_name2 <*> m_phone1
ex04 = Employee <$> m_name2 <*> m_phone2
(.+) = liftA2 (+)
(.*) = liftA2 (*)
n = ([10,5] .* [4,8]) .+ [3,4] .+ [4,3]
newtype ZipList a = ZipList { getZipList :: [a] }
  deriving (Eq, Show, Functor)

instance Applicative ZipList where
  pure = ZipList . repeat
  ZipList fs <*> ZipList xs = ZipList (zipWith ($) fs xs)

Now we can see a couple of different ways to go back and redefine Applicative BinTree. Should it expand into “tree product”, or should it try to match up trees (in which case we need something like repeat for trees)?