[GHC] #14080: GHC panic while forcing the thunk for TyThing IsFile (regression)

GHC ghc-devs at haskell.org
Wed Aug 2 17:04:45 UTC 2017


#14080: GHC panic while forcing the thunk for TyThing IsFile (regression)
-------------------------------------+-------------------------------------
           Reporter:  inaki          |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1
           Keywords:  hs-boot        |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Compile-time
  Unknown/Multiple                   |  crash or panic
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  #13803, #13981
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Consider the following set of files:
 {{{#!hs
 -- A.hs
 {-# LANGUAGE KindSignatures #-}
 {-# LANGUAGE TypeFamilies #-}

 module A (AI(..)) where

 import GHC.Exts (Constraint)

 class AI (info :: *) where
     type S info :: * -> Constraint
 }}}

 {{{#!hs
 -- C.hs
 module C () where

 import {-# SOURCE #-} qualified OC as OC
 import {-# SOURCE #-} qualified OV as OV
 }}}

 {{{#!hs
 -- IF.hs
 module IF where

 import qualified C as C
 import {-# SOURCE #-} qualified OF as OF

 class IsF o
 }}}

 {{{#!hs
 -- IF.hs-boot
 module IF where

 class IsF o
 }}}

 {{{#!hs
 -- OC.hs
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE EmptyDataDecls #-}

 module OC () where

 import A (AI(..))

 data I
 instance AI I where
     type S I = (~) ()
 }}}

 {{{#!hs
 -- OC.hs-boot
 module OC where
 }}}

 {{{#!hs
 -- 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
 }}}

 {{{#!hs
 -- OF.hs-boot
 module OF where
 }}}

 {{{#!hs
 -- OV.hs
 module OV () where
 }}}

 {{{#!hs
 -- 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
 for `gi-gio`, which persists after fixing the panic in the minimal
 testcase in ticket:13803#comment:9. (It seems like the original code was
 hitting more than one issue.)

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14080>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list