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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/7b35ba093aacd0b9978e23b30ea325ea968d1723

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

commit 7b35ba093aacd0b9978e23b30ea325ea968d1723
Author: Simon Peyton Jones <[email protected]>
Date:   Thu Sep 29 12:31:33 2011 +0100

    Test Trac #5515

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

 tests/indexed-types/should_fail/T5515.hs     |   17 +++++++++++++++++
 tests/indexed-types/should_fail/T5515.stderr |    8 ++++++++
 tests/indexed-types/should_fail/all.T        |    2 ++
 3 files changed, 27 insertions(+), 0 deletions(-)

diff --git a/tests/indexed-types/should_fail/T5515.hs 
b/tests/indexed-types/should_fail/T5515.hs
new file mode 100644
index 0000000..72c1733
--- /dev/null
+++ b/tests/indexed-types/should_fail/T5515.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE ConstraintKinds, FlexibleInstances, TypeFamilies,
+     MultiParamTypeClasses, FlexibleContexts, UndecidableInstances, 
ScopedTypeVariables #-}
+module T5515 where
+
+
+class ctx (Arg ctx) => Bome ctx where 
+  type BArg ctx
+instance ctx a => Bome ctx where 
+  type BArg ctx = a
+
+class C f a
+class C f (Arg f) => Some f where 
+  type Arg f
+instance C f a => Some f where 
+  type Arg f = a
+
+
diff --git a/tests/indexed-types/should_fail/T5515.stderr 
b/tests/indexed-types/should_fail/T5515.stderr
new file mode 100644
index 0000000..e1d7979
--- /dev/null
+++ b/tests/indexed-types/should_fail/T5515.stderr
@@ -0,0 +1,8 @@
+
+T5515.hs:9:3:
+    The RHS of an associated type declaration mentions type variable `a'
+      All such variables must be bound on the LHS
+
+T5515.hs:15:3:
+    The RHS of an associated type declaration mentions type variable `a'
+      All such variables must be bound on the LHS
diff --git a/tests/indexed-types/should_fail/all.T 
b/tests/indexed-types/should_fail/all.T
index a793947..15eefb6 100644
--- a/tests/indexed-types/should_fail/all.T
+++ b/tests/indexed-types/should_fail/all.T
@@ -71,3 +71,5 @@ test('T2664a', normal, compile, [''])
 test('T2544', normal, compile_fail, [''])
 test('T1897b', normal, compile_fail, [''])
 test('T5439', normal, compile_fail, [''])
+test('T5515', normal, compile_fail, [''])
+



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

Reply via email to