summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--testsuite/tests/th/T12561.hs7
-rw-r--r--testsuite/tests/th/T12561.stderr20
-rw-r--r--testsuite/tests/th/T12561A.hs23
-rw-r--r--testsuite/tests/th/all.T1
4 files changed, 51 insertions, 0 deletions
diff --git a/testsuite/tests/th/T12561.hs b/testsuite/tests/th/T12561.hs
new file mode 100644
index 0000000000..6dfef1ad30
--- /dev/null
+++ b/testsuite/tests/th/T12561.hs
@@ -0,0 +1,7 @@
+{-# Language TemplateHaskell #-}
+
+module T12561 where
+
+import T12561A
+
+main = $$(t1) + $$(t2)
diff --git a/testsuite/tests/th/T12561.stderr b/testsuite/tests/th/T12561.stderr
new file mode 100644
index 0000000000..dc4f68b2e6
--- /dev/null
+++ b/testsuite/tests/th/T12561.stderr
@@ -0,0 +1,20 @@
+
+T12561.hs:7:20: error:
+ • The exact Name ‘x’ is not in scope
+ Probable cause: you used a unique Template Haskell name (NameU),
+ perhaps via newName, but did not bind it
+ If that's it, then -ddump-splices might be useful
+ • In the result of the splice:
+ $t2
+ To see what the splice expanded to, use -ddump-splices
+ In the Template Haskell splice $$(t2)
+ In the second argument of ‘(+)’, namely ‘$$(t2)’
+
+T12561.hs:7:20: error:
+ • GHC internal error: ‘x’ is not in scope during type checking, but it passed the renamer
+ tcl_env of environment: [r3ej :-> Identifier[main::t1, TopLevelLet {} False]]
+ • In the expression: x
+ In the result of the splice:
+ $t2
+ To see what the splice expanded to, use -ddump-splices
+ In the Template Haskell splice $$(t2)
diff --git a/testsuite/tests/th/T12561A.hs b/testsuite/tests/th/T12561A.hs
new file mode 100644
index 0000000000..c3a4e93cbe
--- /dev/null
+++ b/testsuite/tests/th/T12561A.hs
@@ -0,0 +1,23 @@
+{-# Language TemplateHaskell #-}
+
+module T12561A where
+
+import Language.Haskell.TH
+import Language.Haskell.TH.Syntax
+
+import Data.IORef
+
+t1 = do
+ c1 <- [|| (1::Int) + 2 ||]
+ c2 <- [|| 3 + $$(return c1) ||]
+ return c2
+
+t2 :: Q (TExp Int)
+t2 = do
+ r <- runIO $ newIORef undefined
+ c1 <- [|| \x -> (1::Int) +
+ $$(do
+ xv <- [||x||]
+ runIO $ writeIORef r xv
+ return xv) ||]
+ runIO $ readIORef r
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 6d4a5036d7..bfd917ca4f 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -382,6 +382,7 @@ test('T12478_5', omit_ways(['ghci']), compile, ['-v0'])
test('T12503', normal, compile, ['-v0'])
test('T12513', omit_ways(['ghci']), compile_fail, ['-v0'])
test('T12530', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
+test('T12561', normal, multimod_compile_fail, ['T12561.hs', '-v0 -dsuppress-uniques'])
test('T12646', normal, compile, ['-v0'])
test('T12788', [], multimod_compile_fail,
['T12788.hs', '-v0 ' + config.ghc_th_way_flags])