[GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression)
GHC
ghc-devs at haskell.org
Thu Jun 8 17:46:53 UTC 2017
#13803: 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-rc2
Resolution: | 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: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Minimizing this bug is probably going to take off a couple years of my
life...
But in any case, I've managed to reduce this down to six (!) files with
one external dependency (`haskell-gi-base`):
{{{#!hs
module GIGioInterfacesFile where
import Data.GI.Base.ShortPrelude -- from haskell-gi-base
import {-# SOURCE #-} qualified GIGioObjectsFileEnumerator as
Gio.FileEnumerator
import {-# SOURCE #-} qualified GIGioObjectsMountOperation as
Gio.MountOperation
class IsFile o
}}}
{{{#!hs
module GIGioInterfacesFile where
class IsFile o
}}}
{{{#!hs
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
module GIGioObjectsFileEnumerator where
import GHC.Exts (Constraint)
import {-# SOURCE #-} qualified GIGioInterfacesFile as Gio.File
class IsFileEnumerator o
class AttrInfo info where
type family AttrSetTypeConstraint info :: * -> Constraint
data FileEnumeratorContainerPropertyInfo
instance AttrInfo FileEnumeratorContainerPropertyInfo where
type AttrSetTypeConstraint FileEnumeratorContainerPropertyInfo =
Gio.File.IsFile
}}}
{{{#!hs
module GIGioObjectsFileEnumerator where
class IsFileEnumerator o
}}}
{{{#!hs
module GIGioObjectsMountOperation where
class IsMountOperation o
}}}
{{{#!hs
module GIGioObjectsMountOperation where
class IsMountOperation o
}}}
{{{
$ /opt/ghc/8.2.1/bin/ghci GIGioInterfacesFile.hs
GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 6] Compiling GIGioInterfacesFile[boot] ( GIGioInterfacesFile.hs-
boot, interpreted )
[2 of 6] Compiling GIGioObjectsFileEnumerator[boot] (
GIGioObjectsFileEnumerator.hs-boot, interpreted )
[3 of 6] Compiling GIGioObjectsFileEnumerator (
GIGioObjectsFileEnumerator.hs, interpreted )
[4 of 6] Compiling GIGioObjectsMountOperation[boot] (
GIGioObjectsMountOperation.hs-boot, interpreted )
[5 of 6] Compiling GIGioInterfacesFile ( GIGioInterfacesFile.hs,
interpreted )
ghc: panic! (the 'impossible' happened)
(GHC version 8.2.0.20170522 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 IsFile
which was lazily initialized by initIfaceCheck typecheckLoop,
I tried to tie the knot, but I couldn't find IsFile
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:1689:23 in
ghc:TcIface
}}}
The annoying bit is that I haven't figure out how to eliminate that
`import Data.GI.Base.ShortPrelude` from the `haskell-gi-base` library.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13803#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list