[commit: ghc] ghc-8.0: Add failing testcase for #10603 (279f080)

git at git.haskell.org git at git.haskell.org
Sat Jan 9 18:26:54 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/279f08012b4109f891900856b8c819f7340ad63e/ghc

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

commit 279f08012b4109f891900856b8c819f7340ad63e
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Sat Jan 9 18:57:40 2016 +0100

    Add failing testcase for #10603
    
    (cherry picked from commit 987f563f1a682a059eee5ab5c63e91561d6bd4dc)


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

279f08012b4109f891900856b8c819f7340ad63e
 testsuite/tests/th/T10603.hs     | 5 +++++
 testsuite/tests/th/T10603.stderr | 6 ++++++
 testsuite/tests/th/all.T         | 1 +
 3 files changed, 12 insertions(+)

diff --git a/testsuite/tests/th/T10603.hs b/testsuite/tests/th/T10603.hs
new file mode 100644
index 0000000..be42b49
--- /dev/null
+++ b/testsuite/tests/th/T10603.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T10603 where
+
+main = print $ $([| case Just 'a' of Just a -> Just ((\x -> x) a) |])
diff --git a/testsuite/tests/th/T10603.stderr b/testsuite/tests/th/T10603.stderr
new file mode 100644
index 0000000..47f2a7a
--- /dev/null
+++ b/testsuite/tests/th/T10603.stderr
@@ -0,0 +1,6 @@
+T10603.hs:5:18-68: Splicing expression
+    [| case Just 'a' of {
+         Just a_atn -> Just ((\ x_ato -> x_ato) a_atn) } |]
+  ======>
+    case Just 'a' of {
+      Just a_a4uM -> Just ((\ x_a4uN -> x_a4uN) a_a4uM) }
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index b881933..39a0aa9 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -397,3 +397,4 @@ test('T11341', normal, compile, ['-v0 -dsuppress-uniques'])
 test('T11345', normal, compile_and_run, ['-v0 -dsuppress-uniques'])
 
 test('TH_finalizer', normal, compile, ['-v0'])
+test('T10603', expect_broken(10603), compile, ['-ddump-splices'])
\ No newline at end of file



More information about the ghc-commits mailing list