[commit: ghc] master: Update tests for Trac #11039 (d1e9f82)

git at git.haskell.org git at git.haskell.org
Wed Dec 23 12:09:21 UTC 2015


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

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

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

commit d1e9f827c36f6f552a643c2e537abdf74d87c893
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Dec 23 12:09:32 2015 +0000

    Update tests for Trac #11039


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

d1e9f827c36f6f552a643c2e537abdf74d87c893
 testsuite/tests/patsyn/should_fail/T11039.hs     |  4 +++-
 testsuite/tests/patsyn/should_fail/T11039.stderr | 11 +++++++++++
 testsuite/tests/patsyn/should_fail/T11039a.hs    |  8 ++++++++
 testsuite/tests/patsyn/should_fail/all.T         |  3 ++-
 4 files changed, 24 insertions(+), 2 deletions(-)

diff --git a/testsuite/tests/patsyn/should_fail/T11039.hs b/testsuite/tests/patsyn/should_fail/T11039.hs
index 69e8d2b..fab5824 100644
--- a/testsuite/tests/patsyn/should_fail/T11039.hs
+++ b/testsuite/tests/patsyn/should_fail/T11039.hs
@@ -1,7 +1,9 @@
 {-# LANGUAGE PatternSynonyms #-}
-module Foo () where
+module T11039 where
 
 data A a = A a
 
+-- This should fail
 pattern Q :: () => (A ~ f) => a -> f a
 pattern Q a = A a
+
diff --git a/testsuite/tests/patsyn/should_fail/T11039.stderr b/testsuite/tests/patsyn/should_fail/T11039.stderr
new file mode 100644
index 0000000..2c7c663
--- /dev/null
+++ b/testsuite/tests/patsyn/should_fail/T11039.stderr
@@ -0,0 +1,11 @@
+
+T11039.hs:8:15: error:
+    • Couldn't match type ‘f’ with ‘A’
+      ‘f’ is a rigid type variable bound by
+        the type signature for pattern synonym ‘Q’:
+          forall (f :: * -> *) a. a -> f a
+        at T11039.hs:7:14
+      Expected type: f a
+        Actual type: A a
+    • In the pattern: A a
+      In the declaration for pattern synonym ‘Q’
diff --git a/testsuite/tests/patsyn/should_fail/T11039a.hs b/testsuite/tests/patsyn/should_fail/T11039a.hs
new file mode 100644
index 0000000..527a90f
--- /dev/null
+++ b/testsuite/tests/patsyn/should_fail/T11039a.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE PatternSynonyms #-}
+module T11039a where
+
+data A a = A a
+
+-- This should succeed
+pattern Q2 :: (A ~ f) => a -> f a
+pattern Q2 a = A a
diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T
index eeb405b..fbe5d58 100644
--- a/testsuite/tests/patsyn/should_fail/all.T
+++ b/testsuite/tests/patsyn/should_fail/all.T
@@ -16,7 +16,8 @@ test('records-mixing-fields', normal, compile_fail, [''])
 test('records-exquant', normal, compile_fail, [''])
 test('records-poly-update', normal, compile_fail, [''])
 test('mixed-pat-syn-record-sels', normal, compile_fail, [''])
-test('T11039', [expect_broken(11039)], compile_fail, [''])
+test('T11039', normal, compile_fail, [''])
+test('T11039a', normal, compile, [''])
 test('export-type', normal, compile_fail, [''])
 test('export-syntax', normal, compile_fail, [''])
 test('import-syntax', normal, compile_fail, [''])



More information about the ghc-commits mailing list