It seems everybody is playing around with monads and monad transformers
these days. I tried to `simplify' the multiple constructor classes a
few days ago ;-). `State' worked as you described it, but I encountered
problems with SML-like exception handling:
> class Monad m => ExcMonad e m where
> raise :: e -> m a
> handle :: m a -> (e -> m a) -> m a
> instance Functor (Either a) where
> map f (Right a) = Right (f a)
> map f (Left a) = Left a
> instance Monad (Either a) where
> Left a >>= k = Left a
> Right a >>= k = k a
> return = Right
> instance ExcMonad a (Either a) where
> raise = Left
> Left a `handle` h = h a
> Right a `handle` h = Right a
I don't like the strings-only exception classes, so `ExcMonad' is
parameterized with the type of exceptions. Now, when I simplify the
class definition to
> class Monad m => ExcMonad m where
> raise :: e -> m a
> handle :: m a -> (e -> m a) -> m a
> instance ExcMonad (Either a) where
> raise = Left
> Left a `handle` h = h a
> Right a `handle` h = Right a
`hbc' complains:
Errors:
"ExcMonad.lhs", line 0, [59] Bad restriction
b -> Either c c
of type
a -> Either a a
identified tyvars
in ((\AA2990 -> Left AA2990{FARITY 1}))::c -> Either d d
in Either~a`raise
The class definition is too general: the type of exceptions must be
the fixed since `raise' and `handle' interact. That's in contrast with
a state monad: There is no reason why the type of the state should not
change.
Admittingly, I was a bit disappointed to see that Haskell 1.3 does not
allow for multiple parameter type classes. Most of the constructions to
be found in literature (lifting, composing etc) seem to require this
feature. Take for example lifting:
> class (Monad m, Monad (t m)) => MonadT t m where
> lift :: m a -> t m a
So Haskell 1.3 allows to play with monads but not with monad
transformers. Sigh.
Ralf