Functors, Applicative, and Monads
A simple monadic EDSL for input/output (deep embedding)
We will develop a simple I/O EDSL in Haskell
-- Types data Program a -- Constructors return :: a -> Program a putC :: Char -> Program () getC :: Program (Maybe Char) -- Combinators (>>=) :: Program a -> (a -> Program b) -> Program b -- Run function type IOSem a run :: Program a -> IOSem a
We will use monads to handle the I/O effects!
Scenario
Types for inputs and outputs
type Input = String type Output = String
Following the deep embedding guidelines, we have a constructor in
Program
per constructor / combinator.data Program a where Put :: Char -> Program () Get :: Program (Maybe Char) Return :: a -> Program a Bind :: Program a -> (a -> Program b) -> Program b
Observe the use of GADTs!
- In the definition of
Get
, why usingMaybe Char
instead ofChar
? - We need to indicate the "end of input" somehow, i.e., by using
Nothing
getC = Get putC = Put
- In the definition of
What's the implementation of the type
IOSem
, i.e., the semantics of a program?type IOSem a = Input -> (a, Input, Output)
It is a function which takes an input and returns a result (of type
a
), the left over input (of typeInput
), and an output (of typeOutput
).The
run
functionrun :: Program a -> IOSem a run (Put c) inp = (() , inp , c:"" ) run (Get) "" = (Nothing, "" , "" ) run (Get) (c:cs) = (Just c , cs , "" ) run (Return x) inp = (x , inp , "" ) run (Bind p g) inp = (b , inp_b, out_a ++ out_b) where (a, inp_a, out_a) = run p inp (b, inp_b, out_b) = run (g a) inp_a
Let us write an "echo" program
echo :: Program () echo = getC >>= f where f Nothing = return () f (Just c) = putC c
To run it, we need to give it an input
run echo "a" > ((), "", "a")
**Exercise**: write a program which does a *double echo*, i.e., it reads a character from the input and writes it twice into the output
A simple monadic EDSL for input/output (intermediate embedding)
It is often good to move away a bit from the pure deep embedding towards some kind of "normal form" ("optimized", "elemental" embedding).
We want to remove the
Bind
operator. How are we going to write sequential actions then?`(>>=)` is going to be executed when constructing the program, but not when running it!Methodology:
- Looking the most typical usage patterns of
Bind
, - Introduce new constructors to capture such cases, and
- Simplify the data type with the new constructors
- Looking the most typical usage patterns of
Let's look at the different cases for the first argument of
Bind
.Put c >>= f Get >>= f Return x >>= f
Put c >>= f
From the types of
Put
andBind
we note thatf
must have type() -> m a
which is basically just a value of type
m a
. Another way to think about it is thatPut
does not really return any useful value (the actual "putting" is implemented as a "side-effect"). So the function after bind can ignore its argument.Put c >>= \_ -> p ≡ Put c >> p
We will now give a name to this new combination
PutThen c p ≡ Put c >> p
This is a
Program
which starts by printingc
and the behaves likep
.Get >>= f
In a similar way we can introduce a new name for the combination of
Get
andBind
:GetBind f ≡ Get >>= f
Return x >>= f
The third combination would be
ReturnBind
ReturnBind x f ≡ Return x >>= f
but the first monad law already tells us that this is just
(f x)
so no new constructor is needed for this combination.For the last combination, i.e.,
(m >>= g) >>= f
, the associative monadic law tells us how we can rewrite it.We then define
Program
using the first two combinations and returndata Program a where PutThen :: Char -> Program a -> Program a GetBind :: (Maybe Char -> Program a) -> Program a Return :: a -> Program a
Observe that the data type is a regular Haskell data type and it does not use any of the features of a GADT.
One way to think about
PutThen
andGetBind
is with continuations. For instance,PutThen c p
writes a character into the output of the program and continues behaving asp
. Similarly,Get f
reads maybe a charactermc
from the input and continues behaving as programf mc
.putC :: Char -> Program () putC c = PutThen c $ Return ()
Function
putC
writes a character in the output and then it behaves asReturn ()
getC :: Program (Maybe Char) getC = GetBind Return
Function
getC
reads maybe a character from the input and, once that is done, it behaves asReturn ()
The bind is not going to be a part of the
Program
data structure, but rather part of theinstance Monad
, i.e., thebind
is not deeply implemented as a constructor (intermediate embedding)
Calculating (>>=)
for Program
as a monad (intermediate embedding)
What is the definition for bind?
instance Monad Program where return = Return (>>=) = bindP bindP :: Program a -> (a -> Program b) -> Program b bindP (PutThen c p) k = ? bindP (GetBind f) k = ? bindP (Return x) k = ?
We can *calculate* the correct definition of bindP using the definitions of `PutThen`, `GetBind`, and the monadic laws!bindP (Return x) k = ?
bindP (Return x) k = Def. >>= (Return x) >>= k = Law 1. return x >>= f ≡ f x k x
bindP (Return x) k = k x
bindP (GetBind f) k = ?
bindP (GetBind f) k = Def. of (>>=) (GetBind f) >>= k = Def. GetBind (Get >>= f) >>= k = Law 3. (m >>= f) >>= g == m >>= (\x -> f x >>= g) with m = Get, f = f, g = k Get >>= (\x -> f x >>= k) = Def. GetBind GetBind (\x -> f x >>= k) = Def. of (>>=) GetBind (\x -> bindP (f x) k)
bindP (GetBind f) k = GetBind (\x -> bindP (f x) k)
bindP (PutThen c p) k = ?
bindP (PutThen c p) k = { Def. of (>>=) } (PutThen c p) >>= k = { Def. of PutThen } (Put c >> p) >>= k = (Put c >>= \_ -> p) >>= k = Law3 with m = Put c, f = \_->p, g = k Put c >>= (\x -> (\_->p) x >>= k) = simplify Put c >>= (\_ -> p >>= k) = Def. of >> Put c >> (p >>= k) = Def. of PutThen PutThen c (p >>= k)
bindP (PutThen c p) k = PutThen c (bindP p k)
So, we can now complete defining
Program
as a monad-- | It turns out that bind can still be defined! instance Monad Program where return = Return (>>=) = bindP -- | Bind takes the first argument apart: bindP :: Program a -> (a -> Program b) -> Program b bindP (PutThen c p) k = PutThen c (bindP p k) bindP (GetBind f) k = GetBind (\x -> bindP (f x) k) bindP (Return x) k = k x
A simple monadic EDSL for input/output (shallow embedding)
- This is an exercise for you to do!
Monads
A structure that represents computations defined as sequences of steps.
The bind operator `(>>=)` defines what it means to chain operations of a monadic type.In this lecture, we will learn about two other structures useful in functional programming
- Functors
- Applicative functors
Structure-preserving mappings
We are familiar with the
map
function over listsmap (+1) [2,3,4,5,6]
which applies the function
(+1)
to every element of the list*, and produces the list[3,4,5,6,7]
We can generalize the concept of
map
to work on treesdata Tree a = Leaf a | Node (Tree a) (Tree a) mapTree :: (a -> b) -> Tree a -> Tree b mapTree f (Leaf a) = Leaf (f a) mapTree f (Node t1 t2) = Node (mapTree f t1) (mapTree f t2)
As we did with lists, we can apply the function
(+1)
at every element of the data structure.For instance,
mapTree (+1) $ Node (Leaf 2) (Node (Node (Leaf 3) (Leaf 4)) (Leaf 5))
produces the following tree.
Node (Leaf 3) (Node (Node (Leaf 4) (Leaf 5)) (Leaf 6))
In both cases, the structure of the data type (i.e., lists and trees) is preserved
General pattern:
It is useful to apply functions to data types elements while respecting the structure (shape) of it
Functors
A functor is composed of two elements: a data type definition (container) and a generalized
map
-function calledfmap
.In Haskell,
fmap
is an overloaded function, i.e., defined for every container which supports amap
-like operation.class Functor d where fmap :: (a -> b) -> d a -> d b
A functor must obey the following laws.
Name Law Identity: fmap id ≡ id
Map fusion (or composition): fmap (f . g) ≡ fmap f . fmap g
Let us consider again the
Tree
exampleinstance Functor Tree where fmap f (Leaf a) = Leaf (f a) fmap f (Node t1 t2) = Node (fmap f t1) (fmap f t2)
Now, we can write
(+1) `fmap` (Node (Leaf 2) ((Node (Node (Leaf 3) (Leaf 4)) (Leaf 5))))
Functors: more examples
Maybe
data type(+1) `fmap` (Just 10)
Generalized trees
data TreeG a = LeafG a | BranchG [TreeG a] instance Functor TreeG where fmap f (LeafG a) = LeafG (f a)
What about
BranchG
? We will use thefmap
from lists!fmap f (BranchG ts) = BranchG (fmap (fmap f) ts)
The outermost
fmap
is the one corresponding to lists.For instance, the expression
(+1) `fmap` BranchG [LeafG 10, BranchG [LeafG 11, LeafG 12], BranchG [LeafG 13, LeafG 14, LeafG 15]]
produces
BranchG [LeafG 11, BranchG [LeafG 12, LeafG 13], BranchG [LeafG 14, LeafG 15, LeafG 16]]
To summarize:
Functors simplifies boilerplate code, i.e., destructing a container in order to create another one!As data types can be built from other ones, so do functors! (thus achieving modularity)
Multi-parameter functions map to multiple containers
In a more general case, sometimes we would like to transform elements in a container (data type) based on applying a "multi-parameter function" to multiple containers (the quotes are there since in Haskell every function has exactly one argument due to curryfication)
Keep in mind that
fmap
takes a function of typea -> b
and not "multi-parameter" ones, e.g.,a -> b -> c
Let us take as an example to see what happens when
fmap
is used with a "multi-parameter" function.mp_fmap :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c mp_fmap f ma mb = let m_b_to_c = fmap f ma in undefined
Once we apply
fmap
to the first container, we have a container (m_b_to_c
) with a function of typeb -> c
in it.To keep applying
f
, what we need to do is to take its partial application out of the containerm_b_to_c
and mapped overmb
, where its next argument is located.mp_fmap :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c mp_fmap f ma mb = let m_b_to_c = fmap f ma in case m_b_to_c of Nothing -> Nothing Just fa -> fmap fa mb
What happens if function
f
had more arguments?mp_fmap2 :: (a -> b -> c -> d) -> Maybe a -> Maybe b -> Maybe c -> Maybe d mp_fmap2 f ma mb mc = case fmap f ma of Nothing -> Nothing Just fa -> case fmap fa mb of Nothing -> Nothing Just fab -> fmap fab mc
We would need to implement more code to extract partial application of functions out from containers, applied them, and wrap the result in another container!
Applicative functors are conceived to do precisely this work!
Applicative functors
An applicative functor (or functor with application) is a functor with the following operations
class Functor d => Applicative d where pure :: a -> d a (<*>) :: d (a -> b) -> d a -> d b
Observe that an applicative functor is a functor
The pure operation creates a container with the given argument. The interesting operation is "application"
(<*>)
, which we can describe it graphically as follows:It takes a container of functions and a container of arguments and returns a container of the result of applying such functions.
An applicative functor must obey the following laws
Name Law Identity: pure id <*> vv ≡ vv
Composition: pure (.) <*> ff <*> gg <*> zz ≡ ff <*> (gg <*> zz)
Homomorphism: pure f <*> pure v ≡ pure (f v)
Interchange: ff <*> pure v ≡ pure ($ v) <*> ff
In the rules above, double letters indicate that the denoted element is in a container, e.g.,
ff
means that it is a functionf
inside a container,vv
is a value which is inside a container and so on.One of the most interesting rules is interchange. Before explaining it, let us see the types of the expressions involved.
ff :: d (a -> b) vv :: d a pure ($ v) :: d ((a -> b) -> b)
The rule says that instead of obtaining a
d b
asff <*> pure v
, whereff
is a container with a function andpure v
is its argument, it is possible to apply function($ v)
to the containerff
.
Applicative Maybe
Let us go back to our example using
Maybe
instance Functor Maybe where fmap f Nothing = Nothing fmap f (Just a) = Just (f a) instance Applicative Maybe where pure = Just Nothing <*> vv = Nothing Just f <*> vv = fmap f vv
What can we do now with that?
-- xx :: Maybe String -- yy :: Maybe String pure (++) <*> xx <*> yy
We can apply concatenation on strings stored in containers. All the wrapping and unwrapping is handled by the applicative functor.
A common usage pattern of applicative functors is as follows.
pure f <*> xx <*> yy <*> zz ...
More precisely, a function
f
in a container as the leftmost term follow by its container arguments!To make this pattern to look better, the applicative interface provides a derived operation called
(<$>)
which removes thepure
from the leftmost term.(<$>) :: Functor d => (a -> b) -> d a -> d b
So, the expression
pure f <*> xx <*> yy <*> zz ...
becomes
f <$> xx <*> yy <*> zz ...
Relation to monads
Observe what we have written using the applicative functor
Maybe
pure (++) <*> xx <*> yy
If we consider
Maybe
as a monad instead (which we defined in the previous lecture), we can achieve the same things.do x <- xx y <- yy return (x ++ y)
What is the difference between
Maybe
as an applicative functor or a monad?In the case above, both programs produce the same result (
x++y
). Observe thatx
gets bound but it is not used until thereturn
instruction — the same occurs withy
. However, the effects in a monadic program or an applicative one could be run in a different order.The difference between monad and applicative functors is the difference between *sequential* vs. *parallel* execution of side-effects.To appreciate this difference, let us consider a dramatic side-effect: launching a missile. We need to write a program which launches two missiles to a given target.
Monadic code
The side-effects are sequentially executed!Applicative code
The applicative structure does not impose an order on the execution of the container arguments. Observe that the effects could be run in parallel if possible.
Let's see the types closely
What is better? Monads, Applicative Functors?
FUNCTIONAL PEARL Applicative programming with effects by C. McBride and R. Paterson
The moral is this: if you’ve got an Applicative functor, that’s good; if you’ve also got a Monad, that’s even better! And the dual of the moral is this: if you want a Monad, that’s good; if you only want an Applicative functor, that’s even better!Theory can prove that every monad is an applicative functor and that every applicative functor is a functor.From GHC 7.10, if you define a monad, i.e., give an instance of the type class
Monad
, you also need to give an instance ofApplicative
andFunctor
class Functor d => Applicative d where class Applicative d => Monad d where
In GHC 7.8, you get a warning but your program still compiles. For more information check the Functor-Applicative-Monad proposal.
Not a functor
Not every data type is a functor
type NotAFunctor = Equal newtype Equal a = Equal {runEqual :: a -> a -> Bool} fmapEqual :: (a -> b) -> Equal a -> Equal b fmapEqual _f (Equal _op) = Equal $ \_b1 _b2 -> error "Hopeless!"
What is the problem?
Values of type
a
are in "negative position", i.e., they are given to the function (not produced by it).
A functor, not applicative
Not every functor is applicative
data Pair r a = P r a instance Functor (Pair r) where fmap f (P r a) = P r (f a)
Observe that the value of type
r
is kept as it is in the container (the functor does not create new elements, but modify existing ones)If we want to create a container, we need an
r
butpure
only receives ana
instance Applicative (Pair r) where pure x = P (error "Hopeless!") x f <*> v = error "Hopeless!"
Applicative, not a monad
Not every applicative functor is a monad
To show that, we need some preliminaries.
Every monoid is a phantom applicative functor
newtype Phantom o a = Phantom o
Here, the type
o
is an element from a monoid. Roughly speaking, a monoid is a set of elements which contains a neutral element and an operation between the elements of such set.mempty :: o mappend :: o -> o -> o
The neutral element has no effect on the result produced by
mappend
, i.e.,mappend mempty o == o
andmappend o mempty == o
We declare
Phantom
to be a functor and an applicative functor as follows.instance Functor (Phantom o) where fmap f (Phantom o) = Phantom o instance Monoid o => Applicative (Phantom o) where pure x = Phantom mempty Phantom o1 <*> Phantom o2 = Phantom (mappend o1 o2)
Observe that every application of
<*>
appliesmappend
.To make this idea more concrete, let us define a concrete monoid: natural numbers.
data Nat = Zero | Suc Nat instance Monoid Nat where mempty = Zero mappend Zero m = m mappend (Suc n) m = Suc (mappend n m)
Function
mappend
is simply addition.Let us define the
Phantom
number one.onePhantom :: Phantom Nat Int onePhantom = Phantom (Suc Zero)
In some cases, when
onePhantom
is applied to an applicative function, it counts the total number of its occurrences.(\x y -> x) <$> onePhantom <*> onePhantom > Phantom (Suc (Suc Zero))
Let us try to define
Phantom Nat
as a monadinstance Monad (Phantom Nat) where return = pure
The interesting case is
(>>=)
Phantom n >>= k = ?
Observe that
n :: Nat
andk
is waiting for an argument of typea
and we have none! To make our instance type-checked, we ignorek
.Phanton n >>= k = Phanton m where m = ...
You are free to choose the
m
in the returnedPhantom
!By the left identity rule for Monads, we have that
return x >>= k ≡ k x
By the definition of
(>>=)
above, we know thatreturn x >>= k ≡ Phantom m
By combining these two equations, we have that
Phantom m ≡ k x
Then, it is easy to come up with a function
k
where this equation does not hold. For instance,k = \_ -> ((\x1 x2 .. xm xm1) -> x1) <$> onePhantom <*> .. <*> onePhantom
In other words,
k
is returningPhantom (Suc m)
which is different fromPhantom m
. Contradiction! Therefore,Phantom Nat
cannot be a monad.
Structures learned so far
Monads
Sequential construction of programs
Useful to implement side-effects (e.g., error handling, logging, stateful computations, etc.).
- Simplify code, i.e., it hides plumbing needed to handle the side-effects.
Applicative functors
Useful to apply "multi-parameter" functions to multiple container arguments.
- Simplify code, i.e., it hides the plumbing needed to take out functions and their arguments from containers, applying the function, and place the result back in a container.
Side-effects could potentially be executed in parallel.
They are more generic than monads.
Functors
Useful to map functions into containers, i.e., transform data inside containers without breaking them.
- Simplify code, i.e., it hides the plumbing of destructing the container to obtain the value, apply the function, and put the result in a container.
The most general structure