Monads, Functors and typeclasses
                 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

The definition for the class Monad is in Haskell:

  class Monad m where
    return :: a -> m a
    (>>=)  :: m a -> (a -> m b) -> m b

Further, we have the class Functor, which is defined as follows:

  class Functor m where
    map :: (a -> b) -> m a -> m b

to be a Functor. Haskell, however, doesn't specify any relationship
between Monad's and Functor's. This a problem. 

                  ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~

For example, take the class MonadTrans. It has one member function `lift',
that lifts a monadic value of one monad into another monad:

  class MonadTrans t where
    lift :: Monad m => m a -> t m a

Recently I defined a Monad transformer, let's call it C:

  type C m a = ...
    in ..., liftC, ...

And I defined a lifting function for C as follows:

  liftC :: Functor m => m a -> C m a
  liftC = ... map ...

The nice thing about my definition was that I only needed the `map' for
the underlying monad in order to make this work! This resulted in the
restriction `Functor' instead of `Monad'. So far so good. Then I wanted
`C' to be an instance of MonadTrans. This was not possible!: 

  - the types of `lift' and `liftC' don't match, because Haskell doesn't
    know about any connection between Monad and Functor;

  - Changing the type of `liftC' won't work, it will be something like
      
       (Functor m, Monad m) => m a -> C m a

    which looks like a superfluous context, and still doesn't match with
    `lift'.

Of course I can redefine the function `liftC' (by substituting `map' for
the appopriate monadic definion), but I consider that as cheating. 

                  ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~

The solution is real easy: To express the necessity of a Monad to be a
Functor, change the definition of the class Monad as follows: 

  class Functor m => Monad m where
    ...

Now a context of the form (Monad m) also contains the `map' function, as
you would expect. A context of the form (Functor m, Monad m) will be
reduced to (Monad m). As far as I understand, this won't break any
existing Haskell programs (which seems to be a very important property
for some people).

                  ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~

It also opens the way to incorporate the "standard" definition of a Monad.
The standard definition says that a Monad should have operators `unit' (or
`return') and `join'. We can combine this with our existing definition: 

  class Functor m => Monad m where
    return :: a -> m a
    (>>=)  :: m a -> (a -> m b) -> m b
    join   :: m (m a) -> m a

A nice property of the definition with `>>=' (which is the Kleisli
definition) and the "standard" definition with `join' is that they are
equivalent. `join' and `>>=' can be expressed in terms of each other,
with the help of `map'. We can give default definitions for `join' and
`>>=':

  class Functor m => Monad m where
    ...

    m >>= k  =  join (map k m)
    join m   =  m >>= id

Now, if we define a Monad, we can choose if want to do that according to
the Kleisli definition (then we will define `>>=' and `return'), or the
"standard"  definition (then we will define `join' and `return'). Often it
is easier to define `join' than `>>='.

And even this, as far as I understand it, won't break existing Haskell
programs! (By the way, this is how Gofer defines its Monad class).

                  ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~

Isn't there even a better way to indicate the relation between Monad and
Functor? Indeed, we can express the `map' function of a Functor in terms
of the `return' and `>>=' functions of a Monad:

  map f m = m >>= (return . f)  ,  or

  map f m = [ f a | a <- m ]  ,    if you allow Monad comprehensions.

Sadly, there is no way in Haskell to express this. If we allowed
overlapping instances (like Gofer does), we could say:

  instance Monad m => Functor m where
    map f m = [ f a | a <- m ]

And we never would have to make any Monad explicitly an instance of
Functor anymore... (You have to be careful using the default definition of
`>>=' together with this though.) See also Simon, Erik, and Mark's paper.

                  ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~

Is this a storm in a teacup? Much huff and puff for a seldom-occurring
situation? No! It happens to me ALL THE TIME. ;-)

I sent this message because I would like to know if there is a Real Reason
for Haskell not to define its Monad class in this way.

I also would like to know other people's opinions about this. Do people
find this Really Important, like me? Or is it considered theorectical
whining? 

Monads play such an important role nowadays in Haskell-like languages,
that it is important to get its definition right.

                  ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~ ~~

Regards,
Koen.

--
|  Koen Claessen,                   [EMAIL PROTECTED]  |
|                   http://www.cse.ogi.edu/~kcclaess/  |
|------------------------------------------------------|
|  Visiting student at OGI,    Portland, Oregon, USA.  |






Reply via email to