[GHC] #15298: Support spliced function names in type signatures in TH declaration quotes

GHC ghc-devs at haskell.org
Thu Jun 21 18:56:13 UTC 2018


#15298: Support spliced function names in type signatures in TH declaration quotes
-------------------------------------+-------------------------------------
           Reporter:  ntc2           |             Owner:  (none)
               Type:  feature        |            Status:  new
  request                            |
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.4.3
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  #11129
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 There doesn't seem to be a way to splice function names into type
 signatures in Template Haskell declaration quotes `[d|...|]`. For example,
 `fDecl1` below does not work.

 According to [https://stackoverflow.com/a/32279198/470844 this
 StackOverflow answer], the approach in `fDecl2` below used to work, but it
 doesn't work with recent GHCs and is much less readable than `fDecl1`.

 {{{#!hs
 {-# LANGUAGE TemplateHaskell #-}
 import Language.Haskell.TH

 fName :: Name
 fName = mkName "f"

 fTy :: TypeQ
 fTy = [t| Int |]

 fBody :: ExpQ
 fBody = [e| 3 |]

 -- | Not allowed:
 --
 -- @
 -- error:
 --    Invalid type signature: $fName :: ...
 --    Should be of form <variable> :: <type>
 -- @
 --
 -- Similarly, using @$(varP fName) :: $fTy@ fails with an analogous
 -- error.
 fDecl1 :: DecsQ
 fDecl1 = [d| $fName        :: $fTy
              $(varP fName) = $fBody |]

 -- | Not allowed:
 --
 -- @
 -- error:
 --     Splices within declaration brackets not (yet) handled by Template
 Haskell
 -- @
 fDecl2 :: DecsQ
 fDecl2 = [d| $((:[]) <$> sigD fName fTy)
              $(varP fName) = $fBody |]
 }}}

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


More information about the ghc-tickets mailing list