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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/378433e7d9484a7c042e6b0421ca996f470d16f0

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

commit 378433e7d9484a7c042e6b0421ca996f470d16f0
Author: Paolo Capriotti <[email protected]>
Date:   Mon Apr 30 16:53:36 2012 +0100

    Add test for #6060

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

 tests/rename/should_fail/T6060.hs                  |    5 +++++
 .../should_fail/T6060.stderr}                      |    4 ++--
 tests/rename/should_fail/all.T                     |    1 +
 3 files changed, 8 insertions(+), 2 deletions(-)

diff --git a/tests/rename/should_fail/T6060.hs 
b/tests/rename/should_fail/T6060.hs
new file mode 100644
index 0000000..c323835
--- /dev/null
+++ b/tests/rename/should_fail/T6060.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE ParallelListComp #-}
+
+module T6060 where
+
+foo = do let bad = [True | x <- [] | y <- []]
diff --git a/tests/parser/should_fail/T3811g.stderr 
b/tests/rename/should_fail/T6060.stderr
similarity index 51%
copy from tests/parser/should_fail/T3811g.stderr
copy to tests/rename/should_fail/T6060.stderr
index 94917e5..3d381cb 100644
--- a/tests/parser/should_fail/T3811g.stderr
+++ b/tests/rename/should_fail/T6060.stderr
@@ -1,4 +1,4 @@
 
-T3811g.hs:6:8:
+T6060.hs:5:10:
     The last statement in a 'do' block must be an expression
-      _ <- return ()
+      let bad = [True | x <- [] |  y <- []]
diff --git a/tests/rename/should_fail/all.T b/tests/rename/should_fail/all.T
index a512d19..383a4d7 100644
--- a/tests/rename/should_fail/all.T
+++ b/tests/rename/should_fail/all.T
@@ -102,3 +102,4 @@ test('T5745',
 test('T5892a', normal, compile_fail, [''])
 test('T5892b', normal, compile_fail, [''])
 test('T5951', normal, compile_fail, [''])
+test('T6060', normal, compile_fail, [''])



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

Reply via email to