[Git][ghc/ghc][wip/T23576] Remove SAL and use the equivalent SHL instead

Jaro Reinders (@Noughtmare) gitlab at gitlab.haskell.org
Fri Jul 7 14:33:25 UTC 2023



Jaro Reinders pushed to branch wip/T23576 at Glasgow Haskell Compiler / GHC


Commits:
69cdcfe5 by Jaro Reinders at 2023-07-07T16:33:17+02:00
Remove SAL and use the equivalent SHL instead

- - - - -


3 changed files:

- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs


Changes:

=====================================
compiler/GHC/CmmToAsm/X86/CodeGen.hs
=====================================
@@ -693,10 +693,10 @@ iselExpr64 (CmmMachOp (MO_Mul _) [e1,e2]) = do
                      ]
    return (RegCode64 code rhi rlo)
 
--- To shift a 64-bit number to the left we use the SHLD and SAL instructions.
+-- To shift a 64-bit number to the left we use the SHLD and SHL instructions.
 -- We use SHLD to shift the bits in @rhi@ to the left while copying
 -- high bits from @rlo@ to fill the new space in the low bits of @rhi at .
--- That leaves @rlo@ unchanged, so we use SAL to shift the bits of @rlo@ left.
+-- That leaves @rlo@ unchanged, so we use SHL to shift the bits of @rlo@ left.
 -- However, both these instructions only use the lowest 5 bits from %cl to do
 -- their shifting. So if the sixth bit (0x32) is set then we additionally move
 -- the contents of @rlo@ to @rhi@ and clear @rlo at .
@@ -713,7 +713,7 @@ iselExpr64 (CmmMachOp (MO_Shl _) [e1,e2]) = do
                 toOL [ MOV II32 (OpReg r1lo) (OpReg rlo),
                        MOV II32 (OpReg r1hi) (OpReg rhi),
                        SHLD II32 (OpReg ecx) (OpReg rlo) (OpReg rhi),
-                       SAL II32 (OpReg ecx) (OpReg rlo),
+                       SHL II32 (OpReg ecx) (OpReg rlo),
                        TEST II32 (OpImm (ImmInt 32)) (OpReg ecx),
                        JXX EQQ lbl2,
                        JXX ALWAYS lbl1,


=====================================
compiler/GHC/CmmToAsm/X86/Instr.hs
=====================================
@@ -248,7 +248,6 @@ data Instr
         -- Shifts (amount may be immediate or %cl only)
         | SHL         Format Operand{-amount-} Operand
         | SAR         Format Operand{-amount-} Operand
-        | SAL         Format Operand{-amount-} Operand
         | SHR         Format Operand{-amount-} Operand
         | SHRD        Format Operand{-amount-} Operand Operand
         | SHLD        Format Operand{-amount-} Operand Operand
@@ -400,7 +399,6 @@ regUsageOfInstr platform instr
     BSWAP  _ reg        -> mkRU [reg] [reg]
     NEGI   _ op         -> usageM op
     SHL    _ imm dst    -> usageRM imm dst
-    SAL    _ imm dst    -> usageRM imm dst
     SAR    _ imm dst    -> usageRM imm dst
     SHR    _ imm dst    -> usageRM imm dst
     SHLD   _ imm dst1 dst2 -> usageRMM imm dst1 dst2
@@ -572,7 +570,6 @@ patchRegsOfInstr instr env
     BSWAP fmt reg        -> BSWAP fmt (env reg)
     NEGI fmt op          -> patch1 (NEGI fmt) op
     SHL  fmt imm dst     -> patch1 (SHL fmt imm) dst
-    SAL  fmt imm dst     -> patch1 (SAL fmt imm) dst
     SAR  fmt imm dst     -> patch1 (SAR fmt imm) dst
     SHR  fmt imm dst     -> patch1 (SHR fmt imm) dst
     SHLD fmt imm dst1 dst2 -> patch2 (SHLD fmt imm) dst1 dst2


=====================================
compiler/GHC/CmmToAsm/X86/Ppr.hs
=====================================
@@ -726,9 +726,6 @@ pprInstr platform i = case i of
    SHL format src dst
       -> pprShift (text "shl") format src dst
 
-   SAL format src dst
-      -> pprShift (text "sal") format src dst
-
    SAR format src dst
       -> pprShift (text "sar") format src dst
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69cdcfe58588832e041fbb4f1967180fd82c36cf

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69cdcfe58588832e041fbb4f1967180fd82c36cf
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230707/fd6bbacc/attachment-0001.html>


More information about the ghc-commits mailing list