[GHC] #10599: Template Haskell doesn't allow `newName "type"`

GHC ghc-devs at haskell.org
Fri Jul 3 03:12:56 UTC 2015


#10599: Template Haskell doesn't allow `newName "type"`
-------------------------------------+-------------------------------------
              Reporter:  meteficha   |             Owner:
                  Type:  bug         |            Status:  new
              Priority:  normal      |         Milestone:
             Component:  Template    |           Version:  7.10.1
  Haskell                            |  Operating System:  Unknown/Multiple
              Keywords:              |   Type of failure:  None/Unknown
          Architecture:              |        Blocked By:
  Unknown/Multiple                   |   Related Tickets:
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
 Using `type` as a name is, of course, forbidden.  OTOH, `type_1` is
 allowed as a name.

 However, using GHC 7.10.1 and `ghc --make T.hs` on files:

 {{{#!hs
 -- T.hs
 {-# LANGUAGE TemplateHaskell #-}
 module T where
 import Q
 test

 -- Q.hs
 module Q where

 import Language.Haskell.TH

 test :: Q [Dec]
 test = do
   t <- newName "type"
   return
     [FunD t
       [Clause
          []
          (NormalB $ LitE $ CharL 't')
          []]]
 }}}

 Leads to the following error:

 {{{
 $ ghc --make -ddump-splices T.hs
 [2 of 2] Compiling T                ( T.hs, T.o )

 T.hs:6:1:
     Illegal variable name: ‘type’
     When splicing a TH declaration: ident_0 type_1 = type_1
 }}}

 The above example works fine for GHC 7.8.4, so it's a regression.

 Reference: https://github.com/yesodweb/persistent/issues/412

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


More information about the ghc-tickets mailing list