[GHC] #8455: Core lint error with Template Haskell quotation and type lits

GHC ghc-devs at haskell.org
Fri Oct 18 02:37:38 UTC 2013


#8455: Core lint error with Template Haskell quotation and type lits
------------------------------------+-------------------------------------
       Reporter:  goldfire          |             Owner:  goldfire
           Type:  bug               |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  Template Haskell  |           Version:  7.7
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 When I compile

 {{{
 {-# LANGUAGE TemplateHaskell, DataKinds #-}

 ty = [t| 5 |]
 }}}

 I get

 {{{
 *** Core Lint errors : in result of Desugar (after optimization) ***
 <no location info>: Warning:
     In the expression: Language.Haskell.TH.Lib.numTyLit
                          (GHC.Types.I# 5)
     Argument value doesn't match argument type:
     Fun type:
         GHC.Integer.Type.Integer -> Language.Haskell.TH.Lib.TyLitQ
     Arg type: GHC.Types.Int
     Arg: GHC.Types.I# 5
 *** Offending Program ***
 Main.ty :: Language.Haskell.TH.Lib.TypeQ
 [LclIdX, Str=DmdType]
 Main.ty =
   break<0>()
   Language.Haskell.TH.Lib.litT
     (Language.Haskell.TH.Lib.numTyLit (GHC.Types.I# 5))

 *** End of Offense ***
 }}}

 I'm pretty sure I know what's going on. I will fix.

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


More information about the ghc-tickets mailing list