[GHC] #8566: Panic with kindFunResult
GHC
ghc-devs at haskell.org
Fri Dec 13 12:30:14 UTC 2013
#8566: Panic with kindFunResult
-------------------------------------+------------------------------------
Reporter: dreixel | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: polykinds/T8566 | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by dreixel):
I suspect this fix makes the following code fail to compile with HEAD:
{{{
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
data Field = forall k. APP k [Field]
data InField (u :: Field) :: * where
A :: { unA :: AppVars t (ExpandField args) } -> InField (APP t args)
-- Without the selector, the program compiles
-- A :: AppVars t (ExpandField args) -> InField (APP t args)
type family ExpandField (args :: [Field]) :: [*]
type family AppVars (t :: k) (vs :: [*]) :: *
}}}
Note that simply removing the selector `unA` fixes the problem. The code
compiles with 7.6. Is this a regression, or is it the expected
behaviour?...
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8566#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list