[Haskell-cafe] Re: Type class help please

oleg at pobox.com oleg at pobox.com
Wed May 16 03:31:26 EDT 2007


Adrian Hey wrote:
> -- Instances of GT are instances of Eq --
> instance (GT map key, Eq a) => Eq (map a) where
>   map1 == map2 = assocsAscending map1 == assocsAscending map2
> ...
>      Overlapping instances for Eq [(key, a)]
>        arising from use of `==' at Test.hs:10:16-59
>      Matching instances:
>        instance (Eq a) => Eq [a] -- Defined in GHC.Base
>        instance (GT map key, Eq a) => Eq (map a) -- Defined at Test.hs:9:0
>
> How can my new instance overlap with the old (ghc) instance unless
> [] is also an instance of GT for some key type (which it isn't).
> Could someone explain?

You are right in your explanation of the GHC behavior. Your instance 
|Eq (map a)| indeed overlaps the `standard` instance |Eq [a]|. The
overlap may be easier to see if we write [a] as ([] a), which is what
it is, an application of the type constructor [] to the type variable
a. So, the type [a] (aka [] a) is a particular instance of the type
(map a), with `map' being []. This is the overlapping that GHC is
complaining about.

Regarding the need for -fallow-undecidable-instance: GHC is not a
general purpose termination checker. Furthermore, it seems reasonable
for GHC to employ simple termination heuristics, which can be decided
quickly, syntactically and locally (that is, considering only the
instance in question, rather than collection of all instances in the
program). Thus GHC employs a set of heuristics that look if
the instance constraints are `smaller' than the instance head. That
will assure termination. That criterion is of course not complete, so
there are (many) terminating, decidable typeclass program that fail
simple GHC termination tests and thus require
-fallow-undecidable-instance extension.

One method of avoiding overlapping instances is to define a newtype
wrapper:

newtype MyMap map a = MyMap{unMyMap::map a}

class Ord key => GT map key | map -> key where
  assocsAscending :: map a -> [(key,a)] -- Just 1 of many methods

instance GT (MyMap Data.IntMap) Int where ...

The drawback is writing MyMap and unMyMap in many places. That spoils
the appearance, but rarely fatal.

Another solution is replacing the general instance
instance (GT map key, Eq a) => Eq (map a) where
  map1 == map2 = assocsAscending map1 == assocsAscending map2

with its instantiations, for all `maps' in question:
instance Eq a => Eq (Data.IntMap a) where ...
instance Eq a => Eq (Data.Map key a) where ...
instance Eq a => Eq (Data.IntSet a) where ...




More information about the Haskell-Cafe mailing list