[commit: testsuite] master: Test Trac #7797 (442cc21)
Simon Peyton Jones
simonpj at microsoft.com
Thu May 30 14:17:11 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/442cc216c29932b6aff5b0274440e46257b82c1f
>---------------------------------------------------------------
commit 442cc216c29932b6aff5b0274440e46257b82c1f
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu May 30 12:09:08 2013 +0100
Test Trac #7797
>---------------------------------------------------------------
tests/perf/should_run/T7797.hs | 15 +++++++++++++++
.../T2838.stdout => perf/should_run/T7797.stdout} | 0
tests/perf/should_run/T7797a.hs | 12 ++++++++++++
tests/perf/should_run/all.T | 13 +++++++++++++
4 files changed, 40 insertions(+), 0 deletions(-)
diff --git a/tests/perf/should_run/T7797.hs b/tests/perf/should_run/T7797.hs
new file mode 100644
index 0000000..9329a40
--- /dev/null
+++ b/tests/perf/should_run/T7797.hs
@@ -0,0 +1,15 @@
+{-# LANGUAGE ExistentialQuantification #-}
+module Main where
+
+import T7797a
+
+data Box = forall a. (Size a) => Box a a
+
+box = Box (go 10000000) (go 10000000) where
+ go :: Int -> [Int]
+ go 0 = []
+ go n = 1 : go (n - 1)
+{-# NOINLINE box #-}
+
+main = print $ case box of
+ Box l r -> size l r
diff --git a/tests/codeGen/should_run/T2838.stdout b/tests/perf/should_run/T7797.stdout
similarity index 100%
copy from tests/codeGen/should_run/T2838.stdout
copy to tests/perf/should_run/T7797.stdout
diff --git a/tests/perf/should_run/T7797a.hs b/tests/perf/should_run/T7797a.hs
new file mode 100644
index 0000000..d06df97
--- /dev/null
+++ b/tests/perf/should_run/T7797a.hs
@@ -0,0 +1,12 @@
+module T7797a where
+
+class Size t where
+ size :: t -> t -> Int
+ burg :: t -> t
+
+instance (Ord a, Num a) => Size [a] where
+ {-# SPECIALISE instance Size [Int] #-}
+ size (x:xs) (y:ys) | x+y > 4 = size xs ys
+ | otherwise = size xs ys
+ size _ _ = 0
+ burg = error "urk"
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index 07e6d96..5dad870 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -261,3 +261,16 @@ test('T7436',
],
compile_and_run,
['-O'])
+
+test('T7797',
+ [stats_num_field('bytes allocated',
+ [(wordsize(32), 360940756, 5),
+ # expected value: 2685858140 (x86/OS X)
+ # expected: 360940756 (x86/Linux)
+ (wordsize(64), 480050944, 5)]),
+ # expected: 480050944 (amd64/Linux)
+ only_ways(['normal'])
+ ],
+ compile_and_run,
+ ['-O'])
+
More information about the ghc-commits
mailing list