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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/87425b2781f49f954b61783361be8bbfa560dc99

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

commit 87425b2781f49f954b61783361be8bbfa560dc99
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Mon Oct 8 08:36:58 2012 +0100

    Test Trac #7280

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

 tests/indexed-types/should_compile/T7280.hs |   13 +++++++++++++
 tests/indexed-types/should_compile/all.T    |    1 +
 2 files changed, 14 insertions(+), 0 deletions(-)

diff --git a/tests/indexed-types/should_compile/T7280.hs 
b/tests/indexed-types/should_compile/T7280.hs
new file mode 100644
index 0000000..daa391b
--- /dev/null
+++ b/tests/indexed-types/should_compile/T7280.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE Rank2Types, MultiParamTypeClasses, FlexibleContexts,
+   TypeFamilies, ScopedTypeVariables #-}
+
+module T7280 where
+
+type family Mutable (v :: * -> *) :: * -> * -> *
+class MVector (v :: * -> * -> *) a
+class MVector (Mutable v) a => Vector v a where
+   copy :: Monad m => Mutable v s a -> v a -> m ()
+
+data Chunk v s a = Chunk (forall m. (Monad m, Vector v a) => Mutable v s a -> 
m ())
+
+vstep (v:vs) = Chunk (\mv -> copy mv v)
diff --git a/tests/indexed-types/should_compile/all.T 
b/tests/indexed-types/should_compile/all.T
index b005962..067415d 100644
--- a/tests/indexed-types/should_compile/all.T
+++ b/tests/indexed-types/should_compile/all.T
@@ -199,5 +199,6 @@ test('T7082', normal, compile, [''])
 test('T7156', normal, compile, [''])
 test('T5591a', normal, compile, [''])
 test('T5591b', normal, compile, [''])
+test('T7280', normal, compile, [''])
 
 



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to