[commit: ghc] wip/rae: Added more testing for #9200. (polykinds/T9200b) (24b1791)
git at git.haskell.org
git at git.haskell.org
Fri Aug 8 19:00:15 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/rae
Link : http://ghc.haskell.org/trac/ghc/changeset/24b17914068fecf3921a2c1aa8a18e7b2a5a9fa7/ghc
>---------------------------------------------------------------
commit 24b17914068fecf3921a2c1aa8a18e7b2a5a9fa7
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Thu Aug 7 08:19:22 2014 -0400
Added more testing for #9200. (polykinds/T9200b)
>---------------------------------------------------------------
24b17914068fecf3921a2c1aa8a18e7b2a5a9fa7
testsuite/tests/polykinds/T9200b.hs | 10 ++++++++++
testsuite/tests/polykinds/T9200b.stderr | 6 ++++++
testsuite/tests/polykinds/all.T | 1 +
3 files changed, 17 insertions(+)
diff --git a/testsuite/tests/polykinds/T9200b.hs b/testsuite/tests/polykinds/T9200b.hs
new file mode 100644
index 0000000..f780aba
--- /dev/null
+++ b/testsuite/tests/polykinds/T9200b.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE TypeFamilies, PolyKinds, DataKinds #-}
+
+module T9200b where
+
+---------
+--- test CUSK on closed type families
+type family F (a :: k) where
+ F True = False
+ F False = True
+ F x = x
diff --git a/testsuite/tests/polykinds/T9200b.stderr b/testsuite/tests/polykinds/T9200b.stderr
new file mode 100644
index 0000000..5e8c730
--- /dev/null
+++ b/testsuite/tests/polykinds/T9200b.stderr
@@ -0,0 +1,6 @@
+
+T9200b.hs:8:5:
+ The first argument of ‘F’ should have kind ‘k’,
+ but ‘True’ has kind ‘Bool’
+ In the type ‘True’
+ In the type family declaration for ‘F’
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index abb158b..82c1824 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -107,3 +107,4 @@ test('T9264', normal, compile, [''])
test('T9263', normal, run_command, ['$MAKE -s --no-print-directory T9263'])
test('T9063', normal, compile, [''])
test('T9200', normal, compile, [''])
+test('T9200b', normal, compile_fail, [''])
More information about the ghc-commits
mailing list