#5516: Universally quantified GADT context leads to overlapping instance
---------------------------------+------------------------------------------
Reporter: andersk | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.3 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: GHC rejects valid program
---------------------------------+------------------------------------------
This example from comment:8:ticket:2893 works in GHC 7.0.3, but fails in
GHC master 7.3.20110927:
{{{
#!hs
{-# LANGUAGE GADTs, Rank2Types, FlexibleContexts #-}
class Foo a where
foo :: a -> String
instance Foo [b] where
foo = show . length
data FooDict a where
FooDict :: Foo a => FooDict a
f :: (forall b. FooDict [b]) -> String
f FooDict = foo "Hello" ++ foo [1, 2, 3]
use_foo :: String
use_foo = f FooDict
}}}
with this error:
{{{
foo.hs:13:28:
Overlapping instances for Foo [t0]
arising from a use of `foo'
Matching instances: instance Foo [b] -- Defined at foo.hs:6:10
Matching givens (or their superclasses):
(Foo [b_a])
bound by a pattern with constructor
FooDict :: forall a. Foo a => FooDict a,
in an equation for `f'
at foo.hs:13:3-9
(The choice depends on the instantiation of `t0')
In the second argument of `(++)', namely `foo [1, 2, 3]'
In the expression: foo "Hello" ++ foo [1, 2, 3]
In an equation for `f': f FooDict = foo "Hello" ++ foo [1, 2, 3]
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5516>
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