#5514: bad variable escape analysis when TypeFamilies are enabled
---------------------------------+------------------------------------------
Reporter: dmwit | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.3 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
The following minimal example causes a type error in 7.3.20110927:
{{{
{-# LANGUAGE TypeFamilies #-}
class Foo a where
foo :: a -> a
instance (Foo a, Foo b) => Foo (a, b) where
foo = foo' ()
foo' es = const id (unitId es)
unitId :: () -> ()
unitId = id
}}}
Specifically, the error given is:
{{{
test.hs:6:10:
Couldn't match type `a0' with `(a, b)'
because type variables `a', `b' would escape their scope
These (rigid, skolem) type variables are bound by
the instance declaration
The following variables have types that mention a0
foo' :: () -> a0 -> a0 (bound at test.hs:9:1)
In the instance declaration for `Foo (a, b)'
}}}
This code compiles successfully as recently as 7.3.20110726 (though I
haven't tested any GHC versions in between these two).
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5514>
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