#4418: Superclass functional dependencies are ignored during instance selection
---------------------------------+------------------------------------------
Reporter: reinerp | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 7.1 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: GHC rejects valid program
---------------------------------+------------------------------------------
The following example compiles with ghc-6.12.3, but not with
ghc-7.0.0.20100924:
{{{
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
module Ambiguity where
class C1 a b | b -> a
class (C1 a b) => C2 a b where
foo :: b -> b
data A = A
data B = B
instance C1 A B
instance C2 A B
-- this is accepted by both 6.12.3 and 7
runFoo :: C2 a b => b -> b
runFoo = foo
-- this is accepted by 6.12.3, but not by 7
runFoo2 :: B -> B
runFoo2 = foo
}}}
A straightforward fix is to add the {{{b -> a}}} fundep to the {{{C2}}}
class as well.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4418>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs