[GHC] #16300: Make TH always reify data types with explicit return kinds

GHC ghc-devs at haskell.org
Mon Feb 11 17:47:20 UTC 2019


#16300: Make TH always reify data types with explicit return kinds
-------------------------------------+-------------------------------------
        Reporter:  RyanGlScott       |                Owner:  (none)
            Type:  feature request   |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Template Haskell  |              Version:  8.6.3
      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 RyanGlScott):

 A different (but closely related) issue is that currently, this is
 rejected:

 {{{#!hs
 {-# LANGUAGE KindSignatures #-}
 {-# LANGUAGE TemplateHaskell #-}
 module Bug where

 import Language.Haskell.TH

 $(pure [DataD [] (mkName "D") [] (Just StarT)
               [NormalC (mkName "MkD") []] []])
 }}}
 {{{
 $ /opt/ghc/8.6.3/bin/ghc Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

 Bug.hs:7:3: error:
     Kind signatures are only allowed on GADTs
     When splicing a TH declaration: data D :: * = MkD
   |
 7 | $(pure [DataD [] (mkName "D") [] (Just StarT)
   |   ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
 }}}

 This restriction feels somewhat artificial, given that GHC can't even
 parse Haskell98-style declarations with explicit kind signatures in the
 first place (ignore the bit about `data D :: * = MkD`, as that's just a
 pretty-printing mistake). Indeed, the `Maybe Kind` field of
 `DataD`/`NewtypeD` //only// makes sense if the data type happens to be a
 GADT. If it's not a GADT, surely it doesn't do any harm to just ignore the
 `Maybe Kind`, right?

 I care about this since changing TH reification to always fill in the
 `Maybe Kind` field with `Just <...>` causes the `TH_spliceDecl3` test case
 to start failing with the "`Kind signatures are only allowed on GADTs`"
 error. If you look at the implementation of the test, you'll see why:

 {{{
 -- test splicing of reified and renamed data declarations

 module TH_spliceDecl3
 where

 import Language.Haskell.TH
 import TH_spliceDecl3_Lib

 data T = C

 $(do { TyConI d <- reify ''T; rename' d})
 }}}

 It's reifying `T` (a Haskell98 data type) and then immediately splicing
 back in. Due to the aforementioned restriction about kinds, however, this
 fails. We could dig into the reified AST and change `Just Type` to
 `Nothing` before splicing it back it, but this feels like a lot of
 unnecessary work. I propose that we just drop this restriction as well.

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


More information about the ghc-tickets mailing list