[Git][ghc/ghc][wip/andreask/arm_immediates] Move adhoc reg format checks into a proper place

Andreas Klebinger (@AndreasK) gitlab at gitlab.haskell.org
Mon Jul 10 14:15:12 UTC 2023



Andreas Klebinger pushed to branch wip/andreask/arm_immediates at Glasgow Haskell Compiler / GHC


Commits:
9aa354c2 by Andreas Klebinger at 2023-07-10T16:17:23+02:00
Move adhoc reg format checks into a proper place

- - - - -


3 changed files:

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


Changes:

=====================================
compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
=====================================
@@ -559,12 +559,13 @@ getRegister' config plat expr
       -> case lit of
 
         -- Use wzr xzr for CmmInt 0 if the width matches up, otherwise do a move.
-        CmmInt 0 W32 -> do
-          let format = intFormat W32
-          return (Fixed format reg_zero (unitOL $ (COMMENT ((text . show $ expr))) ))
-        CmmInt 0 W64 -> do
-          let format = intFormat W64
-          return (Fixed format reg_zero (unitOL $ (COMMENT ((text . show $ expr))) ))
+        -- TODO: Reenable after https://gitlab.haskell.org/ghc/ghc/-/issues/23632 is fixed.
+        -- CmmInt 0 W32 -> do
+        --   let format = intFormat W32
+        --   return (Fixed format reg_zero (unitOL $ (COMMENT ((text . show $ expr))) ))
+        -- CmmInt 0 W64 -> do
+        --   let format = intFormat W64
+        --   return (Fixed format reg_zero (unitOL $ (COMMENT ((text . show $ expr))) ))
         CmmInt i W8 | i >= 0 -> do
           return (Any (intFormat W8) (\dst -> unitOL $ annExpr expr (MOV (OpReg W8 dst) (OpImm (ImmInteger (narrowU W8 i))))))
         CmmInt i W16 | i >= 0 -> do


=====================================
compiler/GHC/CmmToAsm/AArch64/Instr.hs
=====================================
@@ -381,9 +381,8 @@ mkSpillInstr config reg delta slot =
     where
         a .&~. b = a .&. (complement b)
 
-        fmt = case reg of
-            RegReal (RealRegSingle n) | n < 32 -> II64
-            _                                  -> FF64
+        fmt = fmtOfRealReg (case reg of { RegReal r -> r; _ -> panic "Expected real reg"})
+
         mkIp0SpillAddr imm = ANN (text "Spill: IP0 <- SP + " <> int imm) $ ADD ip0 sp (OpImm (ImmInt imm))
         mkStrSp imm = ANN (text "Spill@" <> int (off - delta)) $ STR fmt (OpReg W64 reg) (OpAddr (AddrRegImm (regSingle 31) (ImmInt imm)))
         mkStrIp0 imm = ANN (text "Spill@" <> int (off - delta)) $ STR fmt (OpReg W64 reg) (OpAddr (AddrRegImm (regSingle 16) (ImmInt imm)))
@@ -408,9 +407,7 @@ mkLoadInstr config reg delta slot =
     where
         a .&~. b = a .&. (complement b)
 
-        fmt = case reg of
-            RegReal (RealRegSingle n) | n < 32 -> II64
-            _                                  -> FF64
+        fmt = fmtOfRealReg (case reg of { RegReal r -> r; _ -> panic "Expected real reg"})
 
         mkIp0SpillAddr imm = ANN (text "Reload: IP0 <- SP + " <> int imm) $ ADD ip0 sp (OpImm (ImmInt imm))
         mkLdrSp imm = ANN (text "Reload@" <> int (off - delta)) $ LDR fmt (OpReg W64 reg) (OpAddr (AddrRegImm (regSingle 31) (ImmInt imm)))


=====================================
compiler/GHC/CmmToAsm/AArch64/Regs.hs
=====================================
@@ -147,6 +147,13 @@ classOfRealReg (RealRegSingle i)
         | i < 32        = RcInteger
         | otherwise     = RcDouble
 
+fmtOfRealReg :: RealReg -> Format
+fmtOfRealReg real_reg =
+  case classOfRealReg real_reg of
+            RcInteger -> II64
+            RcDouble  -> FF64
+            RcFloat   -> panic "No float regs on arm"
+
 regDotColor :: RealReg -> SDoc
 regDotColor reg
  = case classOfRealReg reg of



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9aa354c2a8b771519dbc31d0e2f63306d8e7c91d
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/20230710/804de96c/attachment-0001.html>


More information about the ghc-commits mailing list