[Git][ghc/ghc][wip/supersven/riscv64-ncg] 2 commits: Rename UDIV -> DIVU

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Sat May 27 09:25:50 UTC 2023



Sven Tennie pushed to branch wip/supersven/riscv64-ncg at Glasgow Haskell Compiler / GHC


Commits:
3ba71edc by Sven Tennie at 2023-05-27T11:14:05+02:00
Rename UDIV -> DIVU

That's how unsigned div is called on RISCV64. This should avoid confusion.

- - - - -
1f737e0a by Sven Tennie at 2023-05-27T11:24:04+02:00
Delete unused EON

It does not exist on RISCV64.

- - - - -


3 changed files:

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


Changes:

=====================================
compiler/GHC/CmmToAsm/RV64/CodeGen.hs
=====================================
@@ -716,7 +716,7 @@ getRegister' config plat expr
                                           truncateReg (formatToWidth format_x) w reg_x `appOL`
                                           code_y `appOL`
                                           truncateReg (formatToWidth format_y) w reg_y `snocOL`
-                                          annExpr expr (UDIV (OpReg w dst) (OpReg w reg_x) (OpReg w reg_y)))
+                                          annExpr expr (DIVU (OpReg w dst) (OpReg w reg_x) (OpReg w reg_y)))
 
     -- 2. Shifts. x << n, x >> n.
     CmmMachOp (MO_Shl w) [x, (CmmLit (CmmInt n _))] | w == W32, 0 <= n, n < 32 -> do
@@ -893,7 +893,7 @@ getRegister' config plat expr
         MO_S_Rem w -> intOp True w (\d x y -> unitOL $ REM d x y)
 
         -- Unsigned multiply/divide
-        MO_U_Quot w -> intOp False w (\d x y -> unitOL $ UDIV d x y)
+        MO_U_Quot w -> intOp False w (\d x y -> unitOL $ DIVU d x y)
         MO_U_Rem w  -> intOp False w (\d x y -> unitOL $ REM d x y)
 
         -- Signed comparisons -- see Note [CSET]


=====================================
compiler/GHC/CmmToAsm/RV64/Instr.hs
=====================================
@@ -89,8 +89,7 @@ regUsageOfInstr platform instr = case instr of
   DIV dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   REM dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   SUB dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
-  -- TODO: It's named DIVU in RISCV64 -> rename
-  UDIV dst src1 src2       -> usage (regOp src1 ++ regOp src2, regOp dst)
+  DIVU dst src1 src2       -> usage (regOp src1 ++ regOp src2, regOp dst)
 
   -- 2. Bit Manipulation Instructions ------------------------------------------
   SBFM dst src _ _         -> usage (regOp src, regOp dst)
@@ -102,8 +101,6 @@ regUsageOfInstr platform instr = case instr of
   ASR dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   BIC dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   BICS dst src1 src2       -> usage (regOp src1 ++ regOp src2, regOp dst)
-  -- TODO: Unused and does not exist in RISCV64
-  EON dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   XOR dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   LSL dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   LSR dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
@@ -226,7 +223,7 @@ patchRegsOfInstr instr env = case instr of
     DIV o1 o2 o3   -> DIV (patchOp o1) (patchOp o2) (patchOp o3)
     REM o1 o2 o3   -> REM (patchOp o1) (patchOp o2) (patchOp o3)
     SUB o1 o2 o3   -> SUB  (patchOp o1) (patchOp o2) (patchOp o3)
-    UDIV o1 o2 o3  -> UDIV (patchOp o1) (patchOp o2) (patchOp o3)
+    DIVU o1 o2 o3  -> DIVU (patchOp o1) (patchOp o2) (patchOp o3)
 
     -- 2. Bit Manipulation Instructions ----------------------------------------
     SBFM o1 o2 o3 o4 -> SBFM (patchOp o1) (patchOp o2) (patchOp o3) (patchOp o4)
@@ -240,7 +237,6 @@ patchRegsOfInstr instr env = case instr of
     ASR o1 o2 o3   -> ASR  (patchOp o1) (patchOp o2) (patchOp o3)
     BIC o1 o2 o3   -> BIC  (patchOp o1) (patchOp o2) (patchOp o3)
     BICS o1 o2 o3  -> BICS (patchOp o1) (patchOp o2) (patchOp o3)
-    EON o1 o2 o3   -> EON  (patchOp o1) (patchOp o2) (patchOp o3)
     XOR o1 o2 o3   -> XOR  (patchOp o1) (patchOp o2) (patchOp o3)
     LSL o1 o2 o3   -> LSL  (patchOp o1) (patchOp o2) (patchOp o3)
     LSR o1 o2 o3   -> LSR  (patchOp o1) (patchOp o2) (patchOp o3)
@@ -609,7 +605,7 @@ data Instr
     | SMULH Operand Operand Operand
     | SMULL Operand Operand Operand
 
-    | UDIV Operand Operand Operand -- rd = rn ÷ rm
+    | DIVU Operand Operand Operand -- rd = rn ÷ rm
 
     -- 2. Bit Manipulation Instructions ----------------------------------------
     | SBFM Operand Operand Operand Operand -- rd = rn[i,j]
@@ -623,7 +619,6 @@ data Instr
     -- | ASR Operand Operand Operand -- rd = rn ≫ rm  or  rd = rn ≫ #i, i is 6 bits
     | BIC Operand Operand Operand -- rd = rn & ~op2
     | BICS Operand Operand Operand -- rd = rn & ~op2
-    | EON Operand Operand Operand -- rd = rn ⊕ ~op2
     | XOR Operand Operand Operand -- rd = rn ⊕ op2
     -- | LSL Operand Operand Operand -- rd = rn ≪ rm  or rd = rn ≪ #i, i is 6 bits
     -- | LSR Operand Operand Operand -- rd = rn ≫ rm  or rd = rn ≫ #i, i is 6 bits
@@ -692,7 +687,7 @@ instrCon i =
       SMULH{} -> "SMULH"
       SMULL{} -> "SMULL"
       SUB{} -> "SUB"
-      UDIV{} -> "UDIV"
+      DIVU{} -> "DIVU"
       SBFM{} -> "SBFM"
       UBFM{} -> "UBFM"
       UBFX{} -> "UBFX"
@@ -701,7 +696,6 @@ instrCon i =
       ASR{} -> "ASR"
       BIC{} -> "BIC"
       BICS{} -> "BICS"
-      EON{} -> "EON"
       XOR{} -> "XOR"
       LSL{} -> "LSL"
       LSR{} -> "LSR"


=====================================
compiler/GHC/CmmToAsm/RV64/Ppr.hs
=====================================
@@ -483,7 +483,7 @@ pprInstr platform instr = case instr of
     | isFloatOp o1 && isFloatOp o2 && isFloatOp o3 -> op3 (text "\tfsub") o1 o2 o3
     | isImmOp o3 -> op3 (text "\taddi") o1 o2 (negOp o3)
     | otherwise -> op3 (text "\tsub")  o1 o2 o3
-  UDIV o1 o2 o3 -> op3 (text "\tdivu") o1 o2 o3
+  DIVU o1 o2 o3 -> op3 (text "\tdivu") o1 o2 o3
 
   -- 2. Bit Manipulation Instructions ------------------------------------------
   SBFM o1 o2 o3 o4 -> op4 (text "\tsbfm") o1 o2 o3 o4
@@ -499,7 +499,6 @@ pprInstr platform instr = case instr of
   ASR o1 o2 o3  -> op3 (text "\tsra") o1 o2 o3
   BIC o1 o2 o3  -> op3 (text "\tbic") o1 o2 o3
   BICS o1 o2 o3 -> op3 (text "\tbics") o1 o2 o3
-  EON o1 o2 o3  -> op3 (text "\teon") o1 o2 o3
   XOR o1 o2 o3  -> op3 (text "\txor") o1 o2 o3
   LSL o1 o2 o3  -> op3 (text "\tsll") o1 o2 o3
   LSR o1 o2 o3  -> op3 (text "\tsrl") o1 o2 o3



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b1489bbd71b228e5296c98c6f365c44678790ccc...1f737e0a4d502070a11cc47e1ea24cd737b45093

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b1489bbd71b228e5296c98c6f365c44678790ccc...1f737e0a4d502070a11cc47e1ea24cd737b45093
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/20230527/d8947b85/attachment-0001.html>


More information about the ghc-commits mailing list