[commit: testsuite] master: Test Trac #876 (cd7895e)
Simon Peyton Jones
simonpj at microsoft.com
Thu Feb 14 09:33:37 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/cd7895eef086ac9ff7befbea01e3b3657d42c29c
>---------------------------------------------------------------
commit cd7895eef086ac9ff7befbea01e3b3657d42c29c
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu Feb 14 08:32:39 2013 +0000
Test Trac #876
>---------------------------------------------------------------
tests/perf/should_run/T876.hs | 11 +++++++++++
.../conc006.stdout => perf/should_run/T876.stdout} | 0
tests/perf/should_run/all.T | 11 +++++++++++
3 files changed, 22 insertions(+), 0 deletions(-)
diff --git a/tests/perf/should_run/T876.hs b/tests/perf/should_run/T876.hs
new file mode 100644
index 0000000..398859f
--- /dev/null
+++ b/tests/perf/should_run/T876.hs
@@ -0,0 +1,11 @@
+-- This test allocates a lot more if length is
+-- not a good consumer
+
+module Main where
+import System.Environment (getArgs)
+
+foo :: Int -> Int
+foo n = sum [ length [i..n] | i <- [1..n] ]
+
+main = do { [arg] <- getArgs
+ ; print (foo (read arg)) }
diff --git a/tests/concurrent/should_run/conc006.stdout b/tests/perf/should_run/T876.stdout
similarity index 100%
copy from tests/concurrent/should_run/conc006.stdout
copy to tests/perf/should_run/T876.stdout
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index a8ea003..58ffe8f 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -49,6 +49,17 @@ test('lazy-bs-alloc',
compile_and_run,
['-O'])
+test('T876',
+ [stats_num_field('bytes allocated',
+ [(wordsize(64), 1263712 , 5),
+ # 2013-02-14: 1263712 (x86_64/Linux)
+ (wordsize(32), 663712, 5)]),
+ only_ways(['normal']),
+ extra_run_opts('10000')
+ ],
+ compile_and_run,
+ ['-O'])
+
# Get reproducible floating-point results on x86
if config.arch == 'i386':
sse2_opts = '-msse2'
More information about the ghc-commits
mailing list