[commit: ghc] master: testsuite: Add test for #14257 (bb2a08e)
git at git.haskell.org
git at git.haskell.org
Wed Nov 22 02:11:56 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/bb2a08e1d9e4d6740f82bc2f3a844bd97bfc4a24/ghc
>---------------------------------------------------------------
commit bb2a08e1d9e4d6740f82bc2f3a844bd97bfc4a24
Author: Ben Gamari <bgamari.foss at gmail.com>
Date: Tue Nov 21 18:30:17 2017 -0500
testsuite: Add test for #14257
Subscribers: rwbarton, thomie, duog
GHC Trac Issues: #14257
Differential Revision: https://phabricator.haskell.org/D4201
>---------------------------------------------------------------
bb2a08e1d9e4d6740f82bc2f3a844bd97bfc4a24
testsuite/tests/profiling/should_run/Makefile | 8 ++++++++
testsuite/tests/profiling/should_run/T14257.hs | 16 ++++++++++++++++
.../tests/profiling/should_run/T14257.stdout | 0
testsuite/tests/profiling/should_run/all.T | 2 ++
4 files changed, 26 insertions(+)
diff --git a/testsuite/tests/profiling/should_run/Makefile b/testsuite/tests/profiling/should_run/Makefile
index 9adb0a1..33d8d9a 100644
--- a/testsuite/tests/profiling/should_run/Makefile
+++ b/testsuite/tests/profiling/should_run/Makefile
@@ -33,3 +33,11 @@ T11489:
# then continue to run and exit normally.
# Caused a segmentation fault in GHC <= 7.10.3
./T11489 +RTS -hr{} -hc
+
+.PHONY: T14257
+T14257:
+ $(RM) T14257
+ "$(TEST_HC)" -O2 --make -prof -v0 -fprof-auto T14257.hs
+ ./T14257 +RTS -hc
+ # Make sure that samples are monotonically increasing
+ awk 'BEGIN{t=0} /BEGIN_SAMPLE/{if ($$2 < t) print "uh oh", $$t, $$0; t=$$2;}' T14257.hp
diff --git a/testsuite/tests/profiling/should_run/T14257.hs b/testsuite/tests/profiling/should_run/T14257.hs
new file mode 100644
index 0000000..af67239
--- /dev/null
+++ b/testsuite/tests/profiling/should_run/T14257.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+module Main where
+
+eval :: forall a b. (a -> b -> b) -> b -> [a] -> b
+eval f b xs = load xs []
+ where
+ load :: [a] -> [a] -> b
+ load [] stk = unload b stk
+ load (x:xs) stk = load xs (x : stk)
+
+ unload :: b -> [a] -> b
+ unload v [] = v
+ unload v (x : stk) = unload ((f $! x) $! v) stk
+
+main :: IO ()
+main = print (eval (||) False (True : replicate 10000000 False))
diff --git a/libraries/base/tests/IO/IOError002.stdout b/testsuite/tests/profiling/should_run/T14257.stdout
similarity index 100%
copy from libraries/base/tests/IO/IOError002.stdout
copy to testsuite/tests/profiling/should_run/T14257.stdout
diff --git a/testsuite/tests/profiling/should_run/all.T b/testsuite/tests/profiling/should_run/all.T
index 530d2fc..7d14f77 100644
--- a/testsuite/tests/profiling/should_run/all.T
+++ b/testsuite/tests/profiling/should_run/all.T
@@ -132,3 +132,5 @@ test('toplevel_scc_1',
[''])
test('T12962', [], compile_and_run, [''])
+
+test('T14257', [], run_command, ['$MAKE -s --no-print-directory T14257'])
More information about the ghc-commits
mailing list