[GHC] #11056: Need to generate Typable info for promoted data constructors

GHC ghc-devs at haskell.org
Tue Nov 3 13:57:46 UTC 2015


#11056: Need to generate Typable info for promoted data constructors
-------------------------------------+-------------------------------------
           Reporter:  simonpj        |             Owner:
               Type:  bug            |            Status:  new
           Priority:  high           |         Milestone:  8.0.1
          Component:  Compiler       |           Version:  7.10.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Trac #10052 isn't relevant for HEAD, because HEAD generates implicit
 `Typeable` bindings for everything.  But in testing
 {{{
 {-# LANGUAGE PolyKinds, DataKinds #-}
 module Foo where
 import Data.Typeable

 data T = A | B Int

 bar :: TypeRep
 bar = typeRep (Proxy :: Proxy '[True])
 }}}
 I discovered that we aren't generating tycon-rep bindings for promoted
 data constructors.  As a result we get
 {{{
 GHC error in desugarer lookup in Foo:
   Can't find interface-file declaration for variable tc'[]
     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
 }}}

 In particular `TcTypeable.mkTypeableBinds` doesn't generate the bindings
 for the `tc'[]` and `tc':`.

 It's not hard to fix this, but it will add more top-level declarations for
 each data type decl.

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


More information about the ghc-tickets mailing list