Query regarding GHC handling of overlapping instances.
Simon Peyton-Jones
simonpj at microsoft.com
Fri Sep 12 12:06:11 EDT 2003
| I have been doing some work recently which involves classes with
| overlapping instances... for example
|
| class Test x y where
| test :: x -> y
|
| instance Test (a b) (c b) where
| test =
|
| instance Test (a b) (a b) where
| test =
|
| This gives an overlapping instance error - which cannot be avoided
with
| -fallow-overlapping-instances.
| However - it is fairly obvious that the first case 'a' cannot be
unified
| with 'c' or it would be a type error, therefore
| the cases do not overlap... Is this a bug in ghc, is it easily fixable
-
| or am I confused?
You are right. They don't overlap. The program below runs fine with
GHC 6.0.1, and prints
cam-02-unx:~/tmp$ ghc -fallow-overlapping-instances -fglasgow-exts
Foo.hs
cam-02-unx:~/tmp$ ./a.out
"Second"
"First"
Simon
=========================
module Main where
class Test x y where
test :: x -> y -> String
instance Test (a b) (c b) where
test x y = "First"
instance Test (a b) (a b) where
test x y = "Second"
main = do { print (test [True] [True]) ;
print (test [True] (Just True)) }
More information about the Glasgow-haskell-users
mailing list