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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/452ccd5bff032bd3da73f730c607e077ef8dace2

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

commit 452ccd5bff032bd3da73f730c607e077ef8dace2
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Thu Dec 20 21:08:59 2012 +0000

    Test Trac #7368 (second example)

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

 tests/typecheck/should_fail/T7368a.hs     |   14 ++++++++++++++
 tests/typecheck/should_fail/T7368a.stderr |   10 ++++++++++
 tests/typecheck/should_fail/all.T         |    1 +
 3 files changed, 25 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_fail/T7368a.hs 
b/tests/typecheck/should_fail/T7368a.hs
new file mode 100644
index 0000000..7b11313
--- /dev/null
+++ b/tests/typecheck/should_fail/T7368a.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE Rank2Types, KindSignatures #-}
+module T7368 where
+
+newtype Bad w = Bad (forall a. (w a -> a))
+-- Bad :: forall w. (forall a. w a -> a) -> Bad w
+
+fun :: forall (f :: * -> *). f (Bad f) -> Bool
+fun (Bad x) = True 
+
+{-  f (Bad f) ~ Bad w
+-->
+    f ~ Bad
+    Bad f ~ w
+-}
diff --git a/tests/typecheck/should_fail/T7368a.stderr 
b/tests/typecheck/should_fail/T7368a.stderr
new file mode 100644
index 0000000..db0f69f
--- /dev/null
+++ b/tests/typecheck/should_fail/T7368a.stderr
@@ -0,0 +1,10 @@
+
+T7368a.hs:8:6:
+    Couldn't match kind `*' with `* -> *'
+    When matching types
+      f :: * -> *
+      Bad :: (* -> *) -> *
+    Expected type: f (Bad f)
+      Actual type: Bad t0
+    In the pattern: Bad x
+    In an equation for `fun': fun (Bad x) = True
diff --git a/tests/typecheck/should_fail/all.T 
b/tests/typecheck/should_fail/all.T
index 2e1ec6e..5899413 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -289,3 +289,4 @@ test('T6069', normal, compile_fail, [''])
 test('T7220', normal, compile_fail, [''])
 test('T7410', normal, compile_fail, [''])
 test('T7453', normal, compile_fail, [''])
+test('T7368a', normal, compile_fail, [''])



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to