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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/71ca58f8d0d83733a709b1ca75f635151c33dd56

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

commit 71ca58f8d0d83733a709b1ca75f635151c33dd56
Author: Daniel Fischer <[email protected]>
Date:   Fri Nov 25 10:03:02 2011 +0100

    Test for #5237
    
    Test that the rewrite rules fire. Check allocation figures to not depend
    on the order of rule firings.

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

 tests/perf/should_run/T5237.hs     |   15 +++++++++++++++
 tests/perf/should_run/T5237.stdout |    1 +
 tests/perf/should_run/all.T        |   13 +++++++++++++
 3 files changed, 29 insertions(+), 0 deletions(-)

diff --git a/tests/perf/should_run/T5237.hs b/tests/perf/should_run/T5237.hs
new file mode 100644
index 0000000..6a12f5e
--- /dev/null
+++ b/tests/perf/should_run/T5237.hs
@@ -0,0 +1,15 @@
+{-# LANGUAGE BangPatterns #-}
+module Main (main) where
+
+-- Test that the rewrite rules for small exponents fire (#5237).
+-- If they don't fire, this will allocate much.
+
+fun :: Double -> Double
+fun x = go 0 1.0
+  where
+    go !acc z
+      | x < z   = acc
+      | otherwise = go (acc + 1/z^4) (z+1.0)
+
+main :: IO ()
+main = print (fun 1e7)
diff --git a/tests/perf/should_run/T5237.stdout 
b/tests/perf/should_run/T5237.stdout
new file mode 100644
index 0000000..a620a54
--- /dev/null
+++ b/tests/perf/should_run/T5237.stdout
@@ -0,0 +1 @@
+1.082323233710861
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index 2901b3e..122294c 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -204,3 +204,16 @@ test('T4474c',
      compile_and_run,
      ['-O'])
 
+test('T5237',
+     [if_wordsize(32,
+          stats_num_field('bytes allocated',  70000,
+                                              90000)),
+                           # expected value: 78328 (i386/Linux)
+      if_wordsize(64,
+          stats_num_field('bytes allocated',  90000,
+                                             130000)),
+                           # expected value: 110888 (amd64/Linux)
+     only_ways(['normal'])
+     ],
+    compile_and_run,
+    ['-O ' + sse2_opts])



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

Reply via email to