[commit: testsuite] master: Test Trac #7609 (bdcc186)

Simon Peyton Jones simonpj at microsoft.com
Wed Jan 30 09:33:09 CET 2013


Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/bdcc18611862283aa4bf55afebda65a0f85e06a5

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

commit bdcc18611862283aa4bf55afebda65a0f85e06a5
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Jan 30 08:24:11 2013 +0000

    Test Trac #7609

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

 tests/typecheck/should_fail/T7609.hs     |    8 ++++++++
 tests/typecheck/should_fail/T7609.stderr |    6 ++++++
 tests/typecheck/should_fail/all.T        |    1 +
 3 files changed, 15 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_fail/T7609.hs b/tests/typecheck/should_fail/T7609.hs
new file mode 100644
index 0000000..242fa94
--- /dev/null
+++ b/tests/typecheck/should_fail/T7609.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE TypeOperators #-}
+
+module T7609 where
+
+data X a b
+
+f :: (a `X` a, Maybe)
+f = undefined
diff --git a/tests/typecheck/should_fail/T7609.stderr b/tests/typecheck/should_fail/T7609.stderr
new file mode 100644
index 0000000..d3430db
--- /dev/null
+++ b/tests/typecheck/should_fail/T7609.stderr
@@ -0,0 +1,6 @@
+
+T7609.hs:7:16:
+    Expecting one more argument to `Maybe'
+    The second argument of a tuple should have kind `*',
+      but `Maybe' has kind `* -> *'
+    In the type signature for `f': f :: (a `X` a, Maybe)
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index ad62ce7..1241e58 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -294,3 +294,4 @@ test('T7368a', normal, compile_fail, [''])
 test('T7545', normal, compile_fail, [''])
 test('T7279', normal, compile_fail, [''])
 test('T2247', normal, compile_fail, [''])
+test('T7609', normal, compile_fail, [''])





More information about the ghc-commits mailing list