[Git][ghc/ghc][master] Fix isAArch64Bitmask for 32bit immediates.

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Oct 5 09:37:39 UTC 2023



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


Commits:
f20d02f8 by Andreas Klebinger at 2023-10-05T05:36:14-04:00
Fix isAArch64Bitmask for 32bit immediates.

Fixes #23802

- - - - -


1 changed file:

- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs


Changes:

=====================================
compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
=====================================
@@ -781,12 +781,12 @@ getRegister' config plat expr
       return $ Any (intFormat w) (\dst -> code_x `snocOL` annExpr expr (LSR (OpReg w dst) (OpReg w reg_x) (OpImm (ImmInteger n))))
 
     -- 3. Logic &&, ||
-    CmmMachOp (MO_And w) [(CmmReg reg), CmmLit (CmmInt n _)] | isAArch64Bitmask (fromIntegral n) ->
+    CmmMachOp (MO_And w) [(CmmReg reg), CmmLit (CmmInt n _)] | isAArch64Bitmask (opRegWidth w') (fromIntegral n) ->
       return $ Any (intFormat w) (\d -> unitOL $ annExpr expr (AND (OpReg w d) (OpReg w' r') (OpImm (ImmInteger n))))
       where w' = formatToWidth (cmmTypeFormat (cmmRegType reg))
             r' = getRegisterReg plat reg
 
-    CmmMachOp (MO_Or w) [(CmmReg reg), CmmLit (CmmInt n _)] | isAArch64Bitmask (fromIntegral n) ->
+    CmmMachOp (MO_Or w) [(CmmReg reg), CmmLit (CmmInt n _)] | isAArch64Bitmask (opRegWidth w') (fromIntegral n) ->
       return $ Any (intFormat w) (\d -> unitOL $ annExpr expr (ORR (OpReg w d) (OpReg w' r') (OpImm (ImmInteger n))))
       where w' = formatToWidth (cmmTypeFormat (cmmRegType reg))
             r' = getRegisterReg plat reg
@@ -1070,13 +1070,16 @@ getRegister' config plat expr
 -- | Is a given number encodable as a bitmask immediate?
 --
 -- https://stackoverflow.com/questions/30904718/range-of-immediate-values-in-armv8-a64-assembly
-isAArch64Bitmask :: Integer -> Bool
+isAArch64Bitmask :: Width -> Integer -> Bool
 -- N.B. zero and ~0 are not encodable as bitmask immediates
-isAArch64Bitmask 0  = False
-isAArch64Bitmask n
-  | n == bit 64 - 1 = False
-isAArch64Bitmask n  =
-    check 64 || check 32 || check 16 || check 8
+isAArch64Bitmask width n =
+  assert (width `elem` [W32,W64]) $
+  case n of
+    0 -> False
+    _ | n == bit (widthInBits width) - 1
+      -> False -- 1111...1111
+      | otherwise
+      -> (width == W64 && check 64) || check 32 || check 16 || check 8
   where
     -- Check whether @n@ can be represented as a subpattern of the given
     -- width.



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f20d02f81e1e84887db311a475adb68ae3c3cfdc
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/20231005/fb8facd1/attachment-0001.html>


More information about the ghc-commits mailing list