[commit: testsuite] master: Fix simplrun010 test (f937604)
Simon Peyton Jones
simonpj at microsoft.com
Thu Jan 17 15:01:51 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/f93760456692e008b2f4e51d69b6c5efe6c848d0
>---------------------------------------------------------------
commit f93760456692e008b2f4e51d69b6c5efe6c848d0
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu Jan 17 13:51:15 2013 +0000
Fix simplrun010 test
Compiler now (correctly) does not eta reduce an infinite loop,
so I had to adjust the test a bit.
>---------------------------------------------------------------
tests/simplCore/should_run/all.T | 4 ++--
tests/simplCore/should_run/simplrun010.hs | 15 ++++++++++++++-
tests/simplCore/should_run/simplrun010.stderr | 4 +++-
3 files changed, 19 insertions(+), 4 deletions(-)
diff --git a/tests/simplCore/should_run/all.T b/tests/simplCore/should_run/all.T
index fc59a0a..40c553f 100644
--- a/tests/simplCore/should_run/all.T
+++ b/tests/simplCore/should_run/all.T
@@ -18,8 +18,8 @@ test('simplrun005', normal, compile_and_run, [''])
test('simplrun007', normal, compile_and_run, [''])
test('simplrun008', normal, compile_and_run, [''])
test('simplrun009', normal, compile_and_run, [''])
-test('simplrun010', composes([extra_run_opts('24 16 8'),
- exit_code(1)])
+test('simplrun010', composes([extra_run_opts('24 16 8 +RTS -M10m -RTS'),
+ exit_code(251)])
, compile_and_run, [''])
# Really we'd like to run T2486 too, to check that its
diff --git a/tests/simplCore/should_run/simplrun010.hs b/tests/simplCore/should_run/simplrun010.hs
index 6cc79f0..eeeb482 100644
--- a/tests/simplCore/should_run/simplrun010.hs
+++ b/tests/simplCore/should_run/simplrun010.hs
@@ -1,6 +1,8 @@
{-# LANGUAGE ForeignFunctionInterface, MagicHash, UnboxedTuples #-}
-- From trac #1947
+-- Should fail with heap exhaustion
+-- See notes below with "Infinite loop here".
module Main(main) where
@@ -244,9 +246,20 @@ f20 v1 v2 =
prelude_error
(skipCAF realWorld# (str_ "Prelude.read: ambiguous parse"))
+-- Infinite loop here. It was originally:
+-- f34 v1 v2 v3 =
+-- let v336 = f34 v1 v2 v3
+-- in v336
+--
+-- But that now (correctly) just makes a non-allocating infinite loop
+-- instead of (incorrectly) eta-reducing to f34 = f34.
+-- So I've changed to an infinite, allocating loop, which makes
+-- the heap get exhausted.
f34 v1 v2 v3 =
- let v336 = f34 v1 v2 v3
+ if abs v2 < 1000 then
+ let v336 = f34 (v1+1) (-v2) v3
in v336
+ else if v2 == 2000 then 0 else v1
f38 v1 v2 =
case v1 of
diff --git a/tests/simplCore/should_run/simplrun010.stderr b/tests/simplCore/should_run/simplrun010.stderr
index 57647f1..a2a586d 100644
--- a/tests/simplCore/should_run/simplrun010.stderr
+++ b/tests/simplCore/should_run/simplrun010.stderr
@@ -1 +1,3 @@
-simplrun010: <<loop>>
+simplrun010: Heap exhausted;
+Current maximum heap size is 10485760 bytes (10 MB);
+use `+RTS -M<size>' to increase it.
More information about the ghc-commits
mailing list