[Git][ghc/ghc][wip/supersven/riscv64-ncg] 4 commits: Fix float absolute (fabs)

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Mon Aug 21 16:31:49 UTC 2023



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


Commits:
bc3660b5 by Sven Tennie at 2023-08-21T18:29:25+02:00
Fix float absolute (fabs)

- - - - -
4dec2e57 by Sven Tennie at 2023-08-21T18:30:46+02:00
Fix float negation

- - - - -
52122a77 by Sven Tennie at 2023-08-21T18:31:03+02:00
Fix unsigned float loading

- - - - -
f7d5ade4 by Sven Tennie at 2023-08-21T18:31:28+02:00
Fix float comparisions

- - - - -


1 changed file:

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


Changes:

=====================================
compiler/GHC/CmmToAsm/RV64/Ppr.hs
=====================================
@@ -403,7 +403,7 @@ pprReg w r = case r of
          | otherwise = pprPanic "Unsupported width in register (max is 64)" (ppr w <+> int i)
 
 isIntOp :: Operand -> Bool
-isIntOp o = not (isFloatOp o || isDoubleOp o)
+isIntOp = not . isFloatOp
 
 isFloatOp :: Operand -> Bool
 isFloatOp (OpReg _ (RegReal (RealRegSingle i))) | i > 31 = True
@@ -482,9 +482,9 @@ pprInstr platform instr = case instr of
     | otherwise -> op3 (text "\tmul") o1 o2 o3
   SMULH o1 o2 o3 -> op3 (text "\tmulh") o1 o2 o3
   SMULL o1 o2 o3 -> op3 (text "\tsmull") o1 o2 o3
-  NEG  o1 o2
-    | isFloatOp o1 && isFloatOp o2 -> op2 (text "\tfneg") o1 o2
-    | otherwise -> op2 (text "\tneg") o1 o2
+  NEG o1 o2 | isFloatOp o1 && isFloatOp o2 && isSingleOp o2 -> op2 (text "\tfneg.s") o1 o2
+  NEG o1 o2 | isFloatOp o1 && isFloatOp o2 && isDoubleOp o2 -> op2 (text "\tfneg.d") o1 o2
+  NEG o1 o2 -> op2 (text "\tneg") o1 o2
   DIV o1 o2 o3 | isFloatOp o1 && isFloatOp o2 && isFloatOp o3
   -- TODO: This must (likely) be refined regarding width
     -> op3 (text "\tfdiv." <> if isSingleOp o1 then text "s" else text "d") o1 o2 o3
@@ -601,7 +601,7 @@ pprInstr platform instr = case instr of
     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"
-    _  -> pprPanic "RV64.ppr: unhandled CSET conditional" (pprOp platform o <> comma <+> pprOp platform r <> comma <+> pprOp platform l)
+    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)
                  | (OpImm _) <- l = panic "RV64.ppr: Cannot SUB IMM _"
@@ -669,7 +669,9 @@ pprInstr platform instr = case instr of
   LDRU II32 o1 o2 -> op2 (text "\tlwu") o1 o2
   -- double words (64bit) cannot be sign extended by definition
   LDRU II64 o1 o2 -> op2 (text "\tld") o1 o2
+  LDRU FF32 o1 o2@(OpAddr (AddrReg _)) -> op2 (text "\tflw") o1 o2
   LDRU FF32 o1 o2@(OpAddr (AddrRegImm _ _)) -> op2 (text "\tflw") o1 o2
+  LDRU FF64 o1 o2@(OpAddr (AddrReg _)) -> op2 (text "\tfld") o1 o2
   LDRU FF64 o1 o2@(OpAddr (AddrRegImm _ _)) -> op2 (text "\tfld") o1 o2
   LDRU f o1 o2 -> pprPanic "Unsupported unsigned load" ((text.show) f <+> pprOp platform o1 <+> pprOp platform o2)
   -- LDAR _f o1 o2 -> op2 (text "\tldar") o1 o2
@@ -696,7 +698,8 @@ pprInstr platform instr = case instr of
   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
+  FABS o1 o2 | isSingleOp o2 -> op2 (text "\tfabs.s") o1 o2
+  FABS o1 o2 | isDoubleOp o2 -> op2 (text "\tfabs.d") o1 o2
   instr -> panic $ "RV64.pprInstr - Unknown instruction: " ++ (instrCon instr)
  where op2 op o1 o2        = line $ op <+> pprOp platform o1 <> comma <+> pprOp platform o2
        op3 op o1 o2 o3     = line $ op <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1c103206664a73d85b61b0cc7768e135eb63dc3c...f7d5ade43134b1d86a4688434f62c5fcfb8657f0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1c103206664a73d85b61b0cc7768e135eb63dc3c...f7d5ade43134b1d86a4688434f62c5fcfb8657f0
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/20230821/701b3e3c/attachment-0001.html>


More information about the ghc-commits mailing list