[Haskell] A problem with overlapping instances and super-classes

Iavor Diatchki iavor.diatchki at gmail.com
Sat Jun 7 18:12:27 EDT 2008


Hello,
(you should be able to copy and paste the code in this email into two
modules called A and B to try it out)

> {-# LANGUAGE OverlappingInstances #-}
> module A where

This module, together with module 'B', illustrates a problem in some
implementations of overlapping instances and their interaction with
super-classes.  I tried GHC 6.8.2 and Hugs (September 2006).
The problem is one of coherency---we can get a method to behave differently,
when instantiated at the same type in the same module.  We need two modules to
illustrate the problem because both Hugs and GHC perform some checking
to avoid this problem.  Unfortunately, it seems that we can circumvent
the checking by moving instances to a different module.

Consider the class 'Name'. We are going to show how 'name' behaves
differently when
instantiated at the same type.

> class Name a where name :: a -> String
> instance Name Char where name _ = "Char"
> instance Name a => Name [a] where name x = "[" ++ name (head x) ++ "]"

We also define a super-class of 'Name' called 'C'.
The methods of 'C' are not important---we use a single method that can
be used to generate 'C' constraints.

> class Name a => C a where c :: a -> ()
> instance Name a => C [a] where c _ = ()

The instance of 'C' is interesting: we have to check that the
super-class constraint holds, so we need to prove (Name a => Name [a]).
In the given context there is exactly one way to do this, namely, by
using the corresponding instance for 'Name'.  Note, however, that
in other modules there may be more specific instances for 'Names [a]'
that could have been used.  This leads to a problem, as we show in module B.


> {-# LANGUAGE OverlappingInstances, FlexibleInstances #-}
> module B where
> import A

We add another instance for 'Name'---it overwrites the generic behavior
on lists, with a specific instance for lists of characters:

> instance Name [Char] where name _ = "String"

Here is an example function that uses both 'c' and 'name' at the same
type ('[a]', for some 'a').  This results in two constraints: (Name [a], C [a]).
Implementations "simplify" this to just (C [a]) by using the fact that
'C [a]' is a super-class of 'Name [a]'.  Unfortunately this commits to using
the "generic" instance for 'Name' on lists (the one in module 'A').

> f x = name [x]
>  where _ = c [x]

Here is an example illustrating the problem:  the two components of the
pair use 'name' at the same instance, '[Char]', but the first ends up
using the generic instance, while the second uses the specific instance.

> test = (f 'x', name ['x'])

GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
[1 of 2] Compiling A                ( A.lhs, interpreted )
[2 of 2] Compiling B                ( B.lhs, interpreted )
Ok, modules loaded: A, B.
*B> test
("[Char]","String")


-Iavor


More information about the Haskell mailing list