[Git][ghc/ghc][wip/andreask/reg-offset] Aarch ncg: Optimized immediate use for address calculations

Andreas Klebinger (@AndreasK) gitlab at gitlab.haskell.org
Sat Jul 29 16:33:55 UTC 2023



Andreas Klebinger pushed to branch wip/andreask/reg-offset at Glasgow Haskell Compiler / GHC


Commits:
de0c15bb by Andreas Klebinger at 2023-07-29T18:33:22+02:00
Aarch ncg: Optimized immediate use for address calculations

- - - - -


1 changed file:

- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs


Changes:

=====================================
compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
=====================================
@@ -61,6 +61,7 @@ import GHC.Data.FastString
 import GHC.Utils.Misc
 import GHC.Utils.Panic
 import GHC.Utils.Constants (debugIsOn)
+import GHC.Hs.Dump (showAstDataFull)
 
 -- Note [General layout of an NCG]
 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -580,6 +581,10 @@ getRegister' config plat (CmmMachOp (MO_Sub w0) [x, CmmLit (CmmInt i w1)]) | i <
 -- Generic case.
 getRegister' config plat expr
   = case expr of
+    -- TODO: Delete
+    -- _
+    --   | pprTrace "getRegister' (monadic CmmMachOp):" (pdoc plat expr $$ (text $ show expr)) False
+    --   -> undefined
     CmmReg (CmmGlobal (GlobalRegUse PicBaseReg _))
       -> pprPanic "getRegisterReg-memory" (ppr $ PicBaseReg)
     CmmLit lit
@@ -711,18 +716,11 @@ getRegister' config plat expr
       -> return (Fixed (cmmTypeFormat (cmmRegType reg))
                        (getRegisterReg plat reg)
                        nilOL)
-    CmmRegOff reg off | isNbitEncodeable 12 (fromIntegral off) -> do
-      getRegister' config plat $
-            CmmMachOp (MO_Add width) [CmmReg reg, CmmLit (CmmInt (fromIntegral off) width)]
-          where width = typeWidth (cmmRegType reg)
-
-    CmmRegOff reg off -> do
-      (off_r, _off_format, off_code) <- getSomeReg $ CmmLit (CmmInt (fromIntegral off) width)
-      (reg, _format, code) <- getSomeReg $ CmmReg reg
-      return $ Any (intFormat width) (\dst -> off_code `appOL` code `snocOL` ADD (OpReg width dst) (OpReg width reg) (OpReg width off_r))
-          where width = typeWidth (cmmRegType reg)
-
-
+    CmmRegOff reg off ->
+      -- If we got here we will load the address into a register either way. So we might as well just expand
+      -- and re-use the existing code path to handle "reg + off".
+      let !width = cmmRegWidth reg
+      in getRegister' config plat (CmmMachOp (MO_Add width) [CmmReg reg, CmmLit (CmmInt (fromIntegral off) width)])
 
     -- for MachOps, see GHC.Cmm.MachOp
     -- For CmmMachOp, see GHC.Cmm.Expr



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

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


More information about the ghc-commits mailing list