[commit: ghc] wip/rae: Test #9200. (polykinds/T9200) (5d682d6)

git at git.haskell.org git at git.haskell.org
Thu Aug 7 18:07:46 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/rae
Link       : http://ghc.haskell.org/trac/ghc/changeset/5d682d6a294ce51bfdb8b4f2ceef1285c6a68129/ghc

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

commit 5d682d6a294ce51bfdb8b4f2ceef1285c6a68129
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Sun Aug 3 21:37:45 2014 -0400

    Test #9200. (polykinds/T9200)


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

5d682d6a294ce51bfdb8b4f2ceef1285c6a68129
 testsuite/tests/polykinds/T9200.hs | 19 +++++++++++++++++++
 testsuite/tests/polykinds/all.T    |  1 +
 2 files changed, 20 insertions(+)

diff --git a/testsuite/tests/polykinds/T9200.hs b/testsuite/tests/polykinds/T9200.hs
new file mode 100644
index 0000000..b74177a
--- /dev/null
+++ b/testsuite/tests/polykinds/T9200.hs
@@ -0,0 +1,19 @@
+{-# LANGUAGE PolyKinds, MultiParamTypeClasses, FlexibleContexts, DataKinds #-}
+
+module T9200 where
+
+------
+-- test CUSK on classes
+
+class C (f :: k) (a :: k2) where
+  c_meth :: D a => ()
+  
+class C () a => D a
+
+
+---------
+--- test CUSK on type synonyms
+data T1 a b c = MkT1 (S True b c)
+data T2 p q r = MkT2 (S p 5 r)
+data T3 x y q = MkT3 (S x y '())
+type S (f :: k1) (g :: k2) (h :: k3) = ((T1 f g h, T2 f g h, T3 f g h) :: *)
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index 22a159d..abb158b 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -106,3 +106,4 @@ test('T9222', normal, compile, [''])
 test('T9264', normal, compile, [''])
 test('T9263', normal, run_command, ['$MAKE -s --no-print-directory T9263'])
 test('T9063', normal, compile, [''])
+test('T9200', normal, compile, [''])



More information about the ghc-commits mailing list