[GHC] #12778: Expose variables bound in quotations to reify

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider the following program: {{{ {-# LANGUAGE TemplateHaskell #-} module A where import Language.Haskell.TH as TH import Language.Haskell.TH.Syntax as TH foo :: IO () foo = $([| let x = True in $(do addModFinalizer $ do Just name <- TH.lookupValueName "x" TH.reify name >>= runIO . print [| return () |] ) |]) }}} When compiled, {{{TH.lookupValueName}}} fails to find {{{x}}}. {{{ $ inplace/bin/ghc-stage2 A.hs -fforce-recomp [1 of 1] Compiling A ( A.hs, A.o ) A.hs:7:9: error: • Pattern match failure in do expression at A.hs:9:23-31 • In the expression: (let x_a3Jy = True in return ()) In an equation for ‘foo’: foo = (let x_a3Jy = True in return ()) }}} It would make producing bindings in {{{inline-java}}} better if the type of {{{x}}} could be found in the finalizer. According to comments in ghc, {{{[| \x -> $(f [| x |]) |]}}} desugars to {{{ gensym (unpackString "x"#) `bindQ` \ x1::String -> lam (pvar x1) (f (var x1)) }}} which erases any hint that a splice point existed at all. This information is necessary to know which variables were in scope. How about we add a some new methods to the `Q` monad for the sake of marking inner splices: {{{ class Q m where ... qSpliceE :: m Exp -> m Exp qSpliceP :: m Pat -> m Pat qSpliceT :: m Type -> m Type ... }}} Now {{{[| \x -> $(f [| x |]) |]}}} would desugar to {{{ gensym (unpackString "x"#) `bindQ` \ x1::String -> lam (pvar x1) (qSpliceE (f (var x1))) }}} When the renamer executes these primitives, it would be aware of the inner splices and could treat them similarly to top-level splices. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * keywords: => template-haskell reify -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * component: Compiler => Template Haskell -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify 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 facundo.dominguez): The proposal is incomplete. For it to work, we would need to extend `Exp`, `Pat` and `Type` with constructors mimicking what `HsSpliced` does in the GHC AST. This is ok for producing code with splices inside brackets, but what about pattern mathing `Exp` values? To be comprehensive of all cases, the following code {{{ case e of TupE [LitE _, LitE _] -> ... _ -> ... }}} would need to be rewritten {{{ case e of TupE [ LitE _, LitE _] -> ... TupE [ LitE _, SplicedE _ (LitE _)] -> ... TupE [SplicedE _ (LitE _), LitE _] -> ... TupE [SplicedE _ (LitE _), SplicedE _ (LitE _)] -> ... _ -> ... }}} It could be alleviated with view patterns like {{{ case e of TupE [ dropSplicedE -> (LitE _), dropSplicedE -> (LitE _)] -> ... _ -> ... where dropSplicedE (SplicedE _ e) = e dropSplicedE e = e }}} but is it tolerable? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify 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 facundo.dominguez): Another issue with this approach is that the finalizer would not be registered by `addModFinalizer` but it is carried in the AST instead. If the user discards the result of the inner splice, the finalizer wouldn't run. The following expression does not run the finalizer, because exp carries the finalizers and it is not used in the result of the outermost splice. {{{ $(do exp@(SplicedE here_we_carry_the_finalizers (TupE [])) <- [| $(addModFinalizer (runIO (putStrLn "finalizer")) >> [| () |] ) |] [| () |] ) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3003 Wiki Page: | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * status: new => patch * differential: => Phab:D3003 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: (none) facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3003 Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Would abandon this in favor of #13608. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: (none) facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3003 Wiki Page: | -------------------------------------+------------------------------------- Comment (by mboes): Here's a clarification as to the scope of this ticket. The example in the description shows that `addModFinalizer` only knows about variables bound in the source code, but not variables introduced by a splice. This ticket is about making the types of all variables queryable in `addModFinalizer`. Whereas #13608 is much less ambitious: it only seeks to name all quasiquotes so that the type of each quasiquote can be queried in `addModFinalizer`, without resolving this ticket in its entirety. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: (none) facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3003 Wiki Page: | -------------------------------------+------------------------------------- Comment (by mboes): In the attached Diff, Simon PJ admits to, understandably, being very confused by the original use case. The description in this ticket doesn't expatiate that, so here's a quick summary. inline-java defines the `java` quasiquoter, which stands for a call to a *typed* static Java method (with the antiquotation variables being the arguments): {{{ jadd :: Int32 -> Int32 -> IO Int32 jadd x y = do [java| { return $x + $y } |] }}} At compile time, we need to add somewhere the definition of this static method. Something like: {{{ public static int wrapperFun(int x, int y) { return x + y; } }}} At runtime, we need to call this method. Note that the user doesn't need to specify the Java types of antiquotation variables, nor the Java return type. Those are inferred from the types in the Haskell context of quasiquote (`Int32` maps to Java's `int`, `Bool` maps to `boolean` etc). We use `addModFinalizer` to compute the signature of the Java method at the very end of type checking a module, at a time when the full types of all the local variables in all contexts are known. Getting the type of antiquotation variables this way works fine in 8.0.2. But getting the expected return type of a quasiquotation and inferring a Java return type is not currently possible. So e.g. above, we can know that `x` and `y` are `int`, because we know that Haskell side `x` and `y` have type `Int32`. But we can't know that the return type is also `int`, because even if the quasiquote expansion is something like {{{ let result = <java method call> in result }}} The type of `result` isn't available, even at the point where module finalizers are executed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: (none) facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3003 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): That's helpful. So you can do it today, like this: {{{ jadd :: Int32 -> Int32 -> IO Int32 jadd x y = let r = [java| { return $x + $y } |] in r }}} But that's a bit painful to write. All this `addModFinalizer` stuff needs careful documentation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: (none) facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3003 Wiki Page: | -------------------------------------+------------------------------------- Comment (by mboes): Replying to [comment:9 simonpj]:
That's helpful. So you can do it today, [...] but that's a bit painful to write.
That's right. And not something I'm keen to ask my users to have to write. #13608 proposes to make the exact style of your example (giving a name to quasiquote results) the default desugaring for all quasiquotes. The semantics I'd expect for `addModFinalizer` is: * Runs ''after'' all variables everywhere in the module have a type (including after TH expansion). * Like any `Q` action, the finalizer is allowed to perform I/O. * ''Any'' variable that is in context of the finalizer at the creation site can have its type reified. * The order of execution of each finalizer, if there are several, is undefined. This ticket proposes to extend the set of reifiable variables to include in addition: * variables in the scope of the `Q` action that created the finalizer. Not all of these will have types by the time the finalizer runs, because some variables might never be spliced in. But those that do, should have their type available in the finalizer. #13608 is a much more modest change in comparison. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: (none) facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3003 Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Another way to address this. We make {{{ $([| let x = True in $(q) |]) }}} desugar to {{{ $(return (LetE [ x = True ] (Splice q))) }}} where `Splice :: Q Exp -> Exp` is a new constructor of the datatype `Language.Haskell.TH.Syntax.Exp`. The compiler runs first the outer splice which becomes {{{ let x = True in $(q) }}} and then it runs the inner splice $(q) as if it were a regular top-level splice. Pros: It makes inner splices work pretty much as outer splices. Cons: This probably is a bigger change in the compiler (hopefully not too big). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: (none) facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3003 Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Regarding the previous proposal, some code might break because this code {{{ do exp <- q [| let x = True in $(return exp) |] }}} stops being equivalent to {{{[| let x = True in $(q) |]}}}. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: (none) facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3003 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): But see #13608 comment:15 and following, for an idea that might submsume this (distressingly complicated) ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12778#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC