126

Applicatives compose, monads don't.

What does the above statement mean? And when is one preferable to other?

imz -- Ivan Zakharyaschev
  • 4,921
  • 6
  • 53
  • 104
missingfaktor
  • 90,905
  • 62
  • 285
  • 365
  • 6
    From where do you got this statement? It may be helpful to see some context. – fuz Aug 12 '11 at 13:43
  • @FUZxxl: I have heard it repeatedly from many different people, recently from debasishg on twitter. – missingfaktor Aug 12 '11 at 13:54
  • Concerning the second question. There aren't many general structures that are applicatives but not monads. The multiple error applicative in Conor McBride and Ross Paterson's paper is one. There are some specific structures that are applicative not monad where they can be optimized if they are just applicative - Doaiste Swierstra's parser combinators are one, and Chalkboard's `Active` type another. – stephen tetley Aug 12 '11 at 15:15
  • 3
    @stephen tetley: Note that many such `Applicative`s are actually a whole *family* of `Monad`s, namely one for each "shape" of structure possible. `ZipList` isn't a `Monad`, but `ZipList`s of a fixed length are. `Reader` is a convenient special (or is it general?) case where the size of the "structure" is fixed as the cardinality of the environment type. – C. A. McCann Aug 12 '11 at 16:09
  • 3
    @C.A.McCann All those zippy applicatives (whether they truncate or pad) restrict to monads if you fix the shape in a way that amounts to a `Reader` monad up to isomorphism. Once you fix the shape of a container, it effectively encodes a function from positions, like a memo trie. Peter Hancock calls such functors "Naperian", as they obey laws of logarithms. – pigworker Aug 12 '11 at 17:56
  • 4
    @stephen tetley: Other examples include the constant-monoid applicative (which is a composition of monads but not a monad), and the unit-delay applicative (which had better not admit join). – pigworker Aug 12 '11 at 18:01

7 Answers7

125

If we compare the types

(<*>) :: Applicative a => a (s -> t) -> a s -> a t
(>>=) :: Monad m =>       m s -> (s -> m t) -> m t

we get a clue to what separates the two concepts. That (s -> m t) in the type of (>>=) shows that a value in s can determine the behaviour of a computation in m t. Monads allow interference between the value and computation layers. The (<*>) operator allows no such interference: the function and argument computations don't depend on values. This really bites. Compare

miffy :: Monad m => m Bool -> m x -> m x -> m x
miffy mb mt mf = do
  b <- mb
  if b then mt else mf

which uses the result of some effect to decide between two computations (e.g. launching missiles and signing an armistice), whereas

iffy :: Applicative a => a Bool -> a x -> a x -> a x
iffy ab at af = pure cond <*> ab <*> at <*> af where
  cond b t f = if b then t else f

which uses the value of ab to choose between the values of two computations at and af, having carried out both, perhaps to tragic effect.

The monadic version relies essentially on the extra power of (>>=) to choose a computation from a value, and that can be important. However, supporting that power makes monads hard to compose. If we try to build ‘double-bind’

(>>>>==) :: (Monad m, Monad n) => m (n s) -> (s -> m (n t)) -> m (n t)
mns >>>>== f = mns >>-{-m-} \ ns -> let nmnt = ns >>= (return . f) in ???

we get this far, but now our layers are all jumbled up. We have an n (m (n t)), so we need to get rid of the outer n. As Alexandre C says, we can do that if we have a suitable

swap :: n (m t) -> m (n t)

to permute the n inwards and join it to the other n.

The weaker ‘double-apply’ is much easier to define

(<<**>>) :: (Applicative a, Applicative b) => a (b (s -> t)) -> a (b s) -> a (b t)
abf <<**>> abs = pure (<*>) <*> abf <*> abs

because there is no interference between the layers.

Correspondingly, it's good to recognize when you really need the extra power of Monads, and when you can get away with the rigid computation structure that Applicative supports.

Note, by the way, that although composing monads is difficult, it might be more than you need. The type m (n v) indicates computing with m-effects, then computing with n-effects to a v-value, where the m-effects finish before the n-effects start (hence the need for swap). If you just want to interleave m-effects with n-effects, then composition is perhaps too much to ask!

pigworker
  • 43,025
  • 18
  • 121
  • 214
  • 3
    For the iffy example you state that it "uses the value of ab to choose between the values of two computations at and af, having carried out both, perhaps to tragic effect." Doesn't the lazy nature of Haskell protect you against this? If I have list = (\b t f -> if b then t else f) : [] and then execute the statement: list <*> pure True <*> pure "hello" <*> pure (error "bad")....I get "hello" and the error never occurs. This code isn't nearly as safe or controlled as a monad, but the post seems like it's suggesting that applicatives cause strict evaluation. Overall great post though! Thanks! – shj Feb 29 '12 at 05:37
  • 9
    You still get the *effects* of both, but pure (error "bad") doesn't have any. If, on the other hand, you try iffy (pure True) (pure "hello") (error "bad"), you get an error which miffy avoids. Moreover, if you try something like iffy (pure True) (pure 0) [1,2], you'll get [0,0] instead of [0]. Applicatives have a kind of strictness about them, in that they build fixed sequences of computations, but the *values* resulting from those computations are still combined lazily, as you observe. – pigworker Mar 01 '12 at 09:32
  • Is it true, that for any monads `m` and `n` you can always write a monad transformer `mt`, and operate in `n (m t)` using `mt n t`? So you can always compose monads, it is just more complicated, using transformers? – ron Jun 19 '12 at 11:11
  • 4
    Such transformers often exist, but as far as I know, there's no canonical way of generating them. There's often a genuine choice about how to resolve interleaved effects from the different monads, the classic example being exceptions and state. Should an exception roll back state changes or not? Both choices have their place. Having said that, there's a "free monad" thing that expresses "arbitrary interleaving". `data Free f x = Ret x | Do (f (Free f x))`, then `data (:+:) f g x = Inl (f x) | Tnr (g x)`, and consider `Free (m :+: n)`. That delays the choice of how to run interleavings. – pigworker Jun 19 '12 at 11:26
  • @pigworker Concerning the lazy/strict debate. I think that with applicatives you cannot control the effect from *within* the computation, but the *effect-layer* can very well decide not to evaluate later values. For (applicative) parsers this means that if the parser fails early, subsequent parsers are not evaluated/applied to the input. For `Maybe` this means that an early `Nothing` will suppress the evaluation of the `a` of a later/subsequent `Just a`. Is this correct? – ziggystar Oct 15 '15 at 14:07
  • @ziggystar Yes. What can't happen is that the values from earlier computations determine the choice of later computations. How lazy or strict the execution of computations might be is entirely another matter. – pigworker Oct 15 '15 at 20:03
  • I thought I understood Applicatives, but this post cured me of my folly. – Arek' Fu Sep 15 '16 at 06:18
  • @pigworker, how does `error "bad"` not have any effects? I'm stumped. Can you please define "effects"? – Arek' Fu Sep 15 '16 at 06:20
  • 1
    @Arek'Fu you've neglected the `pure'. It's pure (error "bad") that has no effects, or any pure (anything) for that matter. – ivan vadovič Aug 06 '18 at 18:25
88

Applicatives compose, monads don't.

Monads do compose, but the result might not be a monad. In contrast, the composition of two applicatives is necessarily an applicative. I suspect the intention of the original statement was that "Applicativeness composes, while monadness doesn't." Rephrased, "Applicative is closed under composition, and Monad is not."

Conal
  • 18,517
  • 2
  • 37
  • 40
  • 26
    Additionally, any two applicatives compose in a completely mechanical way, whereas the monad formed by the composition of two monads is specific to that composition. – Apocalisp Aug 15 '11 at 20:26
  • 14
    Moreover monads compose in other ways, the product of two monads is a monad, it is only the coproducts that need some kind of distributive law. – Edward Kmett Aug 16 '11 at 01:38
  • 1
    With, @Apocalisp, comment included, this is the best and most concise answer. – Paul Draper Jul 18 '15 at 03:09
43

If you have applicatives A1 and A2, then the type data A3 a = A3 (A1 (A2 a)) is also applicative (you can write such an instance in a generic way).

On the other hand, if you have monads M1 and M2 then the type data M3 a = M3 (M1 (M2 a)) is not necessarily a monad (there is no sensible generic implementation for >>= or join for the composition).

One example can be the type [Int -> a] (here we compose a type constructor [] with (->) Int, both of which are monads). You can easily write

app :: [Int -> (a -> b)] -> [Int -> a] -> [Int -> b]
app f x = (<*>) <$> f <*> x

And that generalizes to any applicative:

app :: (Applicative f, Applicative f1) => f (f1 (a -> b)) -> f (f1 a) -> f (f1 b)

But there is no sensible definition of

join :: [Int -> [Int -> a]] -> [Int -> a]

If you're unconvinced of this, consider this expression:

join [\x -> replicate x (const ())]

The length of the returned list must be set in stone before an integer is ever provided, but the correct length of it depends on the integer that's provided. Thus, no correct join function can exist for this type.

Rotsor
  • 13,655
  • 6
  • 43
  • 57
  • 1
    ...so avoid monads when a function will do? – andrew cooke Aug 12 '11 at 13:49
  • 2
    @andrew, if you meant functor, then yes, functors are simpler and should be used when sufficient. Note that it's not always. For example `IO` without a `Monad` would be very hard to program. :) – Rotsor Aug 12 '11 at 14:05
18

Unfortunately, our real goal, composition of monads, is rather more difficult. .. In fact, we can actually prove that, in a certain sense, there is no way to construct a join function with the type above using only the operations of the two monads (see the appendix for an outline of the proof). It follows that the only way that we might hope to form a composition is if there are some additional constructions linking the two components.

Composing monads, http://web.cecs.pdx.edu/~mpj/pubs/RR-1004.pdf

Landei
  • 54,104
  • 13
  • 100
  • 195
  • 4
    Tl;dr for impatient readers: you can compose monads if(f?) you can provide a natural transformation `swap : N M a -> M N a` – Alexandre C. Aug 12 '11 at 13:56
  • @Alexandre C.: Just "if", I suspect. Not all monad transformers are described by direct functor composition. For instance, `ContT r m a` is neither `m (Cont r a)` nor `Cont r (m a)`, and `StateT s m a` is roughly `Reader s (m (Writer s a))`. – C. A. McCann Aug 12 '11 at 16:05
  • @C. A. McCann: I can't seem to get from (M monad, N monad, MN monad, NM monad) to (there exists swap : MN -> NM natural). So let's stick to "if" for now (perhaps the answer is in the paper, I must confess I looked it up quickly) – Alexandre C. Aug 12 '11 at 16:11
  • 1
    @Alexandre C.: Just specifying that the compositions are monads may not be enough anyway--you also need some way to relate the two parts with the whole. The existence of `swap` implies that the composition lets the two "cooperate" somehow. Also, note that `sequence` is a special case of "swap" for some monads. So is `flip`, actually. – C. A. McCann Aug 12 '11 at 16:20
  • 7
    To write `swap :: N (M x) -> M (N x)` it looks to me like you can use `returns` (suitably `fmap`ped) to insert an `M` at the front and an `N` at the back, going from `N (M x) -> M (N (M (N x)))`, then use the `join` of the composite to get your `M (N x)`. – pigworker Aug 12 '11 at 16:26
  • @C. A. McCann: I get your point, but I fail to see how `flip` is a special case of `swap`. `sequence` makes sense to me however. – Alexandre C. Aug 12 '11 at 16:28
  • @Alexandre C.: Think of it as `flip :: (->) a ((->) b c) -> (->) b ((->) a c)`. In other words, `swap` used on two reader monads. – C. A. McCann Aug 12 '11 at 16:39
7

The distributive law solution l : MN -> NM is enough

to guarantee monadicity of NM. To see this you need a unit and a mult. i'll focus on the mult (the unit is unit_N unitM)

NMNM - l -> NNMM - mult_N mult_M -> NM

This does not guarantee that MN is a monad.

The crucial observation however, comes into play when you have distributive law solutions

l1 : ML -> LM
l2 : NL -> LN
l3 : NM -> MN

thus, LM, LN and MN are monads. The question arises as to whether LMN is a monad (either by

(MN)L -> L(MN) or by N(LM) -> (LM)N

We have enough structure to make these maps. However, as Eugenia Cheng observes, we need a hexagonal condition (that amounts to a presentation of the Yang-Baxter equation) to guarantee monadicity of either construction. In fact, with the hexagonal condition, the two different monads coincide.

user278559
  • 121
  • 4
  • 10
    This is probably a great answer, but it went *whoosh* way over my head. – Dan Burton Aug 16 '11 at 02:35
  • 1
    That's because, using the term Applicative and haskell tag, this is a question about haskell but with an answer in a different notation. – codeshot Dec 23 '17 at 06:45
2

Any two applicative functors can be composed and yield another applicative functor. But this does not work with monads. A composition of two monads is not always a monad. For example, a composition of State and List monads (in any order) is not a monad.

Moreover, one cannot combine two monads in general, whether by composition or by any other method. There is no known algorithm or procedure that combines any two monads M, N into a larger, lawful monad T so that you can inject M ~> T and N ~> T by monad morphisms and satisfy reasonable non-degeneracy laws (e.g., to guarantee that T is not just a unit type that discards all effects from M and N).

It is possible to define a suitable T for specific M and N, for example of M = Maybe and N = State s and so on. But it is unknown how to define T that would work parametrically in the monads M and N. Neither functor composition, nor more complicated constructions work adequately.

One way of combining monads M and N is first, to define the co-product C a = Either (M a) (N a). This C will be a functor but, in general, not a monad. Then one constructs a free monad (Free C) on the functor C. The result is a monad that is able to represent effects of M and N combined. However, it is a much larger monad that can also represent other effects; it is much larger than just a combination of effects of M and N. Also, the free monad will need to be "run" or "interpreted" in order to extract any results (and the monad laws are guaranteed only after "running"). There will be a run-time penalty as well as memory size penalty because the free monad will potentially build very large structures in memory before it is "run". If these drawbacks are not significant, the free monad is the way to go.

Another way of combining monads is to take one monad's transformer and apply it to the other monad. But there is no algorithmic way of taking a definition of a monad (e.g., type and code in Haskell) and producing the type and code of the corresponding transformer.

There are at least 4 different classes of monads whose transformers are constructed in completely different but regular ways (composed-inside, composed-outside, adjunction-based monad, product monad). A few other monads do not belong to any of these "regular" classes and have transformers defined "ad hoc" in some way.

Distributive laws exist only for composed monads. It is misleading to think that any two monads M, N for which one can define some function M (N a) -> N (M a) will compose. In addition to defining a function with this type signature, one needs to prove that certain laws hold. In many cases, these laws do not hold.

There are even some monads that have two inequivalent transformers; one defined in a "regular" way and one "ad hoc". A simple example is the identity monad Id a = a; it has the regular transformer IdT m = m ("composed") and the irregular "ad hoc" one: IdT2 m a = forall r. (a -> m r) -> m r (the codensity monad on m).

A more complicated example is the "selector monad": Sel q a = (a -> q) -> a. Here q is a fixed type and a is the main type parameter of the monad Sel q. This monad has two transformers: SelT1 m a = (m a -> q) -> m a (composed-inside) and SelT2 m a = (a -> m q) -> m a (ad hoc).

Full details are worked out in Chapter 14 of the book "The Science of Functional Programming". https://github.com/winitzki/sofp or https://leanpub.com/sofp/

winitzki
  • 3,179
  • 24
  • 32
0

Here is some code making monad composition via a distributive law work. Note that there are distributive laws from any monad to the monads Maybe, Either, Writer and []. On the other hand, you won't find such (general) distributive laws into Reader and State. For these, you will need monad transformers.

 {-# LANGUAGE FlexibleInstances #-}
 
 module ComposeMonads where
 import Control.Monad
 import Control.Monad.Writer.Lazy
 
 newtype Compose m1 m2 a = Compose { run :: m1 (m2 a) }
 
 instance (Functor f1, Functor f2) => Functor (Compose f1 f2) where
   fmap f = Compose . fmap (fmap f) . run
 
 class (Monad m1, Monad m2) => DistributiveLaw m1 m2 where
   dist :: m2 (m1 a) -> m1 (m2 a)
 
 instance (Monad m1,Monad m2, DistributiveLaw m1 m2)
           => Applicative (Compose m1 m2) where
     pure = return
     (<*>) = ap
 
 instance (Monad m1, Monad m2, DistributiveLaw m1 m2)
           => Monad (Compose m1 m2) where
   return = Compose . return . return
   Compose m1m2a >>= g =
     Compose $ do m2a <- m1m2a -- in monad m1
                  m2m2b <- dist $ do a <- m2a  -- in monad m2
                                     let Compose m1m2b = g a
                                     return m1m2b
                                  -- do ... ::  m2 (m1 (m2 b))
                           -- dist ... :: m1 (m2 (m2 b))          
                  return $ join m2m2b -- in monad m2
 
 instance Monad m => DistributiveLaw m Maybe where
   dist Nothing = return Nothing
   dist (Just m) = fmap Just m
 
 instance Monad m => DistributiveLaw m (Either s) where
   dist (Left s) = return $ Left s
   dist (Right m) = fmap Right m
 
 instance Monad m => DistributiveLaw m [] where
   dist = sequence
 
 instance (Monad m, Monoid w) => DistributiveLaw m (Writer w) where
   dist m = let (m1,w) = runWriter m
            in do a <- m1
                  return $ writer (a,w)
 
 liftOuter :: (Monad m1, Monad m2, DistributiveLaw m1 m2) =>
                    m1 a -> Compose m1 m2 a
 liftOuter = Compose . fmap return
 
 liftInner :: (Monad m1, Monad m2, DistributiveLaw m1 m2) =>
                    m2 a -> Compose m1 m2 a
 liftInner = Compose . return
 
 
   
 
tillmo
  • 607
  • 5
  • 11