[Git][ghc/ghc][wip/supersven/riscv64-ncg] CmmLoad: Load sub-words unsigned (no sign-extension)

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Fri Jul 7 18:04:09 UTC 2023



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


Commits:
b21e0985 by Sven Tennie at 2023-07-07T20:01:41+02:00
CmmLoad: Load sub-words unsigned (no sign-extension)

The contract is that each operation should leave sub-words
zero-extended.

This fixes the test (test-primops):

//    Failed:
//    0::W64 - (~(zext[W32→W64](load[W32](0x8c::W64))))
//    ((0 :: bits64) - (~%zx64(bits32[buffer + (140 :: bits64)])))
//    0x8f8e8d8d /= 0xffffffff8f8e8d8d

test(bits64 buffer) {
    bits64 ret;
    ret = ((0 :: bits64) - (~%zx64(bits32[buffer + (140 :: bits64)])));
    return (ret);
}

- - - - -


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
=====================================
@@ -559,9 +559,16 @@ getRegister' config plat expr =
         CmmBlock _ -> pprPanic "getRegister' (CmmLit:CmmLabelOff): " (pdoc plat expr)
         CmmHighStackMark -> pprPanic "getRegister' (CmmLit:CmmLabelOff): " (pdoc plat expr)
     CmmLoad mem rep _ -> do
-      Amode addr addr_code <- getAmode plat (typeWidth rep) mem
       let format = cmmTypeFormat rep
-      return (Any format (\dst -> addr_code `snocOL` LDR format (OpReg (formatToWidth format) dst) (OpAddr addr)))
+          width = typeWidth rep
+      Amode addr addr_code <- getAmode plat width mem
+      case width of
+        w | w <= W64 ->
+            -- Load without sign-extension. See Note [Signed arithmetic on RISCV64]
+            pure (Any format (\dst -> addr_code `snocOL` LDRU format (OpReg width dst) (OpAddr addr)))
+        _ ->
+          pprPanic ("Width too big! Cannot load: " ++ show width) (pdoc plat expr)
+
     CmmStackSlot _ _
       -> pprPanic "getRegister' (CmmStackSlot): " (pdoc plat expr)
     CmmReg reg


=====================================
compiler/GHC/CmmToAsm/RV64/Instr.hs
=====================================
@@ -126,6 +126,7 @@ regUsageOfInstr platform instr = case instr of
   STR _ src dst            -> usage (regOp src ++ regOp dst, [])
   -- STLR _ src dst      L     -> usage (regOp src ++ regOp dst, [])
   LDR _ dst src            -> usage (regOp src, regOp dst)
+  LDRU _ dst src           -> usage (regOp src, regOp dst)
   -- LDAR _ dst src           -> usage (regOp src, regOp dst)
   -- TODO is this right? see STR, which I'm only partial about being right?
   -- STP _ src1 src2 dst      -> usage (regOp src1 ++ regOp src2 ++ regOp dst, [])
@@ -263,6 +264,7 @@ patchRegsOfInstr instr env = case instr of
     STR f o1 o2    -> STR f (patchOp o1) (patchOp o2)
     -- STLR f o1 o2   -> STLR f (patchOp o1) (patchOp o2)
     LDR f o1 o2    -> LDR f (patchOp o1) (patchOp o2)
+    LDRU f o1 o2    -> LDRU f (patchOp o1) (patchOp o2)
     -- LDAR f o1 o2   -> LDAR f (patchOp o1) (patchOp o2)
     -- STP f o1 o2 o3 -> STP f (patchOp o1) (patchOp o2) (patchOp o3)
     -- LDP f o1 o2 o3 -> LDP f (patchOp o1) (patchOp o2) (patchOp o3)
@@ -577,7 +579,8 @@ data Instr
     -- We do however have {L,S}{B,H,W,D}[U] instructions for Load/Store, Byte, Half, Word, Double, (Unsigned).
     -- Reusing the arm logic with the _format_ specifier will hopefully work.
     | STR Format Operand Operand -- str Xn, address-mode // Xn -> *addr
-    | LDR Format Operand Operand -- ldr Xn, address-mode // Xn <- *addr
+    | LDR Format Operand Operand -- ldr Xn, address-mode // Xn <- *addr (sign-extended)
+    | LDRU Format Operand Operand -- ldr Xn, address-mode // Xn <- *addr (unsigned)
 
     -- 3. Control Flow ---------------------------------------------------------
     -- B{EQ,GE,GEU,LT,LTU}, these are effectively BCOND from AArch64;
@@ -710,6 +713,7 @@ instrCon i =
       STR{} -> "STR"
       -- STLR{} -> "STLR"
       LDR{} -> "LDR"
+      LDRU{} -> "LDRU"
       -- LDAR{} -> "LDAR"
       -- STP{} -> "STP"
       -- LDP{} -> "LDP"


=====================================
compiler/GHC/CmmToAsm/RV64/Ppr.hs
=====================================
@@ -638,6 +638,7 @@ pprInstr platform instr = case instr of
     -- op_add o1 (text "%pcrel_lo(" <> pprAsmLabel platform lbl <> text ")")
     line $ text "\tla" <+> pprOp platform o1 <> comma <+> pprAsmLabel platform lbl
 
+  -- TODO: Are these two special cases really needed?
   LDR _f o1@(OpReg W8 reg) o2 | isIntRealReg reg ->
     op2 (text "\tlb") o1 o2
   LDR _f o1@(OpReg W16 reg) o2 | isIntRealReg reg ->
@@ -649,6 +650,13 @@ pprInstr platform instr = case instr of
   LDR II64 o1 o2 -> op2 (text "\tld") o1 o2
   LDR FF32 o1 o2 -> op2 (text "\tflw") o1 o2
   LDR FF64 o1 o2 -> op2 (text "\tfld") o1 o2
+
+  LDRU II8  o1 o2 -> op2 (text "\tlbu") o1 o2
+  LDRU II16 o1 o2 -> op2 (text "\tlhu") o1 o2
+  LDRU II32 o1 o2 -> op2 (text "\tlwu") o1 o2
+  -- double words (64bit) cannot be sign extended by definition
+  LDRU II64 o1 o2 -> op2 (text "\tld") o1 o2
+  LDRU f o1 o2 -> pprPanic "Unsupported unsigned load" ((text.show) f <+> pprOp platform o1 <+> pprOp platform o2)
   -- LDAR _f o1 o2 -> op2 (text "\tldar") o1 o2
 
   -- STP _f o1 o2 o3 -> op3 (text "\tstp") o1 o2 o3



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

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


More information about the ghc-commits mailing list