[Haskell-cafe] Request to review my attempt at understanding Monads

Alexander Solla ajs at 2piix.com
Tue Dec 29 03:35:03 EST 2009


I happen to think that the only good way to approach monads is  
mathematically.  Uses come out naturally, once you understand what it  
is that a monad "does".  I'll make a short speech and then comment on  
your questions.

First, an example.  I will assume that there are some things you will  
only do outdoors.  And there are some things you will only do in your  
home.  If you are in your home, and decide you need to do one of these  
"outdoor" things, you need to do something VERY SPECIFIC first.  You  
need to go outdoors.

Second, a monad is conceptually a "one argument" function/functor.   
Outside of the Haskell/programming context, "Monadic" means "one  
argument".  This is important, because a function with one argument  
bears a special relationship to its argument.  Using current  
mathematical convention, the function "goes" on the left.  And the  
argument "goes" on the right.  Obviously, leftness and rightness are  
duals, so it doesn't particularly matter which goes where, as long as  
one is consistent.

Continuing that point, the functions "bind" and "return" capture the  
notion of "moving right" and "moving left".  This is literally  
captures the notion of a "side effect".  The effect of moving the  
context of computation left or right.  A simple example is:

 > data Left a = LeftA a
 >             | LeftB a
 > data Right = Right

 > -- Note that the type (Left Right) is a product of types.
 > -- (Left Right) contains the values (LeftA Right) and (LeftB Right).

 > -- Compare that to LeftRight in:
 > -- data Left = LeftA | LeftB
 > -- data Right = Right
 > -- type LeftRight = (Left, Right) -- contains the values (LeftA,  
Right) and (LeftB, Right).


 > instance Monad Left where
 >     return a = LeftA a   -- moves "execution context" to the left,  
in virtue
 >                          -- of the fact that any function on (Left  
a) has to work
 >                          -- on every type a.
 >     (LeftA a) >>= f = f a
 >     (LeftB a) >>= f = f a

The only complication is that bind (>>=) expects to bind variables to  
functions that return a monadic type.  So, basically, a call to bind  
unwraps the monadic type, applies a function, and then "automatically"  
moves the scope back left, as if you hit the end of a typewriter's  
line.  This is only for convenience.  You could (and sometimes have  
to) use return in order to "return to the left".

Monads are pretty deep mathematically.  Every Monad defines a "join"  
and "eval" function in terms of bind and return, and the Monad type  
class does this for you.  You can use "join" to construct queries  
against a monad, and eval to "run" a monad, like a state machine.   
(Conceptually, the Haskell runtime calls the IO monad's "specially  
defined" eval method on "Main.main".  This is the only Haskell monad  
whose eval function is not defined in terms of >>= and return, as far  
as I know.)

On to your questions:
> are there any other benefits that comes in because of List being a  
> Monad? What would MonadPlus provide me?


If you think List is the right monad to work in, you might as well  
stick to List functions and ignore do-notation.  If you think you  
might need a more general monad, you may as well use do-notation.   
Lists have more structure than "all monads", so we can define more  
functions on lists than we can on an arbitrary monad.

"MonadPlus" applies to Monads that have a sort of "additive"  
structure.  There's no "sensible" way to add (LeftA a) and (LeftB a)  
values together, but we can impose one by declaring Left as a  
MonadPlus.  If you allow some abuse of the syntax, this might be a  
better example:

 > -- we are treating the Integers as one argument data constructors
 > -- this code will not run, because we are abusing the Integers.
 > -- This is kind of like an "infinite" Maybe monad
 > type Count a = 0 | 1 a | 2 a | 3 a | 4 a | 5 a | ...
 > instance Monad Count where
 >    return a = 0 a
 >    (int, a) >>= f = f a

 > instance MonadPlus Count where
 >    mzero = 0
 >    m `mplus` n = (m + n) -- still abusing notation. m and n are  
"really" (m a) and (n b)
 >                          -- but this is clear enough, and captures  
the semantics of counting

The MonadPlus instance lets us add "Count" values, without regard to  
what is being counted. Note that while Count's addition function is  
commutative (so that m `mplus` n  = n `mplus` n), that does not have  
to be true in general.  Lists are a good example.  Adding to a list  
amounts to concatenating values to it.

> 3. The comprehension syntax for Lists in Haskell - can that be used  
> in anyway for other Monads?

Partly.  The <- in your l2 function is really the most important part  
of comprehension syntax.  return does the wrapping you might expect  
from something like "M (x <- blarg)"  There isn't "M ( x <- blarg )"  
type syntax for arbitrary monads.  Lists are a special case, since []  
is a special case as a type constructor.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20091229/28e4ff92/attachment.html


More information about the Haskell-Cafe mailing list