[commit: testsuite] master: Add test case for #7938. (54a9631)

Richard Eisenberg eir at ghc.haskell.org
Sun Aug 4 18:33:26 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/54a9631efdfcf324e2de52b667ca2be8831f6c16

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

commit 54a9631efdfcf324e2de52b667ca2be8831f6c16
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Sun Aug 4 17:32:59 2013 +0100

    Add test case for #7938.

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

 tests/indexed-types/should_fail/T7938.hs     |   12 ++++++++++++
 tests/indexed-types/should_fail/T7938.stderr |    6 ++++++
 tests/indexed-types/should_fail/all.T        |    1 +
 3 files changed, 19 insertions(+)

diff --git a/tests/indexed-types/should_fail/T7938.hs b/tests/indexed-types/should_fail/T7938.hs
new file mode 100644
index 0000000..405a7e5
--- /dev/null
+++ b/tests/indexed-types/should_fail/T7938.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE TypeFamilies, PolyKinds, MultiParamTypeClasses,
+             FlexibleInstances, DataKinds #-}
+
+module T7938 where
+
+data KProxy (a :: *) = KP
+
+class Foo (a :: k1) (b :: k2) where
+  type Bar a
+
+instance Foo (a :: k1) (b :: k2) where
+  type Bar a = (KP :: KProxy k2)
\ No newline at end of file
diff --git a/tests/indexed-types/should_fail/T7938.stderr b/tests/indexed-types/should_fail/T7938.stderr
new file mode 100644
index 0000000..3ac16f1
--- /dev/null
+++ b/tests/indexed-types/should_fail/T7938.stderr
@@ -0,0 +1,6 @@
+
+T7938.hs:12:16:
+    Expected kind ‛*’, but ‛KP’ has kind ‛KProxy k2’
+    In the type ‛(KP :: KProxy k2)’
+    In the type instance declaration for ‛Bar’
+    In the instance declaration for ‛Foo (a :: k1) (b :: k2)’
diff --git a/tests/indexed-types/should_fail/all.T b/tests/indexed-types/should_fail/all.T
index ed0e070..d14f345 100644
--- a/tests/indexed-types/should_fail/all.T
+++ b/tests/indexed-types/should_fail/all.T
@@ -100,3 +100,4 @@ test('T7786', normal, compile_fail, [''])
 test('NoGood', normal, compile_fail, [''])
 test('T7967', normal, compile_fail, [''])
 
+test('T7938', normal, compile_fail, [''])
\ No newline at end of file






More information about the ghc-commits mailing list