GHC panic while forcing the thunk for TyThing IsFile (regression)
Consider the following set of files:
-- A.hs
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
module A (AI(..)) where
import GHC.Exts (Constraint)
class AI (info :: *) where
type S info :: * -> Constraint
-- C.hs
module C () where
import {-# SOURCE #-} qualified OC as OC
import {-# SOURCE #-} qualified OV as OV
-- IF.hs
module IF where
import qualified C as C
import {-# SOURCE #-} qualified OF as OF
class IsF o
-- IF.hs-boot
module IF where
class IsF o
-- OC.hs
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE EmptyDataDecls #-}
module OC () where
import A (AI(..))
data I
instance AI I where
type S I = (~) ()
-- OC.hs-boot
module OC where
-- OF.hs
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE EmptyDataDecls #-}
module OF () where
import A (AI(..))
import {-# SOURCE #-} qualified IF as IF
data P
instance AI P where
type S P = IF.IsF
-- OF.hs-boot
module OF where
-- OV.hs
module OV () where
-- OV.hs-boot
module OV where
This works with ghc-8.0.2
and earlier versions, but fails with ghc-8.2.1
. When I run ghc IF
for 8.2.1
I get
[ 1 of 10] Compiling A ( A.hs, A.o )
[ 2 of 10] Compiling IF[boot] ( IF.hs-boot, IF.o-boot )
[ 3 of 10] Compiling OC[boot] ( OC.hs-boot, OC.o-boot )
[ 4 of 10] Compiling OC ( OC.hs, OC.o )
[ 5 of 10] Compiling OF[boot] ( OF.hs-boot, OF.o-boot )
[ 6 of 10] Compiling OF ( OF.hs, OF.o )
[ 7 of 10] Compiling OV[boot] ( OV.hs-boot, OV.o-boot )
[ 8 of 10] Compiling C ( C.hs, C.o )
[ 9 of 10] Compiling IF ( IF.hs, IF.o )
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 8.2.1 for x86_64-unknown-linux):
tcIfaceGlobal (local): not found
You are in a maze of twisty little passages, all alike.
While forcing the thunk for TyThing IsF
which was lazily initialized by initIfaceCheck typecheckLoop,
I tried to tie the knot, but I couldn't find IsF
in the current type environment.
If you are developing GHC, please read Note [Tying the knot]
and Note [Type-checking inside the knot].
Consider rebuilding GHC with profiling for a better stack trace.
Contents of current type environment: []
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/iface/TcIface.hs:1696:23 in ghc:TcIface
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
For context, this is a minimal testcase of the panic reported in #13803 (closed) for gi-gio
, which persists after fixing the panic in the minimal testcase in ticket:13803#comment:137812. (It seems like the original code was hitting more than one issue.)
Trac metadata
Trac field | Value |
---|---|
Version | 8.2.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | #13803 (closed), #13981 (closed) |
Blocking | |
CC | |
Operating system | |
Architecture |