[Haskell-cafe] Martin Odersky on "What's wrong with Monads"

Anton Kholomiov anton.kholomiov at gmail.com
Sun Jun 24 11:41:10 CEST 2012


Here is an half-baked idea how to make monads more functional.
It's too wild to be implemented in haskell.
But maybe you are interested more in ideas than implementations,
so let's start with monad class

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


I think monad's methods are misleading, let's rename them

class Monad m where
    idM  :: a -> m a
    (*$) :: (a -> m b) -> m a -> m b


We can see that `return` is a monadic identity and the `bind`
is an application in disguise. So now we have two applications.
It's standard `($)` and monadic `(*$)`. But they are application.
Well isn't it something like `plusInt` and `plusDouble`?
Maybe we can devise single class for application. Let's
imagine a special class `App`

class App ?? where
    ($) :: ???

As you can see it's defined so that we can fit
monads and plain functions in this framework. Moreover
if we redefine this class than whitespace is redefined
automatically! So `($)` really means *white space* in haskell.

`idM` is interesting too. In standard world we can safely
put `id` in any expression. So when we write

    f = a + b

we can write

    f = id (a + b)

or even

    f = id ((id a) + (id b))

meaning doesn't change. So if we have special class `Id`

class Id f where
    id :: ???

Again you can see that monads fit nicely in the type.
Why do we need this class? Whenever compiler gets an type mismatch,
it tries to apply method from `Id` class, if it's defined ofcourse.

But we have a class called `Category`, `id` belongs to it:

class Category (~>) where
    id   :: a ~> a
    (>>) :: (a ~> b) -> (b ~> c) -> (a ~> c)


Let's pretend that `(>>)` is reversed composition `(.)`.
It's interesting to note that there is another formulation
of 'Monad' class. It's called Kelisli category.

class Kelisli m where
    idK  :: a -> m a
    (>>) :: (a -> m b) -> (b -> m c) -> (a -> m c)

Here again let's forget about monad's `(>>)` for a moment,
here it's composiotion. `Kleisli` is equivalent to `Monad`.

If we can define `Category` instance for `Kleisli`, so that
somehow this classes become unified on type level we
can define application in terms of composition like this:

f $ a = (const a >> f) ()

And we can get application for monads (or kleislis :) ).

Implications:

Maybe someday you wrote a function like this:

foo :: Boo -> Maybe Foo
foo x = case x of
    1 -> Just ...
    2 -> Just ...
    3 -> Just ...
    4 -> Just ...
    5 -> Just ...
    6 -> Just ...
    7 -> Just ...
    _ -> Nothing

with `idM` rule you can skip all Just's

You can use white space as monadic bind. So functional application
can become monadic on demand. Just switch the types.


Implementation:

I've tried to unify `Category` and `Kleisli` with no luck.
Here is a closest sletches:

simplest sketch requires type functions :(


instance Monad m => Category (\a b -> a -> m b) where
    ...


the other one too :(

class Category (~>) where
    type Dom (~>) :: * -> *
    type Cod (~>) :: * -> *

    id   :: Dom (~>) a -> Cod (~>) a
    (>>) :: (Dom (~>) a ~> Cod (~>) b) -> (Dom (~>) b ~> Cod (~>) c) -> ...


instances

type Id a = a  -- :(

instance Monad m => Category (a -> m b) where
    type Dom (a -> m b) = Id
    type Cod (a -> m b) = m

    ...
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120624/ea0c8c1b/attachment.htm>


More information about the Haskell-Cafe mailing list