#6044: Regression error: Kind variables don't work inside of kind constructors
in
type families
---------------------------------------+------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type
checker)
Version: 7.5 | Keywords: PolyKinds
TypeFamilies
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: GHC rejects valid program | Testcase:
Blockedby: | Blocking:
Related: |
---------------------------------------+------------------------------------
Many thanks for the quick bug fixes around kind variables recently.
With the newest build (7.5.20120425), the following code fails:
{{{
{-# LANGUAGE PolyKinds, DataKinds, TypeFamilies, KindSignatures #-}
type family Foo (a :: k) :: Maybe k
type instance Foo a = Just a
}}}
The error is:
{{{
Kind mis-match
The first argument of `Just' should have kind `k0',
but `a' has kind `k'
In the type `Just a'
In the type instance declaration for `Foo'
}}}
The above code compiles without error on, e.g., 7.5.20120329.
I think it's worth noting that the following compiles fine, which
surprised me given the error above:
{{{
type family Id (a :: k) :: k
type instance Id a = a
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/6044>
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