Reasons behind the "one instance per type" limitation

Diego Dainese xddainese@xlibero.it
09 Oct 2001 14:53:21 +0200


On Mon, 8 Oct 2001 15:03:15 -0700 Ashley Yakeley <ashley@semantic.org>
wrote:
> At 2001-10-08 09:27, Diego Dainese wrote:
> 
> >what are the reasons behind the rule stating that a type must not be
> >declared as an instance of a particular class, more than once in the
> >program?
> 
> It's so that the members of the class are unambiguous.
> 
>     --
>     class C t where
>         foo :: t -> Integer
> 
>     instance C Bool where
>         foo _ = 3;
> 
>     instance C Bool where
>         foo _ = 5;
> 
>     ambiguous = foo True;
>     --

OK, this is reasonable; but why are instance declarations always
automatically exported and imported across modules boundary? This goes
against information hiding.

Consider this situation:

> module M(T, f, g) where
>   data T = ...
>   ...
> 
> module N where
>   import M
> 
>   instance Eq T where
>      ... 

now, suppose that in a second revision of the module M, an instance of
Eq is made for T; even if this instance is needed for internal use
only, it outlaws the instance defined in the module N.

I think this problem could be a real show-stopper for big programs...

Why aren't instance declarations handled by the module system like
every other symbol, so that a module can decide when to import an
instance declaration and when to export it? Are there technical
difficulties with this approach?

> GHC has a flag that will turn the rule off.

I cannot find it!

-- 
Diego

To reply remove the 2 `x' from the address.