[GHC] #7939: RHS of associated type not kind-checked
GHC
ghc-devs at haskell.org
Tue Jun 25 17:42:43 CEST 2013
#7939: RHS of associated type not kind-checked
------------------------------------------+---------------------------------
Reporter: goldfire | Owner: goldfire
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: GHC accepts invalid program | Difficulty: Unknown
Testcase: ghci/scripts/T7939 | Blockedby:
Blocking: | Related:
------------------------------------------+---------------------------------
Comment(by monoidal):
I think it's fine to default to *. But, again, consider
{{{
type family A :: k
type instance A = Double
type instance A = Maybe
}}}
Should this really compile? I don't know, it looks suspicious but perhaps
it is OK.
What makes me suspicious is this. Consider
{{{
data D :: k -> * where
D1 :: D Bool
D2 :: D Maybe
}}}
GHC gives an error:
{{{
Data constructor `D1' cannot be GADT-like in its *kind* arguments
D1 :: D * Bool
}}}
But this seemingly equivalent code compiles:
{{{
{-# LANGUAGE TypeFamilies, GADTs, PolyKinds #-}
type family A :: k
type instance A = Bool
type family B :: k
type instance B = Maybe
data D :: k -> * where
D1 :: D A
D2 :: D B
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7939#comment:9>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list