Repository : ssh://darcs.haskell.org//srv/darcs/testsuite On branch : master
http://hackage.haskell.org/trac/ghc/changeset/4a17fffe774fbb42129821cad50003d0e614eae1 >--------------------------------------------------------------- commit 4a17fffe774fbb42129821cad50003d0e614eae1 Author: Simon Peyton Jones <simo...@microsoft.com> Date: Mon Jan 7 11:37:07 2013 +0000 Test Trac #7436 >--------------------------------------------------------------- tests/perf/should_run/T7436.hs | 22 ++++++++++++++++++++++ tests/perf/should_run/T7436.stdout | 1 + tests/perf/should_run/all.T | 9 +++++++++ 3 files changed, 32 insertions(+), 0 deletions(-) diff --git a/tests/perf/should_run/T7436.hs b/tests/perf/should_run/T7436.hs new file mode 100644 index 0000000..5b1ff09 --- /dev/null +++ b/tests/perf/should_run/T7436.hs @@ -0,0 +1,22 @@ +{-# LANGUAGE DeriveFunctor, DeriveFoldable #-} +module Main where + +import Prelude hiding (foldr) +import Data.Foldable + +data List a = Nil | Cons a (List a) + deriving (Functor, Foldable) + +mkList :: Int -> List Int +mkList 0 = Nil +mkList n = Cons n (mkList (n-1)) + +main :: IO () +main = print $ foldr (\x y -> y) "end" (mkList n) + where n = 40000 + # Increase this to increase the difference between good and bad + # Eg 6000 takes a lot longer + # The biggest difference is not allocation or bytes used, + # but execution time! + + diff --git a/tests/perf/should_run/T7436.stdout b/tests/perf/should_run/T7436.stdout new file mode 100644 index 0000000..e0deb4b --- /dev/null +++ b/tests/perf/should_run/T7436.stdout @@ -0,0 +1 @@ +"end" diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T index 2b0dd27..08ff230 100644 --- a/tests/perf/should_run/all.T +++ b/tests/perf/should_run/all.T @@ -269,3 +269,12 @@ test('Conversions', test('T7507', omit_ways(['ghci']), compile_and_run, ['-O']) # For 7507, stack overflow is the bad case + +test('T7436', + [stats_num_field('max_bytes_used', 50000, + 100000), + # expected value: 127,000 (amd64/Linux) + only_ways(['normal']) + ], + compile_and_run, + ['-O']) _______________________________________________ Cvs-ghc mailing list Cvs-ghc@haskell.org http://www.haskell.org/mailman/listinfo/cvs-ghc