
#14880: GHC panic: updateRole -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (Type checker) | Keywords: Roles | 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: -------------------------------------+------------------------------------- The following program panics on GHC 8.0.2, 8.2.2, 8.4.1, and HEAD: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} module Bug where import Data.Kind import Data.Type.Equality ((:~:)(..)) type SameKind (a :: k) (b :: k) = (() :: Constraint) data TyFun :: Type -> Type -> Type type a ~> b = TyFun a b -> Type infixr 0 ~> type family Apply (f :: k1 ~> k2) (x :: k1) :: k2 type f @@ x = f `Apply` x infixl 9 @@ type family WhyCong (x :: Type) (y :: Type) (f :: x ~> y) (a :: x) (z :: x) (e :: a :~: z) :: Type where WhyCong _ _ f a z _ = f @@ a :~: f @@ z data WhyCongSym1 (x :: Type) :: forall (a :: x) (y :: Type) (z :: x). Type ~> (x ~> y) ~> x ~> x ~> a :~: z ~> Type data WhyCongSym0 :: forall (x :: Type) (a :: x) (y :: Type) (z :: x). Type ~> Type ~> (x ~> y) ~> x ~> x ~> a :~: z ~> Type where WhyCongSym0KindInference :: forall x arg. SameKind (Apply WhyCongSym0 arg) (WhyCongSym1 arg) => WhyCongSym0 x }}} {{{ $ /opt/ghc/8.2.2/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): updateRole WhyCongSym0 arg_aYV[sk:1] [aYU :-> 4, a22o :-> 0, a22p :-> 1, a22q :-> 2, a22r :-> 3] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcTyDecls.hs:656:23 in ghc:TcTyDecls }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14880 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler