Expose variables bound in quotations to reify
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.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | goldfire, mboes, simonpj |
Operating system | |
Architecture |