[commit: testsuite] master: Test Trac #7954 (462fa4f)
Simon Peyton Jones
simonpj at microsoft.com
Tue Jun 18 15:26:59 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/462fa4f75a93133269f22f5eb0d9ec32995b76b9
>---------------------------------------------------------------
commit 462fa4f75a93133269f22f5eb0d9ec32995b76b9
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue Jun 18 14:26:16 2013 +0100
Test Trac #7954
>---------------------------------------------------------------
tests/perf/should_run/T7954.hs | 7 +++++++
.../should_run/T7954.stdout} | 0
tests/perf/should_run/all.T | 9 +++++++++
3 files changed, 16 insertions(+), 0 deletions(-)
diff --git a/tests/perf/should_run/T7954.hs b/tests/perf/should_run/T7954.hs
new file mode 100644
index 0000000..2b86d2f
--- /dev/null
+++ b/tests/perf/should_run/T7954.hs
@@ -0,0 +1,7 @@
+module Main where
+
+norm :: [Double] -> Double
+norm = sqrt . sum . map (\x -> x*x)
+
+main :: IO ()
+main = print (norm (enumFromTo 0 10000000) > 100)
diff --git a/tests/codeGen/should_run/cgrun033.stdout b/tests/perf/should_run/T7954.stdout
similarity index 100%
copy from tests/codeGen/should_run/cgrun033.stdout
copy to tests/perf/should_run/T7954.stdout
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index 5dad870..5f99d19 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -274,3 +274,12 @@ test('T7797',
compile_and_run,
['-O'])
+test('T7954',
+ [stats_num_field('bytes allocated',
+ [(wordsize(32), 880051408, 10),
+ (wordsize(64), 1680051408, 10)]),
+ only_ways(['normal'])
+ ],
+ compile_and_run,
+ ['-O'])
+
More information about the ghc-commits
mailing list