Query regarding GHC handling of overlapping instances.
Keean Schupke
k.schupke at imperial.ac.uk
Fri Sep 12 13:35:48 EDT 2003
Thanks, I think I was just confused... (and other types elsewhere may
have been interfearing)... there still seems
something not quite right...
If I add the following definiton to the test code:
instance Test (a -> m b) (m b) where
test _ _ = "Third"
then I add the following print:
print $ test (\_ -> [True]) [True]
it says no instance for (t -> [Bool), but if I add a type annotation all
is Okay:
print $ test ((\_ -> [True]) :: () -> [Bool]) [True]
Is this expected behavior? Finally, If I change the definition to:
instance Test (a -> m b) z where
test _ _ = "Third"
it now complains about it overlapping with both of the other
definitions... Why does this overlap?
Regards,
Keean.
Simon Peyton-Jones wrote:
>| 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