[Git][ghc/ghc][wip/supersven/riscv64-ncg] 2 commits: MO_FS_Conv: Truncate register after conversion

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Sat Nov 4 15:58:44 UTC 2023



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


Commits:
8b4f5ae9 by Sven Tennie at 2023-11-04T16:37:54+01:00
MO_FS_Conv: Truncate register after conversion

Otherwise, sign-extension bits may stay around.

- - - - -
d4c45787 by Sven Tennie at 2023-11-04T16:39:38+01:00
Fix float operation attributes

This is its own little hell...

- - - - -


2 changed files:

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


Changes:

=====================================
compiler/GHC/CmmToAsm/RV64/CodeGen.hs
=====================================
@@ -616,8 +616,10 @@ getRegister' config plat expr =
                                                                       -- W32 is the smallest width to convert to. Decrease width afterwards.
                                                                       annExpr expr (FCVTZS (OpReg W32 dst) (OpReg from reg)) `appOL`
                                                                       signExtendAdjustPrecission W32 to dst dst) -- (float convert (-> zero) signed)
-        MO_FS_Conv from to -> pure $ Any (intFormat to) (\dst -> code `snocOL` annExpr expr (FCVTZS (OpReg to dst) (OpReg from reg))) -- (float convert (-> zero) signed)
-
+        MO_FS_Conv from to -> pure $ Any (intFormat to) (\dst ->
+                                                           code `snocOL`
+                                                           annExpr expr (FCVTZS (OpReg to dst) (OpReg from reg)) `appOL` -- (float convert (-> zero) signed)
+                                                           truncateReg from to dst)
         MO_UU_Conv from to | from <= to -> pure $ Any (intFormat to) (\dst ->
                                                                           code `snocOL`
                                                                           annExpr e (MOV (OpReg to dst) (OpReg from reg))


=====================================
compiler/GHC/CmmToAsm/RV64/Ppr.hs
=====================================
@@ -579,7 +579,7 @@ pprInstr platform instr = case instr of
   CSET o l r c  -> case c of
     EQ | isIntOp l && isIntOp r -> lines_ [ subFor l r
                   , text "\tseqz" <+> pprOp platform o <> comma <+> pprOp platform o]
-    EQ | isFloatOp l && isFloatOp r -> line $ binOp "\tfeq.s"
+    EQ | isFloatOp l && isFloatOp r -> line $ binOp ("\tfeq." ++ floatOpPrecision platform l r)
     NE | isIntOp l && isIntOp r -> lines_ [ subFor l r
                   , text "\tsnez" <+> pprOp platform o <> comma <+> pprOp platform o]
     --    feq.s   a0,fa0,fa1
@@ -597,10 +597,10 @@ pprInstr platform instr = case instr of
     UGE -> lines_ [ sltuFor l r <+> pprOp platform o <> comma <+> pprOp platform l <> comma <+> pprOp platform r
                   , text "\txori" <+>  pprOp platform o <> comma <+> pprOp platform o <> comma <+> text "1" ]
     UGT -> lines_ [ sltuFor l r <+> pprOp platform o <> comma <+> pprOp platform r <> comma <+> pprOp platform l ]
-    OLT | isFloatOp l && isFloatOp r -> line $ binOp "\tflt.s"
-    OLE | isFloatOp l && isFloatOp r -> line $ binOp "\tfle.s"
-    OGT | isFloatOp l && isFloatOp r -> line $ binOp "\tfgt.s"
-    OGE | isFloatOp l && isFloatOp r -> line $ binOp "\tfge.s"
+    OLT | isFloatOp l && isFloatOp r -> line $ binOp ("\tflt." ++ floatOpPrecision platform l r)
+    OLE | isFloatOp l && isFloatOp r -> line $ binOp ("\tfle." ++ floatOpPrecision platform l r)
+    OGT | isFloatOp l && isFloatOp r -> line $ binOp ("\tfgt." ++ floatOpPrecision platform l r)
+    OGE | isFloatOp l && isFloatOp r -> line $ binOp ("\tfge." ++ floatOpPrecision platform l r)
     x  -> pprPanic "RV64.ppr: unhandled CSET conditional" (text (show x) <+> pprOp platform o <> comma <+> pprOp platform r <> comma <+> pprOp platform l)
     where
       subFor l r | (OpImm _) <- r = text "\taddi" <+> pprOp platform o <> comma <+> pprOp platform l <> comma <+> pprOp platform (negOp r)
@@ -612,6 +612,7 @@ pprInstr platform instr = case instr of
       sltuFor l r| (OpImm _) <- r = text "\tsltui"
                  | (OpImm _) <- l = panic "PV64.ppr: Cannot SLTU IMM _"
                  | otherwise      = text "\tsltu"
+      binOp :: (IsLine doc) => String -> doc
       binOp op = text op <+> pprOp platform o <> comma <+> pprOp platform l <> comma <+> pprOp platform r
 
   CBZ o (TBlock bid) -> line $ text "\tbeq x0, " <+> pprOp platform o <> comma <+> pprAsmLabel platform (mkLocalBlockLabel (getUnique bid))
@@ -686,8 +687,8 @@ pprInstr platform instr = case instr of
   FCVT o1 o2 -> op2 (text "\tfcvt") o1 o2
   SCVTF o1@(OpReg W32 _) o2@(OpReg W32 _) -> op2 (text "\tfcvt.s.w") o1 o2
   SCVTF o1@(OpReg W32 _) o2@(OpReg W64 _) -> op2 (text "\tfcvt.s.w") o1 o2
-  SCVTF o1@(OpReg W64 _) o2@(OpReg W32 _) -> op2 (text "\tfcvt.s.l") o1 o2
-  SCVTF o1@(OpReg W64 _) o2@(OpReg W64 _) -> op2 (text "\tfcvt.s.l") o1 o2
+  SCVTF o1@(OpReg W64 _) o2@(OpReg W32 _) -> op2 (text "\tfcvt.d.l") o1 o2
+  SCVTF o1@(OpReg W64 _) o2@(OpReg W64 _) -> op2 (text "\tfcvt.d.l") o1 o2
   SCVTF o1 o2 -> pprPanic "RV64.pprInstr - impossible integer to float conversion" $
                   line (pprOp platform o1 <> text "->" <> pprOp platform o2)
 
@@ -711,6 +712,11 @@ pprInstr platform instr = case instr of
        pprDmbType DmbWrite = text "w"
        pprDmbType DmbReadWrite = text "rw"
 
+floatOpPrecision :: Platform -> Operand -> Operand -> String
+floatOpPrecision p l r | isFloatOp l && isFloatOp r && isSingleOp l && isSingleOp r = "s" -- single precision
+floatOpPrecision p l r | isFloatOp l && isFloatOp r && isDoubleOp l && isDoubleOp r = "d" -- double precision
+floatOpPrecision p l r = pprPanic "Cannot determine floating point precission" (text "op1" <+> pprOp p l <+> text "op2" <+> pprOp p r)
+
 pprBcond :: IsLine doc => Cond -> doc
 pprBcond c = text "b." <> pprCond c
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/15809ebaa682fce112d9f09f61cbf615838186fa...d4c45787c83f7d262c2432587af8998bd3452cec

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/15809ebaa682fce112d9f09f61cbf615838186fa...d4c45787c83f7d262c2432587af8998bd3452cec
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/20231104/a6136e78/attachment-0001.html>


More information about the ghc-commits mailing list