
#15778: GHC HEAD-only panic (zonkTcTyVarToTyVar) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.8.1 Component: Compiler | Version: 8.5 (Type checker) | Keywords: | 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 typechecks on GHC 8.0.1 through 8.6.1: {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} module Bug where import Data.Kind type a ~> b = a -> b -> Type type family Apply (f :: k1 ~> k2) (x :: k1) :: k2 data family Sing (a :: k) data Flarble (a :: Type) where MkFlarble :: Flarble Bool data instance Sing (z :: Flarble a) where SMkFlarble :: Sing MkFlarble elimFlarble :: forall a (p :: forall x. Flarble x ~> Type) (f :: Flarble a). Sing f -> Apply p MkFlarble -> Apply p f elimFlarble s@SMkFlarble pMkFlarble = case s of (_ :: Sing (MkFlarble :: Flarble probablyABadIdea)) -> pMkFlarble }}} However, it panics on GHC HEAD: {{{ $ ~/Software/ghc/inplace/bin/ghc-stage2 Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.7.20181015 for x86_64-unknown-linux): zonkTcTyVarToTyVar probablyABadIdea_aWn[tau:2] Bool Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcMType.hs:1627:34 in ghc:TcMType }}} If I replace `probablyABadIdea` with `Bool`, then it typechecks again. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15778 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler