[GHC] #12451: TemplateHaskell and Data.Typeable - tcIfaceGlobal (local): not found

GHC ghc-devs at haskell.org
Tue Aug 2 11:04:13 UTC 2016


#12451: TemplateHaskell and Data.Typeable - tcIfaceGlobal (local): not found
-------------------------------------+-------------------------------------
           Reporter:  mkloczko       |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Unknown/Multiple
  TemplateHaskell, Typeable          |
       Architecture:  x86_64         |   Type of failure:  GHC rejects
  (amd64)                            |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following code produces an ghc panic error:

 {{{#!hs
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE ScopedTypeVariables #-}

 module TH where

 import Language.Haskell.TH
 import Language.Haskell.TH.Syntax
 import Data.Typeable


 usingType :: forall a. Typeable a => a -> Q [Dec]
 usingType _ = do
     -- Try to get anything using typeRep.
     let name = (tyConName $ typeRepTyCon $ typeRep (Proxy :: Proxy a))
 `seq` "The name!"
     -- theF = "The name!"
     return [FunD (mkName "theF") [Clause [] (NormalB $ LitE $ StringL name
 )  []]]
 }}}

 {{{#!hs
 {-# LANGUAGE TemplateHaskell #-}

 module Main where
 import TH

 data A = A Int

 -- Changing the argument to (A 3) does not help.
 $(usingType (undefined :: A))

 main = putStrLn $ theF
 }}}

 The error:

 {{{
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.0.1 for x86_64-unknown-linux):
         tcIfaceGlobal (local): not found:
   $tcA
   [r5m0 :-> Type constructor ‘A’, r5m3 :-> Data constructor ‘A’,
    r5m9 :-> Identifier ‘A’]
 }}}

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


More information about the ghc-tickets mailing list