[GHC] #16133: TH can sneak in TypeApplications without enabling the extension

GHC ghc-devs at haskell.org
Sat Jan 5 17:36:56 UTC 2019


#16133: TH can sneak in TypeApplications without enabling the extension
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.8.1
          Component:  Template       |           Version:  8.6.3
  Haskell                            |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  GHC accepts
  Unknown/Multiple                   |  invalid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 This program compiles:

 {{{#!hs
 {-# LANGUAGE TemplateHaskell #-}
 module Bug1 where

 import Language.Haskell.TH

 $([d| f :: Int
       f = $(varE 'id `appTypeE` conT ''Int `appE` litE (integerL 42)) |])
 }}}

 But it shouldn't: this splices in code that uses `TypeApplications`, but
 the language extension isn't enabled! What's worse, this is inconsistent
 with visible kind applications, since the following code //is// rejected:

 {{{#!hs
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE TemplateHaskell #-}
 module Bug2 where

 import Data.Kind
 import Language.Haskell.TH hiding (Type)

 data P (a :: k) = MkP

 $([d| type P' = $(conT ''P `appKindT` conT ''Type) |])
 }}}
 {{{
 $ ~/Software/ghc4/inplace/bin/ghc-stage2 Bug2.hs
 [1 of 1] Compiling Bug2             ( Bug2.hs, Bug2.o )

 Bug2.hs:10:3: error:
     Illegal visible kind application ‘Type’
       Perhaps you intended to use TypeApplications
    |
 10 | $([d| type P' = $(conT ''P `appKindT` conT ''Type) |])
    |   ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
 }}}

 Let's bring the two into harmony. Patch incoming.

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


More information about the ghc-tickets mailing list