[GHC] #11629: reify returns Dec that use ConT instead of PromotedT

GHC ghc-devs at haskell.org
Mon May 9 10:28:31 UTC 2016


#11629: reify returns Dec that use ConT instead of PromotedT
-------------------------------------+-------------------------------------
        Reporter:  aavogt            |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.0.2
       Component:  Template Haskell  |              Version:  7.10.2
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by bollmann):

 Also with promoted tuples quotation with quotation brackets `[t| .. |]`
 yields a different promoted type than the type obtained by reify.
 Consider:

 {{{
 {-# LANGUAGE FlexibleInstances, KindSignatures, TemplateHaskell, DataKinds
 #-}
 module MoreBugs where

 import Language.Haskell.TH

 class D (a :: (Bool, Bool))
 instance D '(True, False)

 $(return [])

 main = do
   putStrLn $ $([t| D '(True, False) |] >>= stringE . show)
   putStrLn "vs."
   putStrLn $ $(do ClassI _ [InstanceD _ ty _] <- reify ''D
                   stringE (show ty))
 }}}

 On a recent GHC snapshot this gives:

 {{{
 AppT (ConT MoreBugs.D) (AppT (AppT (PromotedTupleT 2) (PromotedT
 GHC.Types.True)) (PromotedT GHC.Types.False))
 vs.
 AppT (ConT MoreBugs.D) (SigT (AppT (AppT (ConT GHC.Tuple.(,)) (ConT
 GHC.Types.True)) (ConT GHC.Types.False)) (AppT (AppT (TupleT 2) (ConT
 GHC.Types.Bool)) (ConT GHC.Types.Bool)))
 }}}

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


More information about the ghc-tickets mailing list