[commit: testsuite] master: Add a test for #7850 (107218a)

Ian Lynagh igloo at ghc.haskell.org
Sun Jul 14 01:50:54 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/107218acfa306b50d737ab4bd08758fee874480d

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

commit 107218acfa306b50d737ab4bd08758fee874480d
Author: Ian Lynagh <ian at well-typed.com>
Date:   Sat Jul 13 20:37:31 2013 +0100

    Add a test for #7850

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

 tests/perf/should_run/T7850.hs     |   11 +++++++++++
 tests/perf/should_run/T7850.stdout |    1 +
 tests/perf/should_run/all.T        |    6 ++++++
 3 files changed, 18 insertions(+)

diff --git a/tests/perf/should_run/T7850.hs b/tests/perf/should_run/T7850.hs
new file mode 100644
index 0000000..d3124db
--- /dev/null
+++ b/tests/perf/should_run/T7850.hs
@@ -0,0 +1,11 @@
+
+{-# LANGUAGE BangPatterns #-}
+
+main :: IO ()
+main = print $ ack 4 1
+
+ack :: Int -> Int -> Int
+ack 0 !n = n+1
+ack m  0 = ack (m-1) 1
+ack m  n = ack (m-1) $ ack m (n-1)
+
diff --git a/tests/perf/should_run/T7850.stdout b/tests/perf/should_run/T7850.stdout
new file mode 100644
index 0000000..b07de00
--- /dev/null
+++ b/tests/perf/should_run/T7850.stdout
@@ -0,0 +1 @@
+65533
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index f95f751..84bb9d3 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -284,3 +284,9 @@ test('T7954',
      compile_and_run,
      ['-O'])
 
+test('T7850',
+     [stats_num_field('peak_megabytes_allocated', (4, 1)),
+      only_ways(['normal'])],
+     compile_and_run,
+     ['-O'])
+





More information about the ghc-commits mailing list