[GHC] #9263: Iface type variable out of scope with default associated types and polykinds

GHC ghc-devs at haskell.org
Fri Jul 4 01:43:07 UTC 2014


#9263: Iface type variable out of scope with default associated types and
polykinds
------------------------------------+-------------------------------------
       Reporter:  goldfire          |             Owner:
           Type:  bug               |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  Compiler          |           Version:  7.9
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 I have

 {{{
 {-# LANGUAGE DataKinds, PolyKinds, TypeFamilies #-}

 module A where

 import Data.Proxy

 class kproxy ~ 'KProxy => PEq (kproxy :: KProxy a) where
   type F (x :: a) :: Bool
   type F (x :: a) = False
 }}}

 {{{
 {-# LANGUAGE DataKinds, KindSignatures, TypeFamilies #-}

 module B where

 import A
 import Data.Proxy

 data Void

 instance PEq ('KProxy :: KProxy Void)
 }}}

 {{{
 module C where

 import B
 }}}

 Now, this happens in a terminal window:

 {{{
 rae:21:38:44 ~/temp> ghc A.hs
 [1 of 1] Compiling A                ( A.hs, A.o )
 rae:21:38:46 ~/temp> ghc B.hs
 [2 of 2] Compiling B                ( B.hs, B.o )
 rae:21:38:47 ~/temp> ghc C.hs
 [3 of 3] Compiling C                ( C.hs, C.o )
 The interface for ‘B’
 Declaration for R:FVoidx:
   Iface type variable out of scope:  a
 Cannot continue after interface file error
 }}}

 If any two of the files are compiled together, the error does not occur.
 The emptiness of the `Void` type is irrelevant -- the error initially
 occurred with an inhabited type.

 This is a regression from 7.8.2.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9263>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list