Actually, I think your hypothesis wasn't too far off, bgamari. Here's a minimal example which triggers the panic:
{-# LANGUAGE TemplateHaskell #-}moduleBugwhereimportLanguage.Haskell.TH.LibimportLanguage.Haskell.TH.Syntaxmain::IO()main=print$(conE(mkNameG_v"ghc-prim""GHC.Types""True"))
$ ghc/inplace/bin/ghc-stage2 Bug2.hs[1 of 1] Compiling Bug ( Bug2.hs, Bug2.o )ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.5.20180616 for x86_64-unknown-linux): ASSERT failed! True Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1164:37 in ghc:Outputable pprPanic, called at compiler/utils/Outputable.hs:1223:5 in ghc:Outputable assertPprPanic, called at compiler/typecheck/TcHsSyn.hs:655:67 in ghc:TcHsSyn
It turns out that I was using conE (mkNameG_v "ghc-prim" "GHC.Types" "True") in deriving-compat. Oops!
• Can't find interface-file declaration for data constructor GHC.Base.id Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error • In the expression: (GHC.Base.id) In an equation for ‘it’: it = (GHC.Base.id)
I suppose we want something like that last error if we try to use $(conE (mkNameG_v "ghc-prim" "GHC.Types" "True")) as in ticket:15270#comment:155053. That being said, I can't figure out why we don't //currently// get that error. After all, that error message is caused by looking up a Name in an EPS and failing, so if $(conE (mkNameG_v "ghc-prim" "GHC.Types" "True")) isn't erroring, does that mean that a value named True //is// located in the EPS?
I'm afraid I don't know how to proceed at this point, so do you think you could look at this, Ben?