[commit: ghc] master: x86: Always generate add instruction in MO_Add2 (#9013) (71bd4e3)

git at git.haskell.org git at git.haskell.org
Mon Aug 11 13:57:49 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/71bd4e310793b9225767b66f3aa758156816632e/ghc

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

commit 71bd4e310793b9225767b66f3aa758156816632e
Author: Reid Barton <rwbarton at gmail.com>
Date:   Mon Aug 11 09:33:13 2014 -0400

    x86: Always generate add instruction in MO_Add2 (#9013)
    
    Test Plan:
     - ran validate
     - ran T9013 test with all ways
     - ran CarryOverflow test with all ways, for good measure
    
    Reviewers: austin, simonmar
    
    Reviewed By: simonmar
    
    Differential Revision: https://phabricator.haskell.org/D137


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

71bd4e310793b9225767b66f3aa758156816632e
 compiler/nativeGen/X86/CodeGen.hs        | 5 +++--
 compiler/nativeGen/X86/Instr.hs          | 8 ++++++++
 compiler/nativeGen/X86/Ppr.hs            | 3 +++
 testsuite/tests/codeGen/should_run/all.T | 5 +----
 4 files changed, 15 insertions(+), 6 deletions(-)

diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs
index 04a1820..d6fdee1 100644
--- a/compiler/nativeGen/X86/CodeGen.hs
+++ b/compiler/nativeGen/X86/CodeGen.hs
@@ -1912,9 +1912,10 @@ genCCall _ is32Bit target dest_regs args = do
         case args of
         [arg_x, arg_y] ->
             do hCode <- getAnyReg (CmmLit (CmmInt 0 width))
-               lCode <- getAnyReg (CmmMachOp (MO_Add width) [arg_x, arg_y])
                let size = intSize width
-                   reg_l = getRegisterReg platform True (CmmLocal res_l)
+               lCode <- anyReg =<< trivialCode width (ADD_CC size)
+                                     (Just (ADD_CC size)) arg_x arg_y
+               let reg_l = getRegisterReg platform True (CmmLocal res_l)
                    reg_h = getRegisterReg platform True (CmmLocal res_h)
                    code = hCode reg_h `appOL`
                           lCode reg_l `snocOL`
diff --git a/compiler/nativeGen/X86/Instr.hs b/compiler/nativeGen/X86/Instr.hs
index 172ce93..b8b81ae 100644
--- a/compiler/nativeGen/X86/Instr.hs
+++ b/compiler/nativeGen/X86/Instr.hs
@@ -204,6 +204,12 @@ data Instr
         | DIV         Size Operand              -- eax := eax:edx/op, edx := eax:edx%op
         | IDIV        Size Operand              -- ditto, but signed
 
+        -- Int Arithmetic, where the effects on the condition register
+        -- are important. Used in specialized sequences such as MO_Add2.
+        -- Do not rewrite these instructions to "equivalent" ones that
+        -- have different effect on the condition register! (See #9013.)
+        | ADD_CC      Size Operand Operand
+
         -- Simple bit-twiddling.
         | AND         Size Operand Operand
         | OR          Size Operand Operand
@@ -360,6 +366,7 @@ x86_regUsageOfInstr platform instr
     MUL2   _ src        -> mkRU (eax:use_R src []) [eax,edx]
     DIV    _ op -> mkRU (eax:edx:use_R op []) [eax,edx]
     IDIV   _ op -> mkRU (eax:edx:use_R op []) [eax,edx]
+    ADD_CC _ src dst    -> usageRM src dst
     AND    _ src dst    -> usageRM src dst
     OR     _ src dst    -> usageRM src dst
 
@@ -533,6 +540,7 @@ x86_patchRegsOfInstr instr env
     MUL2 sz src         -> patch1 (MUL2 sz) src
     IDIV sz op          -> patch1 (IDIV sz) op
     DIV sz op           -> patch1 (DIV sz) op
+    ADD_CC sz src dst   -> patch2 (ADD_CC sz) src dst
     AND  sz src dst     -> patch2 (AND  sz) src dst
     OR   sz src dst     -> patch2 (OR   sz) src dst
     XOR  sz src dst     -> patch2 (XOR  sz) src dst
diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs
index 15d2967..6e2da18 100644
--- a/compiler/nativeGen/X86/Ppr.hs
+++ b/compiler/nativeGen/X86/Ppr.hs
@@ -563,6 +563,9 @@ pprInstr (ADC size src dst)
 pprInstr (SUB size src dst) = pprSizeOpOp (sLit "sub") size src dst
 pprInstr (IMUL size op1 op2) = pprSizeOpOp (sLit "imul") size op1 op2
 
+pprInstr (ADD_CC size src dst)
+  = pprSizeOpOp (sLit "add") size src dst
+
 {- A hack.  The Intel documentation says that "The two and three
    operand forms [of IMUL] may also be used with unsigned operands
    because the lower half of the product is the same regardless if
diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T
index a5983a5..9ae7707 100644
--- a/testsuite/tests/codeGen/should_run/all.T
+++ b/testsuite/tests/codeGen/should_run/all.T
@@ -120,8 +120,5 @@ test('CopySmallArray', normal, compile_and_run, [''])
 test('CopySmallArrayStressTest', reqlib('random'), compile_and_run, [''])
 test('SizeOfSmallArray', normal, compile_and_run, [''])
 test('T9001', normal, compile_and_run, [''])
-test('T9013',
-     [ omit_ways(['ghci']),  # ghci doesn't support unboxed tuples
-       when(arch('x86') or arch('x86_64'),
-            expect_broken_for(9013, list(set(opt_ways) - set(llvm_ways)))) ],
+test('T9013', omit_ways(['ghci']),  # ghci doesn't support unboxed tuples
      compile_and_run, [''])



More information about the ghc-commits mailing list