[commit: ghc] master: Add test for #12411 (184d7cb)

git at git.haskell.org git at git.haskell.org
Wed Oct 12 19:03:02 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/184d7cb8278b9c6cb3f9786a96f081d08e4640db/ghc

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

commit 184d7cb8278b9c6cb3f9786a96f081d08e4640db
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Wed Oct 12 14:57:32 2016 -0400

    Add test for #12411
    
    The fix for #12584 also fixed the problem in #12411. Let's add a test to ensure
    that it stays fixed.


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

184d7cb8278b9c6cb3f9786a96f081d08e4640db
 testsuite/tests/{driver/recomp009/Sub2.hs => th/T12411.hs} | 5 +++--
 testsuite/tests/th/T12411.stderr                           | 4 ++++
 testsuite/tests/th/all.T                                   | 1 +
 3 files changed, 8 insertions(+), 2 deletions(-)

diff --git a/testsuite/tests/driver/recomp009/Sub2.hs b/testsuite/tests/th/T12411.hs
similarity index 50%
copy from testsuite/tests/driver/recomp009/Sub2.hs
copy to testsuite/tests/th/T12411.hs
index 7ca8b12..fd8f9db 100644
--- a/testsuite/tests/driver/recomp009/Sub2.hs
+++ b/testsuite/tests/th/T12411.hs
@@ -1,3 +1,4 @@
 {-# LANGUAGE TemplateHaskell #-}
-module Sub where
-x = [| 2 |]
+module T12411 where
+
+pure @Q []
diff --git a/testsuite/tests/th/T12411.stderr b/testsuite/tests/th/T12411.stderr
new file mode 100644
index 0000000..1f34432
--- /dev/null
+++ b/testsuite/tests/th/T12411.stderr
@@ -0,0 +1,4 @@
+
+T12411.hs:4:1: error:
+    Pattern syntax in expression context: pure at Q
+    Did you mean to enable TypeApplications?
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index d6a124c..b2aee12 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -425,6 +425,7 @@ test('T12130', extra_clean(['T12130a.hi','T12130a.o']),
 test('T12403', omit_ways(['ghci']),
               compile_and_run, ['-v0 -ddump-splices -dsuppress-uniques'])
 test('T12407', omit_ways(['ghci']), compile, ['-v0'])
+test('T12411', normal, compile_fail, [''])
 test('T12478_1', omit_ways(['ghci']), compile_and_run,
      ['-v0 -dsuppress-uniques'])
 test('T12478_2', omit_ways(['ghci']), compile_and_run, ['-v0'])



More information about the ghc-commits mailing list