#2448: Type equality constraint not propagated to superclass
---------------------------------------------------------+------------------
Reporter: conal | Owner:
Type: bug | Status: new
Priority: normal | Component:
Compiler
Version: 6.9 | Severity: normal
Keywords: type families, type equality constraints | Testcase:
Architecture: Unknown | Os:
Unknown
---------------------------------------------------------+------------------
The code:
{{{
{-# LANGUAGE TypeFamilies, UndecidableInstances #-}
-- Demonstrates a bug in propagating type equality constraints
class VectorSpace v where
type Scalar v :: *
class VectorSpace v => InnerSpace v
instance (VectorSpace u,VectorSpace v, Scalar u ~ Scalar v) =>
VectorSpace (u,v) where
type Scalar (u,v) = Scalar u
instance (InnerSpace u,InnerSpace v, Scalar u ~ Scalar v) => InnerSpace
(u,v)
}}}
In ghc 6.9.20080622, the last line yields
{{{
Data\TypeEqBug.hs:20:0:
Couldn't match expected type `Scalar v'
against inferred type `Scalar u'
When checking the super-classes of an instance declaration
In the instance declaration for `InnerSpace (u, v)'
}}}
I'd expect the type equality constraint in the {{{InnerSpace}}} instance
to get propagated to the parent class.
By the way, without the {{{UndecidableInstances}}} above, we get:
{{{
Constraint is no smaller than the instance head
in the constraint: Scalar u ~ Scalar v
(Use -XUndecidableInstances to permit this)
In the instance declaration for `VectorSpace (u, v)'
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2448>
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