[Git][ghc/ghc][wip/supersven/riscv64-ncg] Implement MO_NOT: Replace MVN

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Sat May 27 07:23:32 UTC 2023



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


Commits:
6418dd82 by Sven Tennie at 2023-05-27T09:21:41+02:00
Implement MO_NOT: Replace MVN

MVN does not exist in RV64. Replace it by pseudo-instr not's effective
assembly.

- - - - -


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
=====================================
@@ -614,8 +614,9 @@ getRegister' config plat expr
         MO_Not w -> return $ Any (intFormat w) $ \dst ->
             let w' = opRegWidth w
              in code `snocOL`
-                MVN (OpReg w' dst) (OpReg w' reg) `appOL`
-                truncateReg w' w dst -- See Note [Signed arithmetic on AArch64]
+                -- pseudo instruction `not` is `xori rd, rs, -1`
+                ann (text "not") (XORI (OpReg w' dst) (OpReg w' reg) (OpImm (ImmInt (-1)))) `appOL`
+                truncateReg w' w dst -- See Note [Signed arithmetic on RISCV64]
 
         MO_S_Neg w -> negate code w reg
         MO_F_Neg w -> return $ Any (floatFormat w) (\dst -> code `snocOL` NEG (OpReg w dst) (OpReg w reg))


=====================================
compiler/GHC/CmmToAsm/RV64/Instr.hs
=====================================
@@ -109,9 +109,9 @@ regUsageOfInstr platform instr = case instr of
   LSR dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   MOV dst src              -> usage (regOp src, regOp dst)
   MOVK dst src             -> usage (regOp src, regOp dst)
-  MVN dst src              -> usage (regOp src, regOp dst)
   -- ORI's third operand is always an immediate
   ORI dst src1 _           -> usage (regOp src1, regOp dst)
+  XORI dst src1 _          -> usage (regOp src1, regOp dst)
   ROR dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   TST src1 src2            -> usage (regOp src1 ++ regOp src2, [])
   -- 4. Branch Instructions ----------------------------------------------------
@@ -248,9 +248,9 @@ patchRegsOfInstr instr env = case instr of
     LSR o1 o2 o3   -> LSR  (patchOp o1) (patchOp o2) (patchOp o3)
     MOV o1 o2      -> MOV  (patchOp o1) (patchOp o2)
     MOVK o1 o2     -> MOVK (patchOp o1) (patchOp o2)
-    MVN o1 o2      -> MVN  (patchOp o1) (patchOp o2)
     -- o3 cannot be a register for ORI (always an immediate)
     ORI o1 o2 o3   -> ORI  (patchOp o1) (patchOp o2) (patchOp o3)
+    XORI o1 o2 o3  -> XORI  (patchOp o1) (patchOp o2) (patchOp o3)
     ROR o1 o2 o3   -> ROR  (patchOp o1) (patchOp o2) (patchOp o3)
     TST o1 o2      -> TST  (patchOp o1) (patchOp o2)
 
@@ -640,9 +640,9 @@ data Instr
     | MOVK Operand Operand
     -- | MOVN Operand Operand
     -- | MOVZ Operand Operand
-    | MVN Operand Operand -- rd = ~rn
     | ORN Operand Operand Operand -- rd = rn | ~op2
     | ORI Operand Operand Operand -- rd = rn | op2
+    | XORI Operand Operand Operand -- rd = rn `xor` imm
     | ROR Operand Operand Operand -- rd = rn ≫ rm  or  rd = rn ≫ #i, i is 6 bits
     | TST Operand Operand -- rn & op2
     -- Load and stores.
@@ -718,9 +718,9 @@ instrCon i =
       LSR{} -> "LSR"
       MOV{} -> "MOV"
       MOVK{} -> "MOVK"
-      MVN{} -> "MVN"
       ORN{} -> "ORN"
       ORI{} -> "ORI"
+      XORI{} -> "ORI"
       ROR{} -> "ROR"
       TST{} -> "TST"
       STR{} -> "STR"


=====================================
compiler/GHC/CmmToAsm/RV64/Ppr.hs
=====================================
@@ -521,9 +521,9 @@ pprInstr platform instr = case instr of
         -> lines_ [ text "\tli" <+> pprOp platform o1 <> comma <+>  pprOp platform o2 ]
     | otherwise                    -> op3 (text "\taddi") o1 o2 (OpImm (ImmInt 0))
   MOVK o1 o2    -> op2 (text "\tmovk") o1 o2
-  MVN o1 o2     -> op2 (text "\tmvn") o1 o2
   ORN o1 o2 o3  -> op3 (text "\torn") o1 o2 o3
   ORI o1 o2 o3  -> op3 (text "\tori") o1 o2 o3
+  XORI o1 o2 o3 -> op3 (text "\txori") o1 o2 o3
   ROR o1 o2 o3  -> op3 (text "\tror") o1 o2 o3
   TST o1 o2     -> op2 (text "\ttst") o1 o2
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6418dd82005f9b84fbb490756493f57cfb350f34

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6418dd82005f9b84fbb490756493f57cfb350f34
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/7b6a5c90/attachment-0001.html>


More information about the ghc-commits mailing list