[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:06:41 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
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
More information about the ghc-tickets
mailing list