[commit: ghc] ghc-8.2: testsuite: Make T10245 pass on 32-bit platforms (0b8263e)
git at git.haskell.org
git at git.haskell.org
Mon Mar 27 02:59:37 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.2
Link : http://ghc.haskell.org/trac/ghc/changeset/0b8263e80b6e31044f6963b0c970f481a622cc65/ghc
>---------------------------------------------------------------
commit 0b8263e80b6e31044f6963b0c970f481a622cc65
Author: Ben Gamari <ben at smart-cactus.org>
Date: Fri Mar 24 11:36:31 2017 -0400
testsuite: Make T10245 pass on 32-bit platforms
(cherry picked from commit ff6ee998e06c74bf41841a9ccf2e55a722268e91)
>---------------------------------------------------------------
0b8263e80b6e31044f6963b0c970f481a622cc65
testsuite/tests/codeGen/should_run/T10245.hs | 12 ++++++++++++
testsuite/tests/codeGen/should_run/T10245.stdout-ws-32 | 3 +++
.../should_run/{T10245.stdout => T10245.stdout-ws-64} | 0
3 files changed, 15 insertions(+)
diff --git a/testsuite/tests/codeGen/should_run/T10245.hs b/testsuite/tests/codeGen/should_run/T10245.hs
index 7094a1d..43383a3 100644
--- a/testsuite/tests/codeGen/should_run/T10245.hs
+++ b/testsuite/tests/codeGen/should_run/T10245.hs
@@ -1,11 +1,23 @@
+{-# LANGUAGE CPP #-}
+
+#include "MachDeps.h"
+
f :: Int -> String
f n = case n of
+#if WORD_SIZE_IN_BITS == 64
0x8000000000000000 -> "yes"
+#else
+ 0x80000000 -> "yes"
+#endif
_ -> "no"
{-# NOINLINE f #-}
main = do
+#if WORD_SIZE_IN_BITS == 64
let string = "0x8000000000000000"
+#else
+ let string = "0x80000000"
+#endif
let i = read string :: Integer
let i' = fromIntegral i :: Int
print i
diff --git a/testsuite/tests/codeGen/should_run/T10245.stdout-ws-32 b/testsuite/tests/codeGen/should_run/T10245.stdout-ws-32
new file mode 100644
index 0000000..a6c8f1f
--- /dev/null
+++ b/testsuite/tests/codeGen/should_run/T10245.stdout-ws-32
@@ -0,0 +1,3 @@
+2147483648
+-2147483648
+"yes"
diff --git a/testsuite/tests/codeGen/should_run/T10245.stdout b/testsuite/tests/codeGen/should_run/T10245.stdout-ws-64
similarity index 100%
rename from testsuite/tests/codeGen/should_run/T10245.stdout
rename to testsuite/tests/codeGen/should_run/T10245.stdout-ws-64
More information about the ghc-commits
mailing list