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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/8f2f883f6d55bbcca80c0c67a4065d2fd79986bc

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

commit 8f2f883f6d55bbcca80c0c67a4065d2fd79986bc
Author: Simon Peyton Jones <[email protected]>
Date:   Wed Nov 16 10:45:07 2011 +0000

    Test Trac #5625

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

 tests/simplCore/should_run/T5625.hs                |    4 ++++
 .../should_run/T5625.stderr}                       |    0 
 tests/simplCore/should_run/all.T                   |    3 +++
 3 files changed, 7 insertions(+), 0 deletions(-)

diff --git a/tests/simplCore/should_run/T5625.hs 
b/tests/simplCore/should_run/T5625.hs
new file mode 100644
index 0000000..b13eca9
--- /dev/null
+++ b/tests/simplCore/should_run/T5625.hs
@@ -0,0 +1,4 @@
+module Main where
+
+main = do { let a = \x -> seq undefined (+1)
+          ; print $ (a `seq` a [] `seq` id) [0] }
diff --git a/tests/indexed-types/should_fail/T1987b.stderr 
b/tests/simplCore/should_run/T5625.stderr
similarity index 100%
copy from tests/indexed-types/should_fail/T1987b.stderr
copy to tests/simplCore/should_run/T5625.stderr
diff --git a/tests/simplCore/should_run/all.T b/tests/simplCore/should_run/all.T
index bf89c96..265b4f9 100644
--- a/tests/simplCore/should_run/all.T
+++ b/tests/simplCore/should_run/all.T
@@ -49,3 +49,6 @@ test('T5453', normal, compile_and_run, [''])
 test('T5441', extra_clean(['T5441a.o','T5441a.hi']), 
               multimod_compile_and_run, ['T5441',''])
 test('T5603', normal, compile_and_run, [''])
+
+# Run this test *without* optimisation too
+test('T5625', [ only_ways(['normal','optasm']), exit_code(1) ], 
compile_and_run, [''])



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

Reply via email to