Functors and Applicatives

Pedro Vasconcelos, DCC/FCUP

April 2021

Bibliography

Chapter 11 of “Learn You a Haskell for Great Good!”: http://learnyouahaskell.com/functors-applicative-functors-and-monoids

“Functional Pearl: Applicative Programming with Effects”, Connor McBride and Ross Paterson, Journal of Functional Programming, 2008. http://staff.city.ac.uk/~ross/papers/Applicative.html

Functors

Mapping over Lists

map :: (a -> b) -> [a] -> [b]
map f []     = []
map f (x:xs) = f x : map f xs

Mapping over Maybe

mapMaybe :: (a -> b) -> Maybe a -> Maybe b
mapMaybe f Nothing  = Nothing
mapMaybe f (Just x) = Just (f x)

Mapping over Trees

data Tree a = Empty | Node a (Tree a) (Tree a)

mapTree :: (a -> b) -> Tree a -> Tree b
mapTree f Empty = Empty
mapTree f (Node x l r)
  = Node (f x) (mapTree f l) (mapTree f r)


Can we factor out the common pattern?

The Functor class

A functor is a type constructor with a mapping operation.

-- in the standard Prelude
class Functor f where
   fmap :: (a -> b) -> f a -> f b

Functor examples

Lists and Maybe are instances of Functor:

-- from the standard Prelude
instance Functor [] where
   fmap = map

instance Functor Maybe where
   fmap = mapMaybe -- as before

Functor examples (2)

data Tree a = Empty | Node a (Tree a) (Tree a)


We can declare an instance of Functor for trees:

instance Functor Tree where
    fmap = mapTree -- as before

Examples

> fmap (*2) [1,2,3]
[2,4,6]

> fmap (*2) (Just 5)
Just 10

> fmap (++"!!") (Just "hello, world")
Just "hello, world!!!"

> fmap (*2) (Node 1 Empty (Node 3 Empty Empty))
Node 2 Empty (Node 6 Empty Empty)

More Functors

Functors are not always data structures; for example, IO is also a functor.

-- in standard Prelude
instance Functor IO where
   fmap f m = do x <- m
                 return (f x) 


More generally: every monad is a functor (later).

Examples

> fmap toUpper getChar
h               -- standard input
'H'

> fmap (++"!!!") getLine
hello, world    -- standard input
"hello, world!!!"

> fmap length getLine
hello, world    -- standard input
12

The Functor laws

The functor map operation should satisfy two laws:

Identity

fmap id \(=\) id

Composition

fmap (f . g) \(=\) fmap f . fmap g

Lists are Functors

For lists: \[ \begin{aligned} map~ id~ xs &=& xs \\ map~ (f \circ g)~ xs &=& map~ f~ (map~ g~ xs) \end{aligned} \] Proof: by induction on \(xs\) using the recursive definition of \(map\).


Exercise: prove the functor laws for the Maybe and Tree instances (need structural induction for the later).

Example of a Non-Functor

A Maybe-like container that “counts” the number of fmaps.

data CMaybe a = CNothing | CJust Int a

instance Functor CMaybe where
  fmap f CNothing = CNothing
  fmap f (CJust c x) = CJust (c+1) (f x)

Example of a Non-Functor (2)

The Functor instance breaks both functor laws:

> fmap id (CJust 0 'a')
CJust 1 'a'

> fmap ((+1).(*2)) (CJust 0 1)
CJust 1 3

> fmap (+1) (fmap (*2) (CJust 0 1))
CJust 2 3

More functors

Functions are also functors on the result type; fmap is simply function composition.

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

Examples:

> fmap (*2) (*2) 1
4

> fmap length (++"!!") "hello"
7

Applicative Functors

Applicative Functors

fmap applies a function to a value inside a functor:

fmap :: (a -> b) -> f a -> f b

What if want to apply a function inside the functor to a value also inside the functor?

??? :: f (a -> b) -> f a -> f b

An ordinary functor is not enough; we need an applicative functor!

The Applicative class

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


An applicative functor is a functor with two extra operations:

Applicative instance: Maybe

-- in Control.Applicative
instance Applicative Maybe where
   pure = Just
   Nothing <*> _  = Nothing
   Just f <*> something = fmap f something

Examples

> Just (+3) <*> Just 9
Just 12

> Just (+3) <*> Nothing
Nothing

> Just length <*> Just "world"
Just 5

> Just (++" world") <*> Just "hello,"
Just "hello, world"

> Nothing <*> Just "world"
Nothing

Examples (2)

> pure (+) <*> Just 3 <*> Just 5
Just 8

> pure (+) <*> Just 3 <*> Nothing
Nothing

> pure (+) <*> Nothing <*> Nothing
Nothing


Note that <*> is left-associative, i.e.

A <*> B <*> C \(\equiv\) (A <*> B) <*> C

fmap using Applicative

What does pure f <*> v do?

  1. wrap a function f in the functor;
  2. unwraps it and applies it to a wrapped value v.

Hence, it should do the same as fmap:

pure f <*> v \(=\) fmap f v

(this is one of the applicative laws).

fmap using Applicative (2)

The library defines an infix operator <$> for fmap:

-- in Control.Applicative
(<$>) :: Functor f => (a -> b) -> f a -> f b
f <$> v = fmap f v

Hence: pure f <*> v \(=\) f <$> v

More generally:

pure f <*> v1 <*> v2 <*> ... <*> vn \(=\)
f <$> v1 <*> v2 <*> ... <*> vn

Examples

> length <$> Just "hello"
Just 5

> (+) <$> Just 5 <*> Just 3
Just 8

> (++) <$> Just "hello, " <*> Just "world"
Just "hello, world"

Applicative instance: Lists

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

Examples

> [(*0),(+100),(^2)] <*> [1,2,3]
[0,0,0,101,102,103,1,4,9]

> [(+),(*)] <*> [1,2] <*> [3,4]
[4,5,5,6,3,4,6,8]

> (++) <$> ["ha","heh"] <*> ["?","!"]
["ha?","ha!","heh?","heh!"]

Applicative instance: IO

-- in Control.Applicative
instance Applicative IO where
    pure = return
    a <*> b = do
        f <- a
        x <- b
        return (f x)

Examples

myAction :: IO String
myAction = do
    a <- getLine
    b <- getLine
    return (a ++ b)

-- Can be re-written as:
myAction :: IO String
myAction = pure (++) <*> getLine <*> getLine

-- Or even shorter:
myAction :: IO String
myAction = (++) <$> getLine <*> getLine

Applicative instance: Functions

Functions are also applicative functors on the result type:

instance Applicative ((->) e) where
    pure x = \_ -> x
    f <*> g = \e -> f e (g e)

Example: an evaluator

Abstract syntax for simple expressions:

data Expr = Var Name
          | Lit Int
          | Add Expr Expr
          | Mul Expr Expr
          | Neg Expr 
            deriving Show

Environments

Assume variable values are given by an environment:

type Name = String

type Env = [(Name, Int)]

fetch :: Name -> Env -> Int
fetch x env = case lookup x env of
    Nothing -> error "invalid name"
    Just v -> v

Evaluator, first version

Using an explicit environment:

eval :: Expr -> Env -> Int
eval (Var x) env
   = fetch x env
eval (Lit v) env
   = v
eval (Add e1 e2) env
   = eval e1 env + eval e2 env
eval (Mul e1 e2) env
   = eval e1 env * eval e2 env
eval (Neg e) env
   = negate (eval e env)

Evaluator, applicative style

We can “hide” the environment using the applicative instance for ((->) Env).

eval :: Expr -> Env -> Int
eval (Var x)
   = fetch x
eval (Lit v)
   = pure v
eval (Add e1 e2)
   = pure (+) <*> eval e1 <*> eval e2
eval (Mul e1 e2)
   = pure (*) <*> eval e1 <*> eval e2
eval (Neg e)
   = pure negate <*> eval e

Evaluator, applicative style (2)

Replacing pure f <*> u by f <$> u makes it more succint:

eval :: Expr -> Env -> Int
eval (Var x)
    = fetch x
eval (Lit v)
    = pure v
eval (Add e1 e2)
    = (+) <$> eval e1 <*> eval e2
    eval (Mul e1 e2)
    = (*) <$> eval e1 <*> eval e2
eval (Neg e)
    = negate <$> eval e

Reflections

Applicative Laws

  1. pure f <*> v \(=\) fmap f v
  2. pure id <*> v \(=\) v
  3. pure (.) <*> u <*> v <*> w \(=\) u <*> (v <*> w)
  4. pure f <*> pure x \(=\) pure (f x)
  5. u <*> pure x \(=\) pure (\f -> f x) <*> u


These laws are satifisfied for all applicative instances shown — see the bibliography for details.

(1, 2 and 4 are fairly intuitive; 3 and 5 not so much.)

Every Monad is an Applicative

Just as IO, every monad can be made into an applicative functor.

instance Applicative MyMonad where
   pure = return
   u <*> v = do 
       f <- u
       x <- v
       return (f x)

The reverse is not true: not all applicate functors are monads.

Applicative that is not a Monad: ZipList

The default Applicative for lists combines every function with every value, e.g.:

[f,g] <*> [x1,x2,x3]
   = [f x1, f x2, f x3, g x1, g x2, g x3]

Another way to make lists an applicative functor is to combine functions and values pointwise, e.g.:

[f,g,h] <*> [x1,x2,x3] = [f x1, g x2, h x3]

To avoid ambiguity, such instance is provided for a ZipList newtype.

Applicative instance: ZipList

-- in Control.Applicative
newtype ZipList a = ZipList [a]

instance Applicative ZipList where
   pure x = ZipList (repeat x)
   ZipList fs <*> ZipList xs
      = ZipList (zipWith (\f x -> f x) fs xs)

Note that zipWith result is truncated to the shortest input — hence zipping finite and infinite lists yields a finite list.

Applicative ZipList (2)

To convert ZipLists to ordinary lists:

-- in Control.Applicative
getZipList :: ZipList a -> [a]
getZipList (ZipList xs) = xs

Examples

> (+) <$> ZipList [1,2,3] <*> ZipList [4,5,6]
ZipList [5,7,9]

> max <$> pure 0 <*> ZipList [-1,5,0,-5,10] 
ZipList [0,5,0,0,10]

> (,,) <$> ZipList "dog" <*> ZipList "cat"
       <*> ZipList "rat"
ZipList [('d','c','r'),
         ('o','a','a'),
         ('g','t','t')]

Monads vs Applicatives

(>>=) :: m a -> (a -> m b) -> m b
              -- monadic bind
(<*>) :: f (a -> b) -> f a -> f b
              -- applicative bind

Monad computations are more expressive than applicative ones:

Example

ifM :: Monad m =>       -- monadic "if"
       m Bool -> m a -> m a -> m a
ifM mb mt me = do
   b <- mb
   if b then mt else me

ifA :: Applicative f => -- applicative "if"
       f Bool -> f a -> f a -> f a
ifA fb ft fe = cond <$> fb <*> ft <*> fe
  where cond b t e = if b then t else e

History

Functor / Applicative / Monad

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

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

class Applicative m => Monad m where 
   return :: m a
   (>>=) :: m a -> (a -> m b) -> m b

Usage

Succint syntax

Computations with effects can often be expressed more succintly using applicatives, e.g:

-- monadic 
eval (Add e1 e2) = do v1 <- eval e1
                      v2 <- eval e2
                      return (v1 + v2)

-- applicative 
eval (Add e1 e2) = (+) <$> eval e1 <*> eval e2

Parsing / serialization

Type-safe parsing of data read from databases:

Concurrency

The Haxl project at Facebook: