April 2021
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
mapMaybe :: (a -> b) -> Maybe a -> Maybe b
mapMaybe f Nothing = Nothing
mapMaybe f (Just x) = Just (f x)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?
A functor is a type constructor with a mapping operation.
Lists and Maybe are instances of Functor:
-- from the standard Prelude
instance Functor [] where
fmap = map
instance Functor Maybe where
fmap = mapMaybe -- as before
We can declare an instance of Functor for trees:
> 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)Functors are not always data structures; for example, IO is also a functor.
More generally: every monad is a functor (later).
> fmap toUpper getChar
h -- standard input
'H'
> fmap (++"!!!") getLine
hello, world -- standard input
"hello, world!!!"
> fmap length getLine
hello, world -- standard input
12The functor map operation should satisfy two laws:
fmap id \(=\) id
fmap (f . g) \(=\) fmap f . fmap g
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).
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)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 3Functions are also functors on the result type; fmap is simply function composition.
Examples:
fmap applies a function to a value inside a functor:
What if want to apply a function inside the functor to a value also inside the functor?
An ordinary functor is not enough; we need an applicative functor!
-- 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:
pure takes a value and “wraps it” into the applicative functor<*> applies a “wrapped” function to a “wrapped” value and gets back a “wrapped” result-- in Control.Applicative
instance Applicative Maybe where
pure = Just
Nothing <*> _ = Nothing
Just f <*> something = fmap f somethingpure is Just<*> yields Nothing if the left argument is Nothing; otherwise it maps the function to the right argument> 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> 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 ApplicativeWhat does pure f <*> v do?
f in the functor;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:
Hence: pure f <*> v \(=\) f <$> v
More generally:
pure f <*> v1 <*> v2 <*> ... <*> vn \(=\)
f <$> v1 <*> v2 <*> ... <*> vn
> length <$> Just "hello"
Just 5
> (+) <$> Just 5 <*> Just 3
Just 8
> (++) <$> Just "hello, " <*> Just "world"
Just "hello, world"-- in Control.Applicative
instance Applicative [] where
pure x = [x]
fs <*> xs = [f x | f <- fs, x <- xs]pure gives a singleton list<*> applies every function of the left argument to every value in the right argument> [(*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!"]-- in Control.Applicative
instance Applicative IO where
pure = return
a <*> b = do
f <- a
x <- b
return (f x)pure is return<*> performs the left action to get a function f, the right action to get a value x and returns f xmyAction :: 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 <*> getLineFunctions are also applicative functors on the result type:
pure is the \(K\) combinator<*> is the \(S\) combinatorAbstract syntax for simple expressions:
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 -> vUsing 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)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 eReplacing 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 epure f <*> v \(=\) fmap f vpure id <*> v \(=\) vpure (.) <*> u <*> v <*> w \(=\) u <*> (v <*> w)pure f <*> pure x \(=\) pure (f x)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.)
Just as IO, every monad can be made into an applicative functor.
The reverse is not true: not all applicate functors are monads.
The default Applicative for lists combines every function with every value, e.g.:
Another way to make lists an applicative functor is to combine functions and values pointwise, e.g.:
To avoid ambiguity, such instance is provided for a ZipList newtype.
-- 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)pure yield an infinite repeating list<*> applies functions to values at corresponding positionsNote that zipWith result is truncated to the shortest input — hence zipping finite and infinite lists yields a finite list.
To convert ZipLists to ordinary lists:
> (+) <$> 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')](>>=) :: m a -> (a -> m b) -> m b
-- monadic bind
(<*>) :: f (a -> b) -> f a -> f b
-- applicative bindMonad computations are more expressive than applicative ones:
>>= allows the value returned from the first computation to influence the choice of the next computation<*> fixes the structure of computation; effects of both computations are combinedifM :: 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 eifM performs the effects of mb and either mt or meifA performs all the effects of fb, ft and feApplicative and Monad were unrelated classes (but all standard monads had applicative instances)Applicative is a superclass of Monadclass 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 bComputations 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 e2Type-safe parsing of data read from databases:
The Haxl project at Facebook:
Applicative for implicit concurrency