> >> GHC complains about:
> >>
> >> > class (Monad m, {-, Monad (t m)-}) => MonadT t m where
> >> > lift :: m a -> (t m) a
> >> >
> >> > instance (Monad m) => Monad (EnvT env m) where
> >> > ...
> > instance Monad m => MonadT (EnvT env) m where ...
> >
>
> Even when I use the "decent" definition you suggest, GHC duplicates the
> context:
>
> 8 $d2 _:_ _forall_ [a b :: (* -> *)] {PrelBase.Monad b, PrelBase.Monad b} =>
> (MonadT (EnvT a) b) ;;
Aha! A palpable bug!
GHC implements an optimisation suggested by Mark. Consider
class S a => C a where ...
instance D a => D [a] where ...
The instance declaration gives rise to a function
$d :: D a -> D [a]
that takes a dictionary for (D a) into one for (D [a]). The optimisation
is to make $d do this:
$d :: D a -> S [a] -> D [a]
that is, to pass a dictionary for the superclass too. That can increase
sharing of dictionaries.
Ihe single parameter case, it's impossible for D a and S [a] to be
the same. But in this multi-parameter case they can, and the dups
aren't eliminiated. Hence the error.
I don't see a workaround. I'll just have to fix it...
How urgent is it?
Simon
Re: Instance declaration superclasses
Simon L Peyton Jones Mon, 27 Apr 1998 19:33:43 +0200 (MET DST)
- Instance declaration superclasses Frank A. Christoph
- Re: Instance declaration superclasses Simon L Peyton Jones
- RE: Instance declaration superclasses Frank A. Christoph
- Simon L Peyton Jones
