> >  A.hs:3:23: parse error on input: "("
> 
> I should have said that I've implemented the choices given
> on the Standard Haskell web discussion page.  In particular:
> 
> ===================
> Choice 7a
> ~~~~~~~~~
> 
> The context in a class declaration (which introduces superclasses)
> must constrain only type variables.  For example, this is legal:
> 
>         class (Foo a b, Baz b b) => Flob a b where ...
> but not
>         class (Foo [a] b, Baz (a,b) b) => Flob a b where ...
> 
> It might be possible to relax this restriction (which is the same
> as in current Haskell) without losing decideability, but we're not
> sure.  Choice 7a is conservative, and we don't know of any examples
> that motivate relaxing the restriction.
> ===================
> 
> I'm frankly unsure of the consequences of lifting the 
> restriction.  Can you give a compact summary of why you want
> to?  Our multi-parameter type-class paper gives none, and if
> you've got one I'd like to add it.
> 
> In the short term, you're stuck.  Damn!  First customer too!

I ran into *exactly* the same problem with my own monad transformer
code, but haven't reported it yet because there's a lot of other stuff
I need to do to massage it into GHC-friendly form.

The problem is, the above parens appear in the standard definition of
a monad transformer, the motivating example for MPCs in the first
place!

Consider the state monad transformer:

> type StateT s m v = s -> m (v,s)
> 
> instance Monad m => Monad (StateT s m) where
>   return v = \s -> return (v,s)
>   m >>= f  = \s -> m s      >>= \(v,s') -> 
>                    (f v) s
> 
> instance (Monad m, Monad (StateT s m))   -- here is the problem
>           => MonadT (StateT s) m where
>   lift m = \s -> m             >>= \v ->
>                  return (v,s)
> 
> class Monad m => StateMonad s m where
>   getS :: m s
>   setS :: s -> m ()
> 
> instance Monad m => StateMonad s (StateT s m) where
>   getS   = \s -> return (s ,s)
>   setS s = \_ -> return ((),s)
> 
> instance (StateMonad s m, MonadT t m)
>           => StateMonad s (t m) where
>   getS   = lift getS
>   setS s = lift (setS s)

Note we assume here the definition of MonadT:

> class (Monad m, Monad (t m)) => MonadT t m where  -- here again
>   liftM :: m a -> t m a

You can see the two lines that violate 7a.

> Simon

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) -------------------------:
: PhD Student, Computing Science, University of Glasgow, Scotland.     :
: Native of Antipodean Auckland, New Zealand: 174d47' E, 36d55' S.     :
: http://www.dcs.gla.ac.uk/~keithw/  mailto:[EMAIL PROTECTED]       :
:----------------------------------------------------------------------:

Reply via email to