
#12785: GHC panic, `tcTyVarDetails` is missing a case -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: yes Blocked By: | Blocking: Related Tickets: #12590 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Here's a much simpler program that also trips up the same error: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeFamilies #-} module Bug (foo) where import Data.Kind (Type) foo :: forall (dk :: Type) (c :: Type -> Type) (t :: dk -> Type) (a :: Type). (dk ~ Type) => (forall (d :: dk). c (t d)) -> Maybe (c a) foo _ = Nothing }}} To make things more interesting, on GHC HEAD this errors with: {{{ $ /opt/ghc/head/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.1.20161218 for x86_64-unknown-linux): tcTyVarDetails cobox_aCE :: (dk_aCl[sk:2] :: *) ~# (* :: *) 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/basicTypes/Var.hs:461:22 in ghc:Var }}} But on GHC 8.0.1 and 8.0.2, it compiles fine! So this is actually a regression. I don't know if heisenbug's patch fixes it, nor what commit caused this regression. I'll look later today. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler