[commit: ghc] ghc-8.4: testsuite: Add testcase for #14754 (054abe3)
git at git.haskell.org
git at git.haskell.org
Sun Feb 4 02:11:18 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.4
Link : http://ghc.haskell.org/trac/ghc/changeset/054abe3de4a44b112f1f8155fa6be9fd19b03e1d/ghc
>---------------------------------------------------------------
commit 054abe3de4a44b112f1f8155fa6be9fd19b03e1d
Author: Ben Gamari <ben at smart-cactus.org>
Date: Sat Feb 3 19:19:08 2018 -0500
testsuite: Add testcase for #14754
(cherry picked from commit 606edbfba14b025ce85a02e5ed7c03e8a097d692)
>---------------------------------------------------------------
054abe3de4a44b112f1f8155fa6be9fd19b03e1d
testsuite/tests/codeGen/should_run/T14754.hs | 15 +++++++++++++++
testsuite/tests/codeGen/should_run/T14754.stderr | 2 ++
.../bkprun02.stdout => codeGen/should_run/T14754.stdout} | 0
testsuite/tests/codeGen/should_run/all.T | 1 +
4 files changed, 18 insertions(+)
diff --git a/testsuite/tests/codeGen/should_run/T14754.hs b/testsuite/tests/codeGen/should_run/T14754.hs
new file mode 100644
index 0000000..181659d
--- /dev/null
+++ b/testsuite/tests/codeGen/should_run/T14754.hs
@@ -0,0 +1,15 @@
+module Main where
+
+import Debug.Trace
+
+main :: IO ()
+main = print (alg 3 1)
+
+alg :: Word -> Word -> Word
+alg a b
+ | traceShow (a, b) False = undefined
+ | c < b = alg b c
+ | c > b = alg c b
+ | otherwise = c
+ where
+ c = a - b
diff --git a/testsuite/tests/codeGen/should_run/T14754.stderr b/testsuite/tests/codeGen/should_run/T14754.stderr
new file mode 100644
index 0000000..42c78ed
--- /dev/null
+++ b/testsuite/tests/codeGen/should_run/T14754.stderr
@@ -0,0 +1,2 @@
+(3,1)
+(2,1)
diff --git a/testsuite/tests/backpack/should_run/bkprun02.stdout b/testsuite/tests/codeGen/should_run/T14754.stdout
similarity index 100%
copy from testsuite/tests/backpack/should_run/bkprun02.stdout
copy to testsuite/tests/codeGen/should_run/T14754.stdout
diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T
index 145365e..9403c4b 100644
--- a/testsuite/tests/codeGen/should_run/all.T
+++ b/testsuite/tests/codeGen/should_run/all.T
@@ -166,3 +166,4 @@ test('T13825-unit',
compile_and_run,
['-package ghc'])
test('T14619', normal, compile_and_run, [''])
+test('T14754', normal, compile_and_run, [''])
More information about the ghc-commits
mailing list