[commit: testsuite] master: Test Trac #7645 (bb1f5b3)
Simon Peyton Jones
simonpj at microsoft.com
Thu Feb 14 18:42:57 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/bb1f5b39e4c04f1712b1519b776064d2ddc72b84
>---------------------------------------------------------------
commit bb1f5b39e4c04f1712b1519b776064d2ddc72b84
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu Feb 14 17:42:28 2013 +0000
Test Trac #7645
>---------------------------------------------------------------
tests/typecheck/should_fail/T7645.hs | 8 ++++++++
tests/typecheck/should_fail/T7645.stderr | 6 ++++++
tests/typecheck/should_fail/all.T | 1 +
3 files changed, 15 insertions(+), 0 deletions(-)
diff --git a/tests/typecheck/should_fail/T7645.hs b/tests/typecheck/should_fail/T7645.hs
new file mode 100644
index 0000000..db086c8
--- /dev/null
+++ b/tests/typecheck/should_fail/T7645.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE TypeOperators, KindSignatures #-}
+module T7645 where
+
+data (+) a b = P
+
+f :: ((+) a (a :: *), Maybe)
+f = undefined
+
diff --git a/tests/typecheck/should_fail/T7645.stderr b/tests/typecheck/should_fail/T7645.stderr
new file mode 100644
index 0000000..96bd2e4
--- /dev/null
+++ b/tests/typecheck/should_fail/T7645.stderr
@@ -0,0 +1,6 @@
+
+T7645.hs:6:23:
+ 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 (a :: *), Maybe)
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index 9cffd3d..de9cbb8 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -295,3 +295,4 @@ test('T7545', normal, compile_fail, [''])
test('T7279', normal, compile_fail, [''])
test('T2247', normal, compile_fail, [''])
test('T7609', normal, compile_fail, [''])
+test('T7645', normal, compile_fail, [''])
More information about the ghc-commits
mailing list