[GHC] #13915: GHC 8.2 regression: "Can't find interface-file declaration" for promoted data family instance

#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 Keywords: TypeInType, | Operating System: Unknown/Multiple TypeFamilies | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Due to #12088, you can't define a data family instance and promote it in the same module. One could, up until GHC 8.2, work around this using (somewhat obscure) wisdom: define the data family instance in a separate module from where it's promoted. For example, `Bug` typechecks in GHC 8.0.1 and 8.0.2: {{{#!hs {-# LANGUAGE TypeFamilies #-} module Foo where data family T a data instance T Int = MkT }}} {{{#!hs {-# LANGUAGE TypeInType #-} module Bug where import Foo data Proxy (a :: k) data S = MkS (Proxy 'MkT) }}} However, this stopped typechecking in GHC 8.2: {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hs GHCi, version 8.2.0.20170623: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 2] Compiling Foo ( Foo.hs, interpreted ) [2 of 2] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:1:1: error: Can't find interface-file declaration for variable Foo.$tc'MkT 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 | 1 | {-# LANGUAGE TypeInType #-} | ^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13915 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: bgamari (added) * keywords: TypeInType, TypeFamilies => TypeInType, TypeFamilies, Typeable Comment: This regression was introduced in 8fa4bf9ab3f4ea4b208f4a43cc90857987e6d497 (Type-indexed Typeable). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13915#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Interestingly, GHC isn't actually so great about //using// the `Typeable` instance for `MkT`, regardless of whether it's GHC 8.0 or 8.2. If you tweak `Bug` slightly: {{{#!hs {-# LANGUAGE TypeInType #-} module Bug where import Data.Typeable (Proxy(..), typeRep) import Foo main :: IO () main = print $ typeRep (Proxy :: Proxy MkT) }}} Then it fails on both GHC 8.0 and 8.2 with a similar panic: GHC 8.0: {{{ $ /opt/ghc/8.0.2/bin/runghc Bug.hs GHC error in desugarer lookup in Bug: Can't find interface-file declaration for variable $tc'MkT 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 ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): initDs IOEnv failure }}} GHC 8.2: {{{ $ /opt/ghc/8.2.1/bin/runghc Bug.hs GHC error in desugarer lookup in Bug: Can't find interface-file declaration for variable $tc'MkT 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 ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170623 for x86_64-unknown-linux): initDs }}} So to be honest, I'm not sure how the original program typechecks on GHC 8.0, given the fragility of `MkT`'s `Typeable` instance. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13915#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#13915: GHC 8.2 regression: "Can't find interface-file declaration" for promoted data family instance -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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): Phab:D3759 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3759 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13915#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13915: GHC 8.2 regression: "Can't find interface-file declaration" for promoted
data family instance
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
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): Phab:D3759
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13915: GHC 8.2 regression: "Can't find interface-file declaration" for promoted data family instance -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: fixed | 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): Phab:D3759 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: Merged to `ghc-8.2` as 725249344e28a58d2d827f38e630d0506f4e49cf. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13915#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC