[Git][ghc/ghc][wip/supersven/ghc-master-riscv-ncg] 2 commits: Improve documentation for stack spills

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Sun Sep 1 12:52:48 UTC 2024



Sven Tennie pushed to branch wip/supersven/ghc-master-riscv-ncg at Glasgow Haskell Compiler / GHC


Commits:
45d3d6bd by Sven Tennie at 2024-09-01T14:45:18+02:00
Improve documentation for stack spills

- - - - -
a38bf454 by Sven Tennie at 2024-09-01T14:52:25+02:00
Reformat stack spill code

- - - - -


1 changed file:

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


Changes:

=====================================
compiler/GHC/CmmToAsm/RV64/Instr.hs
=====================================
@@ -71,6 +71,7 @@ regUsageOfInstr platform instr = case instr of
   MULTILINE_COMMENT {} -> usage ([], [])
   PUSH_STACK_FRAME -> usage ([], [])
   POP_STACK_FRAME -> usage ([], [])
+  LOCATION {} -> usage ([], [])
   DELTA {} -> usage ([], [])
   ADD dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst)
   MUL dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst)
@@ -155,6 +156,7 @@ patchRegsOfInstr instr env = case instr of
   MULTILINE_COMMENT {} -> instr
   PUSH_STACK_FRAME -> instr
   POP_STACK_FRAME -> instr
+  LOCATION {} -> instr
   DELTA {} -> instr
   ADD o1 o2 o3 -> ADD (patchOp o1) (patchOp o2) (patchOp o3)
   MUL o1 o2 o3 -> MUL (patchOp o1) (patchOp o2) (patchOp o3)
@@ -255,23 +257,26 @@ patchJumpInstr instr patchF =
     _ -> panic $ "patchJumpInstr: " ++ instrCon instr
 
 -- -----------------------------------------------------------------------------
--- Note [Spills and Reloads]
--- ~~~~~~~~~~~~~~~~~~~~~~~~~
+-- Note [RISCV64 Spills and Reloads]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+--
 -- We reserve @RESERVED_C_STACK_BYTES@ on the C stack for spilling and reloading
--- registers.  AArch64s maximum displacement for SP relative spills and reloads
--- is essentially [-256,255], or [0, 0xFFF]*8 = [0, 32760] for 64bits.
+-- registers. The load and store instructions of RISCV64 address with a signed
+-- 12-bit immediate + a register; machine stackpointer (sp/x2) in this case.
 --
--- The @RESERVED_C_STACK_BYTES@ is 16k, so we can't address any location in a
--- single instruction.  The idea is to use the Inter Procedure 0 (ip) register
--- to perform the computations for larger offsets.
+-- The @RESERVED_C_STACK_BYTES@ is 16k, so we can't always address into it in a
+-- single load/store instruction. There are offsets to sp (not to be confused
+-- with STG's SP!) which need a register to be calculated.
 --
 -- Using sp to compute the offset will violate assumptions about the stack pointer
 -- pointing to the top of the stack during signal handling.  As we can't force
 -- every signal to use its own stack, we have to ensure that the stack pointer
 -- always points to the top of the stack, and we can't use it for computation.
 --
+-- So, we reserve one register (ip) for this purpose (and other, unrelated
+-- intermediate operations.) See Note [The made-up RISCV64 IP register]
 
--- | An instruction to spill a register into a spill slot.
+-- | Generate instructions to spill a register into a spill slot.
 mkSpillInstr ::
   (HasCallStack) =>
   NCGConfig ->
@@ -294,13 +299,22 @@ mkSpillInstr _config reg delta slot =
     fmt = case reg of
       RegReal (RealRegSingle n) | n < d0RegNo -> II64
       _ -> FF64
-    mkStrSpImm imm = ANN (text "Spill@" <> int (off - delta)) $ STR fmt (OpReg W64 reg) (OpAddr (AddrRegImm spMachReg (ImmInt imm)))
-    movImmToIp imm = ANN (text "Spill: IP <- " <> int imm) $ MOV ip (OpImm (ImmInt imm))
-    addSpToIp = ANN (text "Spill: IP <- SP + IP ") $ ADD ip ip sp
-    mkStrIp = ANN (text "Spill@" <> int (off - delta)) $ STR fmt (OpReg W64 reg) (OpAddr (AddrReg ipReg))
+    mkStrSpImm imm =
+      ANN (text "Spill@" <> int (off - delta))
+        $ STR fmt (OpReg W64 reg) (OpAddr (AddrRegImm spMachReg (ImmInt imm)))
+    movImmToIp imm =
+      ANN (text "Spill: IP <- " <> int imm)
+        $ MOV ip (OpImm (ImmInt imm))
+    addSpToIp =
+      ANN (text "Spill: IP <- SP + IP ")
+        $ ADD ip ip sp
+    mkStrIp =
+      ANN (text "Spill@" <> int (off - delta))
+        $ STR fmt (OpReg W64 reg) (OpAddr (AddrReg ipReg))
 
     off = spillSlotToOffset slot
 
+-- | Generate instructions to load a register from a spill slot.
 mkLoadInstr ::
   NCGConfig ->
   -- | register to load
@@ -322,10 +336,18 @@ mkLoadInstr _config reg delta slot =
     fmt = case reg of
       RegReal (RealRegSingle n) | n < d0RegNo -> II64
       _ -> FF64
-    mkLdrSpImm imm = ANN (text "Reload@" <> int (off - delta)) $ LDR fmt (OpReg W64 reg) (OpAddr (AddrRegImm spMachReg (ImmInt imm)))
-    movImmToIp imm = ANN (text "Reload: IP <- " <> int imm) $ MOV ip (OpImm (ImmInt imm))
-    addSpToIp = ANN (text "Reload: IP <- SP + IP ") $ ADD ip ip sp
-    mkLdrIp = ANN (text "Reload@" <> int (off - delta)) $ LDR fmt (OpReg W64 reg) (OpAddr (AddrReg ipReg))
+    mkLdrSpImm imm =
+      ANN (text "Reload@" <> int (off - delta))
+        $ LDR fmt (OpReg W64 reg) (OpAddr (AddrRegImm spMachReg (ImmInt imm)))
+    movImmToIp imm =
+      ANN (text "Reload: IP <- " <> int imm)
+        $ MOV ip (OpImm (ImmInt imm))
+    addSpToIp =
+      ANN (text "Reload: IP <- SP + IP ")
+        $ ADD ip ip sp
+    mkLdrIp =
+      ANN (text "Reload@" <> int (off - delta))
+        $ LDR fmt (OpReg W64 reg) (OpAddr (AddrReg ipReg))
 
     off = spillSlotToOffset slot
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0962e7ad17221416a5d1c355732cc8256c71f236...a38bf4541dc3a2888da1f03bffe906ff5ff5ac63

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0962e7ad17221416a5d1c355732cc8256c71f236...a38bf4541dc3a2888da1f03bffe906ff5ff5ac63
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/20240901/c767baba/attachment-0001.html>


More information about the ghc-commits mailing list