[Git][ghc/ghc][wip/supersven/riscv64-ncg] Implement MO_FS_Conv and MO_SF_Conv (integer <-> float conversion)

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Sat Jun 17 13:56:07 UTC 2023



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


Commits:
7e3679b6 by Sven Tennie at 2023-06-17T15:54:55+02:00
Implement MO_FS_Conv and MO_SF_Conv (integer <-> float conversion)

- - - - -


2 changed files:

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


Changes:

=====================================
compiler/GHC/CmmToAsm/RV64/CodeGen.hs
=====================================
@@ -611,8 +611,20 @@ getRegister' config plat expr
         MO_S_Neg w -> negate code w reg
         MO_F_Neg w -> return $ Any (floatFormat w) (\dst -> code `snocOL` NEG (OpReg w dst) (OpReg w reg))
 
-        MO_SF_Conv from to -> return $ Any (floatFormat to) (\dst -> code `snocOL` SCVTF (OpReg to dst) (OpReg from reg))  -- (Signed ConVerT Float)
-        MO_FS_Conv from to -> return $ Any (intFormat to) (\dst -> code `snocOL` FCVTZS (OpReg to dst) (OpReg from reg)) -- (float convert (-> zero) signed)
+        -- TODO: Can this case happen?
+        MO_SF_Conv from to | from < W32 -> do
+                               -- extend to the smallest available representation
+                               (reg_x, code_x) <- signExtendReg from W32 reg
+                               pure $ Any (floatFormat to)
+                                                    (\dst -> code `appOL` code_x `snocOL` annExpr expr (SCVTF (OpReg to dst) (OpReg from reg_x)))  -- (Signed ConVerT Float)
+        MO_SF_Conv from to -> pure $ Any (floatFormat to) (\dst -> code `snocOL` annExpr expr (SCVTF (OpReg to dst) (OpReg from reg)))  -- (Signed ConVerT Float)
+        -- TODO: Can this case happen?
+        MO_FS_Conv from to | to < W32 -> pure $ Any (intFormat to) (\dst ->
+                                                                      code `snocOL`
+                                                                      -- 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)
 
         -- TODO this is very slow. We effectively use store + load (byte, half, word, double)
         --      for this in memory.


=====================================
compiler/GHC/CmmToAsm/RV64/Ppr.hs
=====================================
@@ -654,8 +654,20 @@ pprInstr platform instr = case instr of
 
   -- 9. Floating Point Instructions --------------------------------------------
   FCVT o1 o2 -> op2 (text "\tfcvt") o1 o2
-  SCVTF o1 o2 -> op2 (text "\tscvtf") o1 o2
-  FCVTZS o1 o2 -> op2 (text "\tfcvtzs") o1 o2
+  SCVTF o1@(OpReg W32 _) o2@(OpReg W32 _) -> op2 (text "\tfcvt.s.w") o1 o2
+  SCVTF o1@(OpReg W64 _) o2@(OpReg W32 _) -> op2 (text "\tfcvt.s.l") o1 o2
+  SCVTF o1@(OpReg W32 _) o2@(OpReg W64 _) -> op2 (text "\tfcvt.d.w") 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)
+
+  FCVTZS o1@(OpReg W32 _) o2@(OpReg W32 _) -> op2 (text "\fcvt.w.s") o1 o2
+  FCVTZS o1@(OpReg W32 _) o2@(OpReg W64 _) -> op2 (text "\fcvt.l.s") o1 o2
+  FCVTZS o1@(OpReg W64 _) o2@(OpReg W32 _) -> op2 (text "\fcvt.w.d") o1 o2
+  FCVTZS o1@(OpReg W64 _) o2@(OpReg W64 _) -> op2 (text "\fcvt.l.d") o1 o2
+  FCVTZS o1 o2 -> pprPanic "RV64.pprInstr - impossible float to integer conversion" $
+                  line (pprOp platform o1 <> text "->" <> pprOp platform o2)
+
   FABS o1 o2 -> op2 (text "\tfabs") o1 o2
   instr -> panic $ "RV64.pprInstr - Unknown instruction: " ++ (instrCon instr)
  where op2 op o1 o2        = line $ op <+> pprOp platform o1 <> comma <+> pprOp platform o2



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7e3679b661f4ffdda53e80982351cc315b3f8029
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/20230617/7778ef82/attachment-0001.html>


More information about the ghc-commits mailing list