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

Monads require true polymorphism. Hence the answer is no (from
Haskell's perspective) if there are constrains on the element type
(like Eq oder Ord).

> 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.

Let's assume that we may fiddle around with the class definition. Here
is another possibility which is missing on your list (no mp type
classes, just plain Haskell 1.4 ;-).

> module Set                    (  module Set  )
> where
>
> import Prelude hiding         (  Monad(..)  )

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

We simply add the constrains to the method contexts. BIG disadvantage:
one has to adapt the class definition if the constrains change. BIG
advantage: no fiddling around with multiple parameters (which may be a
pain).

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

> newtype Set a                 =  Set [a]
> instance Eq a => Eq (Set a) where
>     Set s == Set t            =  undefined
> setUnion                      :: (Eq a) => Set (Set a) -> Set a
> setMap                        :: (Eq a, Eq b) => (a -> b) -> Set a -> Set b
> setSingleton                  :: a -> Set a
> setUnion                      =  undefined
> setMap                        =  undefined
> setSingleton                  =  undefined

Cheers, Ralf



Reply via email to