Yes indeed, this is one of those "well-known" (ie not at all well known, but 
folk lore) problems with overlapping instances, at least in programs where 
different instances can be in scope at different times.

It's discussed (not very clearly) in 
http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extensions.html#instance-overlap
 (..."GHC is conservative about committing to an overlapping instance"...)

I don't think you need a superclass. Suppose you put your function 'f' in 
module A

        f :: Name a => a -> String
        f x = name [x]

Then, f will commit to the Name [a] instance, because it uniquely matches.

But if, in module B you say

        (name ['x'], f 'x')

you'll get two different answers, even though the former is just an unfolding 
of the latter.

If GHC can "see" both instance decls at the moment you declare f, it'll 
complain.  But while it can see only one, it doesn't.  It's the same with your 
instance decl 'instance Name a => C [a]'


This isn't great, but it's not really different than is the case for 
non-overlapping instances.  Suppose module B1 declares 'instance C T', and uses 
that instance; and module B2 declares a *different* 'instance C T', and uses 
that instance; and Main imports B1 and B2, but does not use either instance 
directly.  Then GHC will compile the program without complaint, although it is 
incoherent.


The only way I know to fix this would be to keep a history of all instance-decl 
matches performed during compilation, and check that they are still unique 
matches even when all instance decls in the program are taken into account. Or, 
to put it another (less modular) way: first find all instance decls, and only 
then compile the program.  But this destroys modular compilation.

Simon




| -----Original Message-----
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Iavor Diatchki
| Sent: 07 June 2008 23:12
| To: Haskell users
| Subject: [Haskell] A problem with overlapping instances and super-classes
|
| 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
| _______________________________________________
| Haskell mailing list
| Haskell@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to