Commutative monads vs Applicative functors

From what I have read about applicative functors, they are weaker than monads because with a monad, I can use the results of a computation to select between alternative future computations and their side effects, whereas with an applicative functor, I can only select between the results of computations, while the structure of those computations and
I have a few questions about commutative monads and applicative functors. their side effects are fixed in advance. But then there are commutative monads. I'm not exactly sure what a commutative monad is, but my understanding is that in a commutative monad the order of side effects does not matter. This leads me to wonder, are commutative monads still stronger than applicative functors, or are they equivalent? And by the way, what exactly is a commutative monad?

Hello, On 14 May 2008, at 02:06, Ronald Guida wrote:
I have a few questions about commutative monads and applicative functors.
From what I have read about applicative functors, they are weaker than monads because with a monad, I can use the results of a computation to select between alternative future computations and their side effects, whereas with an applicative functor, I can only select between the results of computations, while the structure of those computations and their side effects are fixed in advance.
But then there are commutative monads. I'm not exactly sure what a commutative monad is, but my understanding is that in a commutative monad the order of side effects does not matter.
This leads me to wonder, are commutative monads still stronger than applicative functors, or are they equivalent?
I would say that they are stronger because they still support: concat :: Monad m => m (m a) -> m a or (>>=) :: Monad m => m a -> (a -> m b) -> m b which are not supported, in general, by applicative functors. In fact, I would probably risk to say that they are even stronger than monads (as there are less commutative monads than regular monads).
And by the way, what exactly is a commutative monad?
Here is a possible characterization: The monad m is commutative if, for all mx and my: do {x <- mx; y <- my; return (x,y)} = do {y <- my; x <- mx; return (x,y)} As you mentioned above, the basic idea is that the order of the side effects does not matter. This law is not true in general for monads. I am not sure if you know about the paper entitled "The essence of the Iterator Pattern" (by Jeremy Gibbons and myself): http://www.comlab.ox.ac.uk/people/Bruno.Oliveira/iterator-jfp.pdf But, you may be interested to read it as it discusses related ideas. In particular you may want to take a look at Section 5.4. Cheers, Bruno

Ronald Guida wrote:
From what I have read about applicative functors, they are weaker than monads because with a monad, I can use the results of a computation to select between alternative future computations and their side effects, whereas with an applicative functor, I can only select between the results of computations, while the structure of those computations and their side effects are fixed in advance.
If you are not already aware of them, you might be interested in the following two papers: http://homepages.inf.ed.ac.uk/wadler/papers/arrows-and-idioms/arrows-and-idi... http://homepages.inf.ed.ac.uk/wadler/papers/arrows/arrows.pdf ("idioms" is a synonym for "applicative functors", and both papers also discuss the relation to monads.) Ciao, Janis. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de

On Tue, May 13, 2008 at 9:06 PM, Ronald Guida
I have a few questions about commutative monads and applicative functors.
From what I have read about applicative functors, they are weaker than monads because with a monad, I can use the results of a computation to select between alternative future computations and their side effects, whereas with an applicative functor, I can only select between the results of computations, while the structure of those computations and their side effects are fixed in advance.
But then there are commutative monads. I'm not exactly sure what a commutative monad is, but my understanding is that in a commutative monad the order of side effects does not matter.
This leads me to wonder, are commutative monads still stronger than applicative functors, or are they equivalent?
And by the way, what exactly is a commutative monad?
A monad is commutative if the expression "a >>= \x -> b >>= \y -> f x
y" is equivalent to "b >>= \y -> a >>= \x -> f x y". The identity,
state reader, and maybe monads are commutative, for example.
To put it another way, a monad is commutative if
liftM2 f a b = liftM2 (flip f) b a
Since liftA2 generalizes liftM2, we can also say that an applicative
functor is commutative if
liftA2 f a b = liftA2 (flip f) b a
Or, put another way, if
a <*> b = flip ($) <$> b <*> a
If w is a commutative monoid (that is, if mappend w1 w2 == mappend w2
w1), then Const w is a commutative applicative functor.
To summarize: some applicative functors are commutative, some
applicative functors are monads, and the ones that are both are
commutative monads.
--
Dave Menendez

David Menendez wrote:
To summarize: some applicative functors are commutative, some applicative functors are monads, and the ones that are both are commutative monads.
OK, so commutativity is orthogonal to "idiom vs monad". Commutativity depends on whether or not the order of side effects is important. Being a monad or just an idiom depends on whether or not "join" is supported. Examples can be constructed for all 4 possibilities of {idiom, monad} (x) {non-commutative, commutative}. Thank you all for clearing this up for me.

On Wed, 14 May 2008, David Menendez wrote:
On Tue, May 13, 2008 at 9:06 PM, Ronald Guida
wrote: I have a few questions about commutative monads and applicative functors.
From what I have read about applicative functors, they are weaker than monads because with a monad, I can use the results of a computation to select between alternative future computations and their side effects, whereas with an applicative functor, I can only select between the results of computations, while the structure of those computations and their side effects are fixed in advance.
But then there are commutative monads. I'm not exactly sure what a commutative monad is, but my understanding is that in a commutative monad the order of side effects does not matter.
This leads me to wonder, are commutative monads still stronger than applicative functors, or are they equivalent?
And by the way, what exactly is a commutative monad?
Interestingly I used a Writer monad with a commutative monoid recently, which is also an example of a commutative monad.

Eight years later, I stumbled across this thread. Here's a cute way to express commutativity of an applicative functor:
forall f. flip (liftA2 f) == liftA2 (flip f)
Cuter yet,
flip . liftA2 == liftA2 . flip
-- Conal
On Wed, May 14, 2008 at 9:59 AM, David Menendez
On Tue, May 13, 2008 at 9:06 PM, Ronald Guida
wrote: I have a few questions about commutative monads and applicative functors.
From what I have read about applicative functors, they are weaker than monads because with a monad, I can use the results of a computation to select between alternative future computations and their side effects, whereas with an applicative functor, I can only select between the results of computations, while the structure of those computations and their side effects are fixed in advance.
But then there are commutative monads. I'm not exactly sure what a commutative monad is, but my understanding is that in a commutative monad the order of side effects does not matter.
This leads me to wonder, are commutative monads still stronger than applicative functors, or are they equivalent?
And by the way, what exactly is a commutative monad?
A monad is commutative if the expression "a >>= \x -> b >>= \y -> f x y" is equivalent to "b >>= \y -> a >>= \x -> f x y". The identity, state reader, and maybe monads are commutative, for example.
To put it another way, a monad is commutative if
liftM2 f a b = liftM2 (flip f) b a
Since liftA2 generalizes liftM2, we can also say that an applicative functor is commutative if
liftA2 f a b = liftA2 (flip f) b a
Or, put another way, if
a <*> b = flip ($) <$> b <*> a
If w is a commutative monoid (that is, if mappend w1 w2 == mappend w2 w1), then Const w is a commutative applicative functor.
To summarize: some applicative functors are commutative, some applicative functors are monads, and the ones that are both are commutative monads.
-- Dave Menendez
http://www.eyrie.org/~zednenem/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (6)
-
Bruno Oliveira
-
Conal Elliott
-
David Menendez
-
Henning Thielemann
-
Janis Voigtlaender
-
Ronald Guida