[commit: ghc] wip/T12561: WIP: Add test for #12561 (6d89d7d)

git at git.haskell.org git at git.haskell.org
Thu Mar 21 20:01:02 UTC 2019


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/T12561
Link       : http://ghc.haskell.org/trac/ghc/changeset/6d89d7d41e25c3aa7e81ec65e9262914912bbb02/ghc

>---------------------------------------------------------------

commit 6d89d7d41e25c3aa7e81ec65e9262914912bbb02
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date:   Thu Mar 21 19:10:04 2019 +0000

    WIP: Add test for #12561
    
    The test still fails because it needs to filter out a line which
    mentions a unique.


>---------------------------------------------------------------

6d89d7d41e25c3aa7e81ec65e9262914912bbb02
 testsuite/tests/th/T12561.hs     |  7 +++++++
 testsuite/tests/th/T12561.stderr | 20 ++++++++++++++++++++
 testsuite/tests/th/T12561A.hs    | 23 +++++++++++++++++++++++
 testsuite/tests/th/all.T         |  1 +
 4 files changed, 51 insertions(+)

diff --git a/testsuite/tests/th/T12561.hs b/testsuite/tests/th/T12561.hs
new file mode 100644
index 0000000..6dfef1a
--- /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 0000000..dc4f68b
--- /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 0000000..c3a4e93
--- /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 c9f2065..c4f3775 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -473,3 +473,4 @@ test('T16195', normal, multimod_compile, ['T16195.hs', '-v0'])
 test('T16293b', normal, compile, [''])
 test('T16326_TH', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
 test('T14741', normal, compile_and_run, [''])
+test('T12561', normal, multimod_compile_fail, ['T12561.hs', '-v0 -dsuppress-uniques'])



More information about the ghc-commits mailing list