I'm sure this must have been thought of before, but I couldn't find
any literature discussing it so...

Two questions:

1) Is it possible for a set to define a monad?

2) Does anyone know if it's possible to define an instance of monads
   for sets in Haskell?  Even with multi-parameter type classes and
   even if the definition of the Monad class is adapted, this seems
   impossible to me.

If the answer to (1) is no, I suppose you may ignore the remainder of
this mail. :-)  However, if it is yes, then please read on.

This is the standard definition of the Monad class:

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

>    m >> k = m >>= \_ -> k


Attempt One
-----------

In order to define an instance of monads for sets using equality of
elements (the minimum constraint necessary), I think we need to
introduce another parameter or two into the Monad definition, so that
we can write:

> instance Eq a => Monad Set a where
>    m >>= k = setUnion (setMap k m)
>    return x = setSingleton x

where

> instance Eq a => Eq (Set a) where
>    <definition to promote equality on elements>

> setUnion :: Eq a => Set (Set a) -> Set a
> setMap :: (Eq a,Eq b) => (a -> b) -> Set a -> Set b
> setSingleton :: a -> Set a

but with only one parameter we arrive at:

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

>    m >> k = m >>= \_ -> k

which leaves (>>=) and (>>) polymorphic in `b'.


Attempt Two
-----------

If we add another type parameter:

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

>    m >> k = m >>= \_ -> k

we have an ambiguous type for `return'.


Attempt Three
-------------

If we parameterise over the other type variable and let `return' use
this variable:

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

>    m >> k = m >>= \_ -> k

> instance Eq b => Monad Set b where
>    m >>= k = setUnion (setFromList (map k (setToList m))
>    return x = setSingleton x

This works fine but smells of a hack to me.  Certainly had we not been
lucky enough to find that we do not need equality on elements to
convert a set to a list, we would have been stuck.

The definition does not look nice to me, it's asymmetrical for a
start.  We cannot constrain the type variable `a'.


Attempt Four
------------

We push `return' up to a superclass, so that we may parameterise over
both type variables in the Monad definition:

> class SuperMonad m a where
>    return :: a -> m a

> instance SuperMonad Set a where
>    return x = setSingleton x

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

>    m >> k = m >>= \_ -> k

> instance (Eq a,Eq b) => Monad Set a b where
>    m >>= k = setUnion (setMap k m)

This works fine but looks awkward.  One problem is that we can no
longer define MonadPlus and MonadZero as subclasses since these are
parameterised over only one variable.  We could place them in
SuperMonad but that would be contrary to the purpose of MonadZero and
MonadPlus.

There is still asymmetry too.  Why the distinction between `a' and
`b'?  We would surely prefer to somehow tie the type variables more
closely.


We need some way of constraining `a' and `b' in the definition of the
Monad class by the _same_ constraint.  A variable that ranges over the
type variables `a' and `b'?!? :-)


Comments, corrections and thoughts welcome.  I don't pretend to
understand monads very well, but I hope that asking this question may
help me.

Graeme.



Reply via email to