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

#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

#15298: Support spliced function names in type signatures in TH declaration quotes -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #6089 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ntc2): * related: #11129 => #6089 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15298#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15298: Support spliced function names in type signatures in TH declaration quotes -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #6089 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tmobile): Wow, just stumbled upon this. It's a rather surprising limitation. Anyone familiar with TH know what it might take to fix this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15298#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15298: Support spliced function names in type signatures in TH declaration quotes -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #6089 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mikelpr): I hit this too. I'm working with yesod+persistent, and I want to expose GET+PUT with JSON for some tables, and all they differ in are the function names and the datatypes they use for the key, and I can't generate these mainly same functions for the routes with [d| get$(funame)R put$(funame)R ... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15298#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15298: Support spliced function names in type signatures in TH declaration quotes -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #6089 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I don't think this would be too hard to fix. What you want is the ability to splice into a ''binding'' position, a place where a `Name` occurs. We already have the ability to splice into a ''pattern'', and indeed you can say {{{ fDecl1 :: DecsQ fDecl1 = [d| $(varP fName) = $fBody |] }}} where we are splicing a pattern on the LHS of a declaration `<pat> = <expr>`. But that won't work for type signatures where you want a `Name`. If we had {{{ fName :: Q Name fName = ... }}} then we jolly well ought to be able to splice it in in place of a name, even in (say) data type declarations {{{ fDecl1 :: DecsQ fDecl1 = [d| data $fName = A | B |] }}} Nothing truly tricky there. But it'd be some work to implement: * A number of places in `HsSyn` that currently have a `Name`, or more precisely `(IdP pass)`, would need an extra constructor for a splice. Specifically: * The `tcdLName` field of a `TyClDecl` * The `fun_id` field of a `HsBindLR` * The second field of a `TypeSig` in the `Sig` type -- and perhaps other constructors too. * The renamer would have to run those splices. * We can't do dependency analysis until we'd run those splices, because we don't know what's being bound. (That is already the case with pattern bindings that have a splice.) But maybe that doesn't matter, because the renamer will run those splices, maybe the dependency analysis occurs after that. I'm not quite sure. Any volunteers? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15298#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC