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

On branch  : master

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

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

commit babd3810867a73ef0c25d8ec2a0d159feba25211
Author: Simon Peyton Jones <[email protected]>
Date:   Tue Aug 28 14:31:35 2012 +0100

    Test Trac #7194

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

 tests/indexed-types/should_fail/T7194.hs |   20 ++++++++++++++++++++
 tests/indexed-types/should_fail/all.T    |    1 +
 2 files changed, 21 insertions(+), 0 deletions(-)

diff --git a/tests/indexed-types/should_fail/T7194.hs 
b/tests/indexed-types/should_fail/T7194.hs
new file mode 100644
index 0000000..753d177
--- /dev/null
+++ b/tests/indexed-types/should_fail/T7194.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE MultiParamTypeClasses, TypeFamilies, FlexibleContexts #-} 
+
+-- This one produced a Lint error in GHC 7.4 and 7.6
+
+module Foo where
+
+type family F a
+
+class C b where {}
+
+foo :: a -> F a
+foo x = error "urk"
+
+h :: (b -> ()) -> Int
+h = error "urk"
+
+f = h (\x -> let g :: C (F a) => a -> Int
+                 g y = length [x, foo y]
+             in ())
+
diff --git a/tests/indexed-types/should_fail/all.T 
b/tests/indexed-types/should_fail/all.T
index d7d66df..f455d46 100644
--- a/tests/indexed-types/should_fail/all.T
+++ b/tests/indexed-types/should_fail/all.T
@@ -77,3 +77,4 @@ test('T5934', normal, compile_fail, [''])
 test('T6123', normal, compile_fail, [''])
 test('ExtraTcsUntch', normal, compile_fail, [''])
 test('T7010', normal, compile_fail, [''])
+test('T7194', expect_broken(7194), compile_fail, [''])



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

Reply via email to