[GHC] #13915: GHC 8.2 regression: "Can't find interface-file declaration" for promoted data family instance
GHC
ghc-devs at haskell.org
Sun Jul 2 16:59:15 UTC 2017
#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
More information about the ghc-tickets
mailing list