
#13915: GHC 8.2 regression: "Can't find interface-file declaration" for promoted data family instance -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | TypeFamilies, Typeable Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): If you try using `MkT`'s `Typeable` instance in the same module it's defined in, it gets even crazier. This program: {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Foo where import Data.Typeable (Proxy(..), typeRep) data family T a data instance T Int = MkT main :: IO () main = print $ typeRep (Proxy :: Proxy MkT) }}} Gives the same panic on GHC 8.0.2 and 8.2.1: {{{ $ /opt/ghc/8.2.1/bin/runghc Foo.hs ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170623 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 $tc'MkT which was lazily initialized by mkDsEnvs, I tried to tie the knot, but I couldn't find $tc'MkT 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: [a1Vr :-> Identifier ‘$dShow_a1Vr’, a218 :-> Identifier ‘$dTypeable_a218’, r1qQ :-> Type constructor ‘T’, r1rU :-> Data constructor ‘MkT’, r1rV :-> Identifier ‘main’, r1uL :-> Identifier ‘$tcT’, r1v7 :-> Type constructor ‘R:TInt’, r1vc :-> Coercion axiom ‘D:R:TInt0’, r1vg :-> Identifier ‘$WMkT’, r1vh :-> Identifier ‘MkT’, r21e :-> Identifier ‘$trModule’] 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 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13915#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler