Difference between revisions of "What a Monad is not"

From HaskellWiki
Jump to navigation Jump to search
(→‎Warning: Reverted "warm and fuzzy" link to archive version of the original. It's really really hand-holdy that's why I chose it. The other one is still nice and crisp for the more math-inclined mind.)
 
(59 intermediate revisions by 11 users not shown)
Line 1: Line 1:
In addition to Burritos, Monads aren't a couple of things:
 
 
 
==Warning==
 
==Warning==
  +
Don't be surprised if you leave this page more confused than before. That just means that it has successfully destroyed your false assumptions, or that you've fallen for some horrible inside joke. Beware of [[Zygohistomorphic prepromorphisms]]. Go for [https://web.archive.org/web/20120114225257/http://ertes.de/articles/monads.html warm and fuzzy], instead. Or [http://en.wikibooks.org/wiki/Haskell/Understanding_monads this one].
This page is currently an unprocessed braindump. Feel free to dump additional stuff or massage stuff into didactic pleasures.
 
  +
  +
==Monads are not a good choice as topic for your first Haskell blog entry==
  +
...just accept that they're [http://blog.plover.com/prog/burritos.html burritos], and wait until later.
   
 
==Monads are not a language feature==
 
==Monads are not a language feature==
Line 8: Line 9:
   
 
==Haskell doesn't need Monads==
 
==Haskell doesn't need Monads==
...well, apart from the Haskell standard defining the way IO is done in terms of Monads: It could be done differently and still work.
+
...well, apart from the current Haskell standard defining the way IO is done in terms of Monads: [http://donsbot.wordpress.com/2009/01/31/reviving-the-gofer-standard-prelude-circa-1994/ It could be done differently and still work].
   
 
==Monads are not impure==
 
==Monads are not impure==
...In no way whatsoever. You don't even need flexible morals to claim it. To be more specific, it's IO that's impure. That makes the IO monad impure. But that's not a general property of monads - just IO.
+
...In no way whatsoever. You don't even need flexible morals to claim it. To be more specific, it's IO that's impure. That makes the IO monad impure. But that's not a general property of monads - just IO. And even then, we can pretend that Haskell is a purely functional description language for imperative programs. But we didn't want to employ flexible morals, now did we?
   
 
==Monads are not about state==
 
==Monads are not about state==
While it is certainly possible to abstract away explicit state passing by using a Monad, that's not what a monad is.
+
While it is certainly possible to abstract away explicit state passing by using a Monad, that's not what a monad is. Some examples for monads that are not about state: Identity monad, Reader monad, List monad, Continuation monad, Exception monad.
   
 
==Monads are not about strictness==
 
==Monads are not about strictness==
  +
Monad operations (bind and return) have to be [[Non-strict semantics|non-strict]] in fact, always! However
There are monads that are strict (like IO), and monads that are lazy (like []). Then there are some that come in multiple flavours, like State.
 
  +
other operations can be specific to each monad.
 
For instance some are strict (like IO), and some are non-strict (like []). Then there are some that come in multiple flavours, like State.
  +
  +
Try the following:
  +
  +
<haskell>
  +
runState (sequence . repeat $ state (\x -> (x,x+1))) 0
  +
</haskell>
  +
  +
Having a look at the implementation of fixIO might be helpful, too.
   
 
==Monads are not values==
 
==Monads are not values==
 
This point might be driven home best by pointing out that instance Monad Foo where ... is not a data type, but a declaration of a typeclass instance. However, to elaborate:
 
This point might be driven home best by pointing out that instance Monad Foo where ... is not a data type, but a declaration of a typeclass instance. However, to elaborate:
   
Monads are not values in the same sense that addition and multiplication are not numbers: They capture a -- very specific -- relationship between values of a specific domain into a common abstraction. We're going to call these values monads manage ''mobits'', like this:
+
Monads are not values in the same sense that addition and multiplication are not numbers: They capture a -- very specific -- relationship between values of a specific domain into a common abstraction. We're going to call these values monads manage ''mobits'', somewhat like this:
   
  +
<haskell>
type Mobit a = Monad m => m a
+
type Mobit m a = Monad m => m a
  +
</haskell>
   
 
The IO monad manages mobits representing side-effects ("IO actions").
 
The IO monad manages mobits representing side-effects ("IO actions").
Line 32: Line 45:
 
The Reader monads manages mobits that are pure computations that use asks to propagate information instead of explicit arguments
 
The Reader monads manages mobits that are pure computations that use asks to propagate information instead of explicit arguments
   
...and while addition and multiplication are both monoids over the positive natural numbers, a monad is a monoid in a category of endofunctors. It's all very simple.
+
...and while addition and multiplication are both monoids over the positive natural numbers, a monad is a monoid object in a category of endofunctors: return is the unit, and join is the binary operation. It couldn't be more simple. If that confuses you, it might be helpful to see a Monad as a lax functor from a terminal bicategory.
 
 
   
 
==Monads are not a replacement for applicative functors==
 
==Monads are not a replacement for applicative functors==
 
Instead, every monad ''is'' an applicative functor (as well as a functor). It is considered good practice not to use >>= if all you need is <*>, or even fmap.
 
Instead, every monad ''is'' an applicative functor (as well as a functor). It is considered good practice not to use >>= if all you need is <*>, or even fmap.
   
Not confusing what features of monads are specific to monads only and which stem from applicative functors are vitally important for a deeper understanding of monads. As an example, the applicative functor interface of parser libraries can parse context-free grammars (and look just like EBNF), while the monadic interface can parse context-sensitive grammars: Monads allow you to influence further processing by inspecting the result of your parse. To understand why, have a look at the type of >>=. To understand why applicative functors by themselves are sufficient to track the current parsing position, have a look at the uu-parsinglib tutorial.
+
Not confusing which features of monads are specific to monads only and which stem from applicative functors is vitally important for a deeper understanding of monads. As an example, the applicative functor interface of parser libraries can parse context-free languages (modulo hacks abusing open recursion), while the monadic interface can parse context-sensitive grammars: Monads allow you to influence further processing by inspecting the result of your parse. To understand why, have a look at the type of >>=. To understand why applicative functors by themselves are sufficient to track the current parsing position and express sequencing, have a look at the [http://www.cs.uu.nl/research/techreps/repo/CS-2008/2008-044.pdf uu-parsinglib tutorial (pdf)].
   
 
The exact differences are elaborated in even greater detail in Brent Yorgey's excellent [[Typeclassopedia]].
 
The exact differences are elaborated in even greater detail in Brent Yorgey's excellent [[Typeclassopedia]].
  +
  +
==Monads are not about ordering/sequencing==
  +
Monads are commonly used to order sequences of computations. But this is misleading. Just as you can use monads for state, or strictness, you can use them to order computations. But there are also commutative monads, like Reader, that don't order anything. So ordering is not in any way essential to what a monad is.
  +
  +
Let's have a look at what's meant by ordering. Consider an expression like
  +
  +
<haskell>
  +
let x = a
  +
y = b
  +
in f x y
  +
</haskell>
  +
  +
That gives the same result as
  +
  +
<haskell>
  +
let y = b
  +
x = a
  +
in f x y
  +
</haskell>
  +
  +
It doesn't matter what order we write the two bindings. But for doing I/O we'd like ordering. Monads allow us to express
  +
  +
<haskell>
  +
do
  +
x <- getChar
  +
y <- getChar
  +
return (x,y)
  +
</haskell>
  +
  +
and have it be different from
  +
  +
<haskell>
  +
do
  +
y <- getChar
  +
x <- getChar
  +
return (x,y)
  +
</haskell>
  +
  +
Unlike the first, the second example returns a pair of characters in the opposite order to which they were entered.
  +
  +
It might help to meditate about the difference between 'assignment' and 'binding', right now.
  +
  +
However, just to spoil the enlightenment you just attained, there are monads for which swapping the order of lines like this makes no difference: For example, the Reader monad.
  +
  +
So while it is correct to say that monads can be used to order operations, it would be wrong to say that monads are a mechanism for ordering operations.
  +
  +
This notion of commutativity looks superficially very different from the familiar one in vanilla algebra where a+b=b+a. It doesn't mean that
  +
<haskell>
  +
m >> n === n >> m
  +
</haskell>
  +
which doesn't hold in general for ''any'' non-trivial monad, as for the most part
  +
<haskell>
  +
return 1 >> return 2 === return 2 =/= return 1 === return 2 >> return 1
  +
</haskell>
  +
  +
This shouldn't be too surprising, though, as >> isn't the binary operation of a monoid. The [http://ncatlab.org/nlab/show/commutative+algebraic+theory category-theoretic definition] of a commutative monad is rather more abstract.
  +
  +
==See also==
  +
  +
* [[Do notation considered harmful]]
  +
  +
[[Category:FAQ]]
  +
[[Category:Monad]]

Latest revision as of 16:45, 2 December 2020

Warning

Don't be surprised if you leave this page more confused than before. That just means that it has successfully destroyed your false assumptions, or that you've fallen for some horrible inside joke. Beware of Zygohistomorphic prepromorphisms. Go for warm and fuzzy, instead. Or this one.

Monads are not a good choice as topic for your first Haskell blog entry

...just accept that they're burritos, and wait until later.

Monads are not a language feature

Really. They are defined in terms of Haskell, not Haskell in terms of them. Conversely,

Haskell doesn't need Monads

...well, apart from the current Haskell standard defining the way IO is done in terms of Monads: It could be done differently and still work.

Monads are not impure

...In no way whatsoever. You don't even need flexible morals to claim it. To be more specific, it's IO that's impure. That makes the IO monad impure. But that's not a general property of monads - just IO. And even then, we can pretend that Haskell is a purely functional description language for imperative programs. But we didn't want to employ flexible morals, now did we?

Monads are not about state

While it is certainly possible to abstract away explicit state passing by using a Monad, that's not what a monad is. Some examples for monads that are not about state: Identity monad, Reader monad, List monad, Continuation monad, Exception monad.

Monads are not about strictness

Monad operations (bind and return) have to be non-strict in fact, always! However other operations can be specific to each monad. For instance some are strict (like IO), and some are non-strict (like []). Then there are some that come in multiple flavours, like State.

Try the following:

runState (sequence . repeat $ state (\x -> (x,x+1))) 0

Having a look at the implementation of fixIO might be helpful, too.

Monads are not values

This point might be driven home best by pointing out that instance Monad Foo where ... is not a data type, but a declaration of a typeclass instance. However, to elaborate:

Monads are not values in the same sense that addition and multiplication are not numbers: They capture a -- very specific -- relationship between values of a specific domain into a common abstraction. We're going to call these values monads manage mobits, somewhat like this:

type Mobit m a = Monad m => m a

The IO monad manages mobits representing side-effects ("IO actions").

The List monad manages mobits representing multiple values ("[a]")

The Reader monads manages mobits that are pure computations that use asks to propagate information instead of explicit arguments

...and while addition and multiplication are both monoids over the positive natural numbers, a monad is a monoid object in a category of endofunctors: return is the unit, and join is the binary operation. It couldn't be more simple. If that confuses you, it might be helpful to see a Monad as a lax functor from a terminal bicategory.

Monads are not a replacement for applicative functors

Instead, every monad is an applicative functor (as well as a functor). It is considered good practice not to use >>= if all you need is <*>, or even fmap.

Not confusing which features of monads are specific to monads only and which stem from applicative functors is vitally important for a deeper understanding of monads. As an example, the applicative functor interface of parser libraries can parse context-free languages (modulo hacks abusing open recursion), while the monadic interface can parse context-sensitive grammars: Monads allow you to influence further processing by inspecting the result of your parse. To understand why, have a look at the type of >>=. To understand why applicative functors by themselves are sufficient to track the current parsing position and express sequencing, have a look at the uu-parsinglib tutorial (pdf).

The exact differences are elaborated in even greater detail in Brent Yorgey's excellent Typeclassopedia.

Monads are not about ordering/sequencing

Monads are commonly used to order sequences of computations. But this is misleading. Just as you can use monads for state, or strictness, you can use them to order computations. But there are also commutative monads, like Reader, that don't order anything. So ordering is not in any way essential to what a monad is.

Let's have a look at what's meant by ordering. Consider an expression like

let x = a
    y = b
in  f x y

That gives the same result as

let y = b
    x = a
in  f x y

It doesn't matter what order we write the two bindings. But for doing I/O we'd like ordering. Monads allow us to express

do
    x <- getChar
    y <- getChar
    return (x,y)

and have it be different from

do
    y <- getChar
    x <- getChar
    return (x,y)

Unlike the first, the second example returns a pair of characters in the opposite order to which they were entered.

It might help to meditate about the difference between 'assignment' and 'binding', right now.

However, just to spoil the enlightenment you just attained, there are monads for which swapping the order of lines like this makes no difference: For example, the Reader monad.

So while it is correct to say that monads can be used to order operations, it would be wrong to say that monads are a mechanism for ordering operations.

This notion of commutativity looks superficially very different from the familiar one in vanilla algebra where a+b=b+a. It doesn't mean that

m >> n === n >> m

which doesn't hold in general for any non-trivial monad, as for the most part

return 1 >> return 2 === return 2 =/= return 1 === return 2 >> return 1

This shouldn't be too surprising, though, as >> isn't the binary operation of a monoid. The category-theoretic definition of a commutative monad is rather more abstract.

See also