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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/7f7f3a3250f8e56f9998a9eb85fedb46f56e0e68

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

commit 7f7f3a3250f8e56f9998a9eb85fedb46f56e0e68
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Fri Nov 23 16:57:20 2012 +0000

    Test Trac #7438

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

 tests/polykinds/Makefile     |    5 +++++
 tests/polykinds/T7438.hs     |    6 ++++++
 tests/polykinds/T7438.stderr |   21 +++++++++++++++++++++
 tests/polykinds/T7438a.hs    |    8 ++++++++
 tests/polykinds/all.T        |    2 +-
 5 files changed, 41 insertions(+), 1 deletions(-)

diff --git a/tests/polykinds/Makefile b/tests/polykinds/Makefile
index d52dd9c..bfeac5b 100644
--- a/tests/polykinds/Makefile
+++ b/tests/polykinds/Makefile
@@ -27,3 +27,8 @@ T7022:
        '$(TEST_HC)' $(TEST_HC_OPTS) -c T7022a.hs
        '$(TEST_HC)' $(TEST_HC_OPTS) -c T7022b.hs -v0
        -'$(TEST_HC)' $(TEST_HC_OPTS) -c -v0 T7022.hs
+
+T7438:
+       $(RM) -f T7438.hi T7438.o T7438a.hi T7438a.o
+       '$(TEST_HC)' $(TEST_HC_OPTS) -c T7438a.hs
+       '$(TEST_HC)' $(TEST_HC_OPTS) -c T7438.hs
diff --git a/tests/polykinds/T7438.hs b/tests/polykinds/T7438.hs
new file mode 100644
index 0000000..3c559d7
--- /dev/null
+++ b/tests/polykinds/T7438.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE PolyKinds, GADTs, KindSignatures, DataKinds, FlexibleInstances #-}
+
+module T7438 where
+import T7438a
+
+go Nil acc = acc
diff --git a/tests/polykinds/T7438.stderr b/tests/polykinds/T7438.stderr
new file mode 100644
index 0000000..ba76601
--- /dev/null
+++ b/tests/polykinds/T7438.stderr
@@ -0,0 +1,21 @@
+
+T7438.hs:6:14:
+    Couldn't match expected type `t1' with actual type `t'
+      `t' is untouchable
+        inside the constraints (t2 ~ t3)
+        bound by a pattern with constructor
+                   Nil :: forall (k :: BOX) (a :: k). Thrist k a a,
+                 in an equation for `go'
+        at T7438.hs:6:4-6
+      `t' is a rigid type variable bound by
+          the inferred type of go :: Thrist k t2 t3 -> t -> t1
+          at T7438.hs:6:1
+      `t1' is a rigid type variable bound by
+           the inferred type of go :: Thrist k t2 t3 -> t -> t1
+           at T7438.hs:6:1
+    Relevant bindings include
+      go :: Thrist k t2 t3 -> t -> t1 (bound at T7438.hs:6:1)
+      acc :: t (bound at T7438.hs:6:8)
+    In the expression: acc
+    In an equation for `go': go Nil acc = acc
+make[2]: *** [T7438] Error 1
diff --git a/tests/polykinds/T7438a.hs b/tests/polykinds/T7438a.hs
new file mode 100644
index 0000000..f48ed98
--- /dev/null
+++ b/tests/polykinds/T7438a.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE PolyKinds, GADTs, KindSignatures, DataKinds, FlexibleInstances #-}
+
+module T7438a where
+
+data Thrist :: k -> k -> * where
+  Nil :: Thrist a a
+
+
diff --git a/tests/polykinds/all.T b/tests/polykinds/all.T
index af25e6d..5a7b460 100644
--- a/tests/polykinds/all.T
+++ b/tests/polykinds/all.T
@@ -79,4 +79,4 @@ test('T7347', normal, compile_fail,[''])
 test('T7341', normal, compile_fail,[''])
 test('T7422', normal, compile,[''])
 test('T7433', normal, compile_fail,[''])
-
+test('T7438', exit_code(2), run_command, ['$MAKE -s --no-print-directory 
T7438'])



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

Reply via email to