[GHC] #7939: RHS of associated type not kind-checked
GHC
ghc-devs at haskell.org
Wed Jun 19 18:22:31 CEST 2013
#7939: RHS of associated type not kind-checked
------------------------------------------+---------------------------------
Reporter: goldfire | Owner:
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:
------------------------------------------+---------------------------------
Changes (by monoidal):
* owner: goldfire =>
* status: closed => new
* resolution: fixed =>
Comment:
Something is suspicious here.
GHC accepts original program
{{{
{-# LANGUAGE TypeFamilies, PolyKinds #-}
class Foo a where
type Bar a
instance Foo Int where
type Bar Int = Maybe
instance Foo Bool where
type Bar Bool = Double
}}}
but rejects
{{{
{-# LANGUAGE TypeFamilies, PolyKinds #-}
type family Baz a
type instance Baz Int = Maybe
type instance Baz Bool = Double
}}}
Is this really expected? Even more, you can write
{{{
instance Foo Bool where
type Bar Bool = Double
type Bar Bool = Maybe
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7939#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list