[Git][ghc/ghc][master] compiler: remove unused MO_U_MulMayOflo
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Tue Nov 29 04:48:32 UTC 2022
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
d4134e92 by Cheng Shao at 2022-11-28T23:48:14-05:00
compiler: remove unused MO_U_MulMayOflo
We actually only emit MO_S_MulMayOflo and never emit MO_U_MulMayOflo anywhere.
- - - - -
6 changed files:
- compiler/GHC/Cmm/MachOp.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
- compiler/GHC/CmmToC.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
Changes:
=====================================
compiler/GHC/Cmm/MachOp.hs
=====================================
@@ -65,7 +65,6 @@ data MachOp
| MO_S_Neg Width -- unary -
-- Unsigned multiply/divide
- | MO_U_MulMayOflo Width -- nonzero if unsigned multiply overflows
| MO_U_Quot Width -- unsigned / (same semantics as WordQuotOp)
| MO_U_Rem Width -- unsigned % (same semantics as WordRemOp)
@@ -251,7 +250,6 @@ isCommutableMachOp mop =
MO_Ne _ -> True
MO_Mul _ -> True
MO_S_MulMayOflo _ -> True
- MO_U_MulMayOflo _ -> True
MO_And _ -> True
MO_Or _ -> True
MO_Xor _ -> True
@@ -379,7 +377,6 @@ machOpResultType platform mop tys =
MO_S_Quot r -> cmmBits r
MO_S_Rem r -> cmmBits r
MO_S_Neg r -> cmmBits r
- MO_U_MulMayOflo r -> cmmBits r
MO_U_Quot r -> cmmBits r
MO_U_Rem r -> cmmBits r
@@ -473,7 +470,6 @@ machOpArgReps platform op =
MO_S_Quot r -> [r,r]
MO_S_Rem r -> [r,r]
MO_S_Neg r -> [r]
- MO_U_MulMayOflo r -> [r,r]
MO_U_Quot r -> [r,r]
MO_U_Rem r -> [r,r]
=====================================
compiler/GHC/Cmm/Parser.y
=====================================
@@ -961,7 +961,6 @@ machOps = listToUFM $
( "ne", MO_Ne ),
( "mul", MO_Mul ),
( "mulmayoflo", MO_S_MulMayOflo ),
- ( "mulmayoflou", MO_U_MulMayOflo ),
( "neg", MO_S_Neg ),
( "quot", MO_S_Quot ),
( "rem", MO_S_Rem ),
=====================================
compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
=====================================
@@ -910,7 +910,6 @@ getRegister' config plat expr
intOp True w (\d x y -> toOL [ SDIV t x y, MSUB d t y x ])
-- Unsigned multiply/divide
- MO_U_MulMayOflo _w -> unsupportedP plat expr
MO_U_Quot w -> intOp False w (\d x y -> unitOL $ UDIV d x y)
MO_U_Rem w -> withTempIntReg w $ \t ->
intOp False w (\d x y -> toOL [ UDIV t x y, MSUB d t y x ])
@@ -962,9 +961,6 @@ getRegister' config plat expr
-> pprPanic "getRegister' (variadic CmmMachOp): " (pdoc plat expr)
where
- unsupportedP :: OutputableP env a => env -> a -> b
- unsupportedP platform op = pprPanic "Unsupported op:" (pdoc platform op)
-
isNbitEncodeable :: Int -> Integer -> Bool
isNbitEncodeable n i = let shift = n - 1 in (-1 `shiftL` shift) <= i && i < (1 `shiftL` shift)
-- This needs to check if n can be encoded as a bitmask immediate:
=====================================
compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
=====================================
@@ -656,7 +656,6 @@ lower_CmmMachOp lbl (MO_S_Neg w0) [x] =
lbl
(MO_Sub w0)
[CmmLit $ CmmInt 0 w0, x]
-lower_CmmMachOp lbl (MO_U_MulMayOflo w0) xs = lower_MO_MulMayOflo lbl w0 xs
lower_CmmMachOp lbl (MO_U_Quot w0) xs =
lower_MO_Bin_Homo
(WasmDiv Unsigned)
=====================================
compiler/GHC/CmmToC.hs
=====================================
@@ -430,8 +430,7 @@ pprMachOpApp :: Platform -> MachOp -> [CmmExpr] -> SDoc
pprMachOpApp platform op args
| isMulMayOfloOp op
= text "mulIntMayOflo" <> parens (commafy (map (pprExpr platform) args))
- where isMulMayOfloOp (MO_U_MulMayOflo _) = True
- isMulMayOfloOp (MO_S_MulMayOflo _) = True
+ where isMulMayOfloOp (MO_S_MulMayOflo _) = True
isMulMayOfloOp _ = False
pprMachOpApp platform mop args
@@ -775,10 +774,6 @@ pprMachOp_for_C platform mop = case mop of
(text "MO_S_MulMayOflo")
(panic $ "PprC.pprMachOp_for_C: MO_S_MulMayOflo"
++ " should have been handled earlier!")
- MO_U_MulMayOflo _ -> pprTrace "offending mop:"
- (text "MO_U_MulMayOflo")
- (panic $ "PprC.pprMachOp_for_C: MO_U_MulMayOflo"
- ++ " should have been handled earlier!")
MO_V_Insert {} -> pprTrace "offending mop:"
(text "MO_V_Insert")
=====================================
compiler/GHC/CmmToLlvm/CodeGen.hs
=====================================
@@ -1451,7 +1451,6 @@ genMachOp _ op [x] = case op of
MO_S_MulMayOflo _ -> panicOp
MO_S_Quot _ -> panicOp
MO_S_Rem _ -> panicOp
- MO_U_MulMayOflo _ -> panicOp
MO_U_Quot _ -> panicOp
MO_U_Rem _ -> panicOp
@@ -1633,8 +1632,6 @@ genMachOp_slow opt op [x, y] = case op of
MO_Sub _ -> genBinMach LM_MO_Sub
MO_Mul _ -> genBinMach LM_MO_Mul
- MO_U_MulMayOflo _ -> panic "genMachOp: MO_U_MulMayOflo unsupported!"
-
MO_S_MulMayOflo w -> isSMulOK w x y
MO_S_Quot _ -> genBinMach LM_MO_SDiv
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d4134e920a79ddfe7abb291964614e4f428c1a24
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d4134e920a79ddfe7abb291964614e4f428c1a24
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/20221128/c1f0df5f/attachment-0001.html>
More information about the ghc-commits
mailing list