[commit: ghc] wip/T16094: PPC NCG: Fix signed 64-bit compare on 32-bit (da42c43)

git at git.haskell.org git at git.haskell.org
Sat Dec 29 10:38:10 UTC 2018


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

On branch  : wip/T16094
Link       : http://ghc.haskell.org/trac/ghc/changeset/da42c43cfcfb29276deb4c0ea2801a1b01d19e12/ghc

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

commit da42c43cfcfb29276deb4c0ea2801a1b01d19e12
Author: Peter Trommler <ptrommler at acm.org>
Date:   Wed Dec 26 20:23:44 2018 +0100

    PPC NCG: Fix signed 64-bit compare on 32-bit


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

da42c43cfcfb29276deb4c0ea2801a1b01d19e12
 compiler/nativeGen/PPC/CodeGen.hs | 54 +++++++++++++++++++++++++++------------
 1 file changed, 38 insertions(+), 16 deletions(-)

diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs
index 6c5d7d2..d46bef7 100644
--- a/compiler/nativeGen/PPC/CodeGen.hs
+++ b/compiler/nativeGen/PPC/CodeGen.hs
@@ -911,22 +911,44 @@ condIntCode cond width x y = do
 condIntCode' :: Bool -> Cond -> Width -> CmmExpr -> CmmExpr -> NatM CondCode
 
 -- simple code for 64-bit on 32-bit platforms
-condIntCode' True cond W64 x y = do
-  ChildCode64 code_x x_lo <- iselExpr64 x
-  ChildCode64 code_y y_lo <- iselExpr64 y
-  let x_hi = getHiVRegFromLo x_lo
-      y_hi = getHiVRegFromLo y_lo
-      cmp  = if condUnsigned cond then CMPL else CMP
-  end_lbl <- getBlockIdNat
-  let code = code_x `appOL` code_y `appOL` toOL
-             [ cmp II32 x_hi (RIReg y_hi)
-             , BCC NE end_lbl Nothing
-             , cmp II32 x_lo (RIReg y_lo)
-             , BCC ALWAYS end_lbl Nothing
-
-             , NEWBLOCK end_lbl
-             ]
-  return (CondCode False cond code)
+condIntCode' True cond W64 x y
+  | condUnsigned cond
+  = do
+      ChildCode64 code_x x_lo <- iselExpr64 x
+      ChildCode64 code_y y_lo <- iselExpr64 y
+      let x_hi = getHiVRegFromLo x_lo
+          y_hi = getHiVRegFromLo y_lo
+      end_lbl <- getBlockIdNat
+      let code = code_x `appOL` code_y `appOL` toOL
+                 [ CMPL II32 x_hi (RIReg y_hi)
+                 , BCC NE end_lbl Nothing
+                 , CMPL II32 x_lo (RIReg y_lo)
+                 , BCC ALWAYS end_lbl Nothing
+
+                 , NEWBLOCK end_lbl
+                 ]
+      return (CondCode False cond code)
+  | otherwise
+  = do
+      ChildCode64 code_x x_lo <- iselExpr64 x
+      ChildCode64 code_y y_lo <- iselExpr64 y
+      let x_hi = getHiVRegFromLo x_lo
+          y_hi = getHiVRegFromLo y_lo
+      end_lbl <- getBlockIdNat
+      cmp_lo  <- getBlockIdNat
+      let code = code_x `appOL` code_y `appOL` toOL
+                 [ CMP II32 x_hi (RIReg y_hi)
+                 , BCC NE end_lbl Nothing
+                 , CMP II32 x_hi (RIImm (ImmInt 0))
+                 , BCC LE cmp_lo Nothing
+                 , CMPL II32 x_lo (RIReg y_lo)
+                 , BCC ALWAYS end_lbl Nothing
+                 , CMPL II32 y_lo (RIReg x_lo)
+                 , BCC ALWAYS end_lbl Nothing
+
+                 , NEWBLOCK end_lbl
+                 ]
+      return (CondCode False cond code)
 
 -- optimize pointer tag checks. Operation andi. sets condition register
 -- so cmpi ..., 0 is redundant.



More information about the ghc-commits mailing list