[Git][ghc/ghc][master] compiler: fix handling of MO_F_Neg in wasm NCG

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Jan 25 08:55:05 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
bc038c3b by Cheng Shao at 2023-01-25T03:54:50-05:00
compiler: fix handling of MO_F_Neg in wasm NCG

In the wasm NCG, we used to compile MO_F_Neg to 0.0-x. It was an
oversight, there actually exists f32.neg/f64.neg opcodes in the wasm
spec and those should be used instead! The old behavior almost works,
expect when GHC compiles the -0.0 literal, which will incorrectly
become 0.0.

- - - - -


3 changed files:

- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs


Changes:

=====================================
compiler/GHC/CmmToAsm/Wasm/Asm.hs
=====================================
@@ -359,6 +359,7 @@ asmTellWasmInstr ty_word instr = case instr of
   WasmF32DemoteF64 -> asmTellLine "f32.demote_f64"
   WasmF64PromoteF32 -> asmTellLine "f64.promote_f32"
   WasmAbs ty -> asmTellLine $ asmFromWasmType ty <> ".abs"
+  WasmNeg ty -> asmTellLine $ asmFromWasmType ty <> ".neg"
   WasmCond t -> do
     asmTellLine "if"
     asmWithTab $ asmTellWasmInstr ty_word t


=====================================
compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
=====================================
@@ -224,6 +224,28 @@ extendSubword W32 TagI64 (WasmExpr instr) =
   WasmExpr $ instr `WasmConcat` WasmI64Extend32S
 extendSubword _ _ expr = expr
 
+-- | Lower an unary homogeneous operation.
+lower_MO_Un_Homo ::
+  ( forall pre t.
+    WasmTypeTag t ->
+    WasmInstr
+      w
+      (t : pre)
+      (t : pre)
+  ) ->
+  CLabel ->
+  CmmType ->
+  [CmmExpr] ->
+  WasmCodeGenM w (SomeWasmExpr w)
+lower_MO_Un_Homo op lbl t0 [x] = case someWasmTypeFromCmmType t0 of
+  SomeWasmType ty -> do
+    WasmExpr x_instr <- lower_CmmExpr_Typed lbl ty x
+    pure $
+      SomeWasmExpr ty $
+        WasmExpr $
+          x_instr `WasmConcat` op ty
+lower_MO_Un_Homo _ _ _ _ = panic "lower_MO_Un_Homo: unreachable"
+
 -- | Lower a binary homogeneous operation. Homogeneous: result type is
 -- the same with operand types.
 lower_MO_Bin_Homo ::
@@ -699,11 +721,12 @@ lower_CmmMachOp lbl (MO_F_Sub w0) xs =
     lbl
     (cmmFloat w0)
     xs
-lower_CmmMachOp lbl (MO_F_Neg w0) [x] =
-  lower_CmmMachOp
+lower_CmmMachOp lbl (MO_F_Neg w0) xs =
+  lower_MO_Un_Homo
+    WasmNeg
     lbl
-    (MO_F_Sub w0)
-    [CmmLit $ CmmFloat 0 w0, x]
+    (cmmFloat w0)
+    xs
 lower_CmmMachOp lbl (MO_F_Mul w0) xs =
   lower_MO_Bin_Homo
     WasmMul


=====================================
compiler/GHC/CmmToAsm/Wasm/Types.hs
=====================================
@@ -305,6 +305,7 @@ data WasmInstr :: WasmType -> [WasmType] -> [WasmType] -> Type where
   WasmF32DemoteF64 :: WasmInstr w ('F64 : pre) ('F32 : pre)
   WasmF64PromoteF32 :: WasmInstr w ('F32 : pre) ('F64 : pre)
   WasmAbs :: WasmTypeTag t -> WasmInstr w (t : pre) (t : pre)
+  WasmNeg :: WasmTypeTag t -> WasmInstr w (t : pre) (t : pre)
   WasmCond :: WasmInstr w pre pre -> WasmInstr w (w : pre) pre
 
 newtype WasmExpr w t = WasmExpr (forall pre. WasmInstr w pre (t : pre))



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bc038c3bd45ee99db9fba23a823a906735740200
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/20230125/35de1d72/attachment-0001.html>


More information about the ghc-commits mailing list