[commit: ghc] ghc-8.2: x86 nativeGen: Fix test with mask in range [128, 255] (#13425) (85dc062)

git at git.haskell.org git at git.haskell.org
Mon Mar 27 03:00:11 UTC 2017


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

On branch  : ghc-8.2
Link       : http://ghc.haskell.org/trac/ghc/changeset/85dc0627beeed6e67329c0f8b60fb049f433585a/ghc

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

commit 85dc0627beeed6e67329c0f8b60fb049f433585a
Author: Reid Barton <rwbarton at gmail.com>
Date:   Thu Mar 23 21:02:29 2017 -0400

    x86 nativeGen: Fix test with mask in range [128,255] (#13425)
    
    My commit bdb0c43c7 optimized the encoding of instructions to test
    tag bits, but it did not always set exactly the same condition codes
    since the testb instruction does a single-byte comparison, rather
    than a full-word comparison.
    
    It would be correct to optimize the expression `x .&. 128 > 0` to
    the sequence
    
        testb $128, %al
        seta %al         ; note: 'a' for unsigned comparison,
                         ; not 'g' for signed comparison
    
    but the pretty-printer is not the right place to make this kind of
    context-sensitive optimization.
    
    Test Plan: harbormaster
    
    Reviewers: trofi, austin, bgamari, dfeuer
    
    Reviewed By: trofi, dfeuer
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D3359
    
    (cherry picked from commit caf94b062a0e37ffa7048e51447fc9486b658917)


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

85dc0627beeed6e67329c0f8b60fb049f433585a
 compiler/nativeGen/X86/Ppr.hs                                  |  6 +++++-
 testsuite/tests/codeGen/should_run/T13425.hs                   | 10 ++++++++++
 .../tests/codeGen/should_run/T13425.stdout                     |  0
 testsuite/tests/codeGen/should_run/all.T                       |  1 +
 4 files changed, 16 insertions(+), 1 deletion(-)

diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs
index 7d19e99..5044c83 100644
--- a/compiler/nativeGen/X86/Ppr.hs
+++ b/compiler/nativeGen/X86/Ppr.hs
@@ -671,8 +671,12 @@ pprInstr (TEST format src dst) = sdocWithPlatform $ \platform ->
         -- (We could handle masks larger than a single byte too,
         -- but it would complicate the code considerably
         -- and tag checks are by far the most common case.)
+        -- The mask must have the high bit clear for this smaller encoding
+        -- to be completely equivalent to the original; in particular so
+        -- that the signed comparison condition bits are the same as they
+        -- would be if doing a full word comparison. See Trac #13425.
         (OpImm (ImmInteger mask), OpReg dstReg)
-          | 0 <= mask && mask < 256 -> minSizeOfReg platform dstReg
+          | 0 <= mask && mask < 128 -> minSizeOfReg platform dstReg
         _ -> format
   in pprFormatOpOp (sLit "test") format' src dst
   where
diff --git a/testsuite/tests/codeGen/should_run/T13425.hs b/testsuite/tests/codeGen/should_run/T13425.hs
new file mode 100644
index 0000000..49d0721
--- /dev/null
+++ b/testsuite/tests/codeGen/should_run/T13425.hs
@@ -0,0 +1,10 @@
+import Data.Bits ((.&.))
+
+flags :: Int -> Int
+flags x
+  | x .&. 128 > 0 = 12
+  | otherwise = 13
+{-# NOINLINE flags #-}
+
+main :: IO ()
+main = print (flags 255)
diff --git a/libraries/base/tests/hPutBuf002.stdout b/testsuite/tests/codeGen/should_run/T13425.stdout
similarity index 100%
copy from libraries/base/tests/hPutBuf002.stdout
copy to testsuite/tests/codeGen/should_run/T13425.stdout
diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T
index b952c10..ffe4b64 100644
--- a/testsuite/tests/codeGen/should_run/all.T
+++ b/testsuite/tests/codeGen/should_run/all.T
@@ -155,3 +155,4 @@ test('T9577', [ unless(arch('x86_64') or arch('i386'),skip),
                 when(opsys('darwin'), expect_broken(12937)),
                 when(opsys('mingw32'), expect_broken(12965)),
                 only_ways(['normal']) ], compile_and_run, [''])
+test('T13425', normal, compile_and_run, ['-O'])



More information about the ghc-commits mailing list