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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/f8b2b8fde595c7c5a432bac9df98d97099463fa1

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

commit f8b2b8fde595c7c5a432bac9df98d97099463fa1
Author: Simon Peyton Jones <[email protected]>
Date:   Tue Oct 2 17:14:42 2012 +0100

    Test Trac #7278

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

 tests/polykinds/T7278.hs     |    9 +++++++++
 tests/polykinds/T7278.stderr |    5 +++++
 tests/polykinds/all.T        |    1 +
 3 files changed, 15 insertions(+), 0 deletions(-)

diff --git a/tests/polykinds/T7278.hs b/tests/polykinds/T7278.hs
new file mode 100644
index 0000000..d43e60c
--- /dev/null
+++ b/tests/polykinds/T7278.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE TypeFamilies, PolyKinds, MultiParamTypeClasses #-}
+module T7278 where
+ 
+type family TF (t  :: k) :: * -> * -> *
+
+class C (t :: k) (dcs :: * -> * -> *)
+
+f :: (C (t :: k) (TF t)) => TF t p1 p0 -> t p1 p0
+f = undefined -- panic caused by (t :: k) in the signature's context
diff --git a/tests/polykinds/T7278.stderr b/tests/polykinds/T7278.stderr
new file mode 100644
index 0000000..96f8dd7
--- /dev/null
+++ b/tests/polykinds/T7278.stderr
@@ -0,0 +1,5 @@
+
+T7278.hs:8:43:
+    `t' is applied to too many type arguments
+    In the type signature for `f':
+      f :: C (t :: k) (TF t) => TF t p1 p0 -> t p1 p0
diff --git a/tests/polykinds/all.T b/tests/polykinds/all.T
index b6d193f..dc9ab14 100644
--- a/tests/polykinds/all.T
+++ b/tests/polykinds/all.T
@@ -67,5 +67,6 @@ test('T7176', normal, compile,[''])
 test('T7224', normal, compile_fail,[''])
 test('T7230', normal, compile_fail,[''])
 test('T7238', normal, compile,[''])
+test('T7278', normal, compile_fail,[''])
 
 



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to