[commit: testsuite] master: Test Trac #7973 (cf46e11)
Simon Peyton Jones
simonpj at microsoft.com
Mon Jun 10 12:05:10 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/cf46e11b788b2c963156d2925977a66b1a82a5c4
>---------------------------------------------------------------
commit cf46e11b788b2c963156d2925977a66b1a82a5c4
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Mon Jun 10 11:04:29 2013 +0100
Test Trac #7973
>---------------------------------------------------------------
tests/polykinds/T7973.hs | 25 +++++++++++++++++++++++++
tests/polykinds/all.T | 1 +
2 files changed, 26 insertions(+), 0 deletions(-)
diff --git a/tests/polykinds/T7973.hs b/tests/polykinds/T7973.hs
new file mode 100644
index 0000000..05787d2
--- /dev/null
+++ b/tests/polykinds/T7973.hs
@@ -0,0 +1,25 @@
+{-# LANGUAGE DataKinds, PolyKinds, KindSignatures #-}
+{-# LANGUAGE ExistentialQuantification, UndecidableInstances, TypeFamilies #-}
+
+module Test where
+
+-- Kind-level proxies.
+data {-kind-} K (a :: *) = KP
+
+-- A type with 1 kind-polymorphic type argument.
+data T (n :: k)
+
+-- A type with 1 kind argument.
+data F (kp :: K k)
+
+-- A class with 1 kind argument.
+class (kp ~ KP) => C (kp :: K k) where
+ f :: T (a :: k) -> F kp
+
+-- A type with 1 kind argument.
+-- Contains an existentially quantified type-variable of this kind.
+data SomeT (kp :: K k) = forall (n :: k). Mk (T n)
+
+-- Show `SomeT` by converting it to `F`, using `C`.
+instance (C kp, Show (F kp)) => Show (SomeT kp) where
+ show (Mk x) = show (f x)
diff --git a/tests/polykinds/all.T b/tests/polykinds/all.T
index 00007b1..24b954b 100644
--- a/tests/polykinds/all.T
+++ b/tests/polykinds/all.T
@@ -87,3 +87,4 @@ test('T7524', normal, compile_fail,[''])
test('T7601', normal, compile,[''])
test('T7805', normal, compile_fail,[''])
test('T7916', normal, compile,[''])
+test('T7973', normal, compile,['-O'])
More information about the ghc-commits
mailing list