[commit: ghc] wip/T9136: Add a test case for #9136 (d408191)

git at git.haskell.org git at git.haskell.org
Fri May 23 13:37:05 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/T9136
Link       : http://ghc.haskell.org/trac/ghc/changeset/d4081919e78b994a9520b89187bb6ab83ffee306/ghc

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

commit d4081919e78b994a9520b89187bb6ab83ffee306
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Fri May 23 15:34:46 2014 +0200

    Add a test case for #9136
    
    The example code is set up so that if the constant folding works, no
    literal 8 is left in the code.


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

d4081919e78b994a9520b89187bb6ab83ffee306
 testsuite/tests/simplCore/should_compile/Makefile |  4 ++++
 testsuite/tests/simplCore/should_compile/T9136.hs | 14 ++++++++++++++
 testsuite/tests/simplCore/should_compile/all.T    |  4 ++++
 3 files changed, 22 insertions(+)

diff --git a/testsuite/tests/simplCore/should_compile/Makefile b/testsuite/tests/simplCore/should_compile/Makefile
index ca0d552..9c21325 100644
--- a/testsuite/tests/simplCore/should_compile/Makefile
+++ b/testsuite/tests/simplCore/should_compile/Makefile
@@ -119,3 +119,7 @@ T8221:
 T5996:
 	$(RM) -f T5996.o T5996.hi
 	'$(TEST_HC)' $(TEST_HC_OPTS) -O -c T5996.hs -ddump-simpl -dsuppress-uniques -dsuppress-all | grep y2
+
+T9136:
+	'$(TEST_HC)' $(TEST_HC_OPTS) -O -c T9136.hs -ddump-simpl -dsuppress-uniques -dsuppress-all > T9136.simpl
+	! grep -v 'Result size' T9136.simpl | grep -q -F 8
diff --git a/testsuite/tests/simplCore/should_compile/T9136.hs b/testsuite/tests/simplCore/should_compile/T9136.hs
new file mode 100644
index 0000000..4b6aed7
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T9136.hs
@@ -0,0 +1,14 @@
+module T9136 where
+
+-- In all these example, no 8 should be found in the final code
+foo1 :: Int -> Int
+foo1 x = (x + 8) - 1
+
+foo2 :: Int -> Int
+foo2 x = (8 + x) - 2
+
+foo3 :: Int -> Int -> Int
+foo3 x y = ((8 + x) + y) - 2
+
+foo4 :: Int -> Int -> Int
+foo4 x y = (8 + x) + (y - 3)
diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T
index 616b6cc..3277771 100644
--- a/testsuite/tests/simplCore/should_compile/all.T
+++ b/testsuite/tests/simplCore/should_compile/all.T
@@ -203,3 +203,7 @@ test('T8832',
      ['$MAKE -s --no-print-directory T8832'])
 test('T8848', only_ways(['optasm']), compile, ['-ddump-rule-firings'])
 test('T8848a', only_ways(['optasm']), compile, ['-ddump-rules'])
+test('T9136',
+     extra_clean(['T9136.hi', 'T9136.o', 'T9136.simpl']),
+     run_command,
+     ['$MAKE -s --no-print-directory T9136'])



More information about the ghc-commits mailing list