[Git][ghc/ghc][wip/supersven/riscv64-ncg] Re-implement takeRegRegMoveInstr

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Sat Mar 9 14:09:49 UTC 2024



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


Commits:
886d2e7a by Sven Tennie at 2024-03-09T15:07:51+01:00
Re-implement takeRegRegMoveInstr

- - - - -


2 changed files:

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


Changes:

=====================================
compiler/GHC/CmmToAsm/RV64/Instr.hs
=====================================
@@ -433,21 +433,9 @@ mkRegRegMoveInstr src dst = ANN desc instr
 --
 -- We have to be a bit careful here: A `MOV` can also mean an implicit
 -- conversion. This case is filtered out.
-takeRegRegMoveInstr :: Instr -> Maybe (Reg,Reg)
--- TODO: If this doesn't work (I don't understand WHY):
--- ghc: panic! (the 'impossible' happened)
---  GHC version 9.6.3:
---        RV64.ppr: unhandled CSET conditional
---  FLE t6, t0, ft0
---  Call stack:
---      CallStack (from HasCallStack):
---        callStackDoc, called at compiler/GHC/Utils/Panic.hs:189:37 in ghc:GHC.Utils.Panic
---        pprPanic, called at compiler/GHC/CmmToAsm/RV64/Ppr.hs:598:11 in ghc:GHC.CmmToAsm.RV64.Ppr
---  CallStack (from HasCallStack):
---    panic, called at compiler/GHC/Utils/Error.hs:454:29 in ghc:GHC.Utils.Error
---
--- Maybe, checking the format isn't enough and we have to check register types by their number?
--- takeRegRegMoveInstr (MOV (OpReg fmt dst) (OpReg fmt' src)) | fmt == fmt' = pure (src, dst)
+takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg)
+takeRegRegMoveInstr (MOV (OpReg width dst) (OpReg width' src))
+  | width == width' && (isFloatReg dst == isFloatReg src) = pure (src, dst)
 takeRegRegMoveInstr _ = Nothing
 
 -- | Make an unconditional jump instruction.
@@ -863,6 +851,20 @@ isNbitEncodeable n i = let shift = n - 1 in (-1 `shiftL` shift) <= i && i < (1 `
 isEncodeableInWidth :: Width -> Integer -> Bool
 isEncodeableInWidth = isNbitEncodeable . widthInBits
 
+isIntOp :: Operand -> Bool
+isIntOp = not . isFloatOp
+
+isFloatOp :: Operand -> Bool
+isFloatOp (OpReg _ reg) | isFloatReg reg = True
+isFloatOp _ = False
+
+isFloatReg :: Reg -> Bool
+isFloatReg (RegReal (RealRegSingle i)) | i > 31 = True
+isFloatReg (RegVirtual (VirtualRegF _)) = True
+isFloatReg (RegVirtual (VirtualRegD _)) = True
+isFloatReg _ = False
+
+
 -- | Making far branches
 
 -- Conditional branch instructions can target labels in a range of +/- 4 KiB.


=====================================
compiler/GHC/CmmToAsm/RV64/Ppr.hs
=====================================
@@ -393,15 +393,6 @@ pprReg w r = case r of
          -- no support for widths > W64.
          | otherwise = pprPanic "Unsupported width in register (max is 64)" (ppr w <+> int i)
 
-isIntOp :: Operand -> Bool
-isIntOp = not . isFloatOp
-
-isFloatOp :: Operand -> Bool
-isFloatOp (OpReg _ (RegReal (RealRegSingle i))) | i > 31 = True
-isFloatOp (OpReg _ (RegVirtual (VirtualRegF _))) = True
-isFloatOp (OpReg _ (RegVirtual (VirtualRegD _))) = True
-isFloatOp _ = False
-
 isSingleOp :: Operand -> Bool
 isSingleOp (OpReg W32 _) = True
 isSingleOp _ = False



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/886d2e7aa463200f39dd6eedcc07d7e3a3fd420f
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/20240309/6925dd01/attachment-0001.html>


More information about the ghc-commits mailing list