[GHC] #15343: Implicitly quantifying a kind variable causes GHC 8.6 to panic (coercionKind)
GHC
ghc-devs at haskell.org
Wed Jul 4 18:37:18 UTC 2018
#15343: Implicitly quantifying a kind variable causes GHC 8.6 to panic
(coercionKind)
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.6.1
Component: Compiler (Type | Version: 8.5
checker) |
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Here's a smaller example:
{{{#!hs
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeInType #-}
module Bug where
import Data.Kind
data HEq :: forall j k. j -> k -> Type where
HRefl :: HEq a a
data Sing :: forall j k (a :: j) (b :: k).
HEq a b -> Type where
SHRefl :: Sing HRefl
elimSing :: forall (j :: Type) (k :: Type) (a :: j) (b :: k)
(p :: forall (z :: Type) (y :: z). HEq a y -> Type)
(r :: HEq a b).
Sing r
-> p HRefl
-> p r
elimSing SHRefl pHRefl = pHRefl
data WhySym (a :: j) :: forall (y :: z). HEq a y -> Type
-- data WhySym (a :: j) :: forall z (y :: z). (a :~~: y) ~> Type
-- The version above does NOT panic
hsym :: forall (j :: Type) (k :: Type) (a :: j) (b :: k) (r :: HEq a b).
Sing r -> WhySym a r
hsym singEq = elimSing @j @k @a @b @(WhySym a) @r singEq undefined
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15343#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list