[Git][ghc/ghc][wip/andreask/bound_cmm_folding] Cmm constant folding: Narrow results to operations bitwidth.
Andreas Klebinger (@AndreasK)
gitlab at gitlab.haskell.org
Mon Jul 1 13:53:04 UTC 2024
Andreas Klebinger pushed to branch wip/andreask/bound_cmm_folding at Glasgow Haskell Compiler / GHC
Commits:
eae742da by Andreas Klebinger at 2024-07-01T15:37:32+02:00
Cmm constant folding: Narrow results to operations bitwidth.
When constant folding operations on literals ensure the result
is still within bounds by explicitly narrowing the results.
Not doing so results in a lot of spurious assembler warnings
especially when testing primops.
- - - - -
3 changed files:
- compiler/GHC/Cmm/Opt.hs
- + testsuite/tests/cmm/opt/T24556.cmm
- testsuite/tests/cmm/opt/all.T
Changes:
=====================================
compiler/GHC/Cmm/Opt.hs
=====================================
@@ -50,6 +50,7 @@ constantFoldExprOpt e = wrapRecExpOpt f e
CmmMachOp op' args' -> fromMaybe (CmmMachOp op' args') <$> cmmMachOpFoldOptM cfg op' args'
e -> pure e
f (CmmRegOff r 0) = pure (CmmReg r)
+ f (CmmLit (CmmInt x rep)) = pure (CmmLit $ CmmInt (narrowU rep x) rep)
f e = pure e
constantFoldExpr :: Platform -> CmmExpr -> CmmExpr
@@ -82,7 +83,7 @@ cmmMachOpFoldM
cmmMachOpFoldM _ op [CmmLit (CmmInt x rep)]
= Just $! case op of
- MO_S_Neg _ -> CmmLit (CmmInt (-x) rep)
+ MO_S_Neg _ -> CmmLit (CmmInt (narrowS rep (-x)) rep)
MO_Not _ -> CmmLit (CmmInt (complement x) rep)
-- these are interesting: we must first narrow to the
@@ -159,9 +160,9 @@ cmmMachOpFoldM platform mop [CmmLit (CmmInt x xrep), CmmLit (CmmInt y _)]
MO_S_Lt _ -> Just $! CmmLit (CmmInt (if x_s < y_s then 1 else 0) (wordWidth platform))
MO_S_Le _ -> Just $! CmmLit (CmmInt (if x_s <= y_s then 1 else 0) (wordWidth platform))
- MO_Add r -> Just $! CmmLit (CmmInt (x + y) r)
- MO_Sub r -> Just $! CmmLit (CmmInt (x - y) r)
- MO_Mul r -> Just $! CmmLit (CmmInt (x * y) r)
+ MO_Add r -> Just $! CmmLit (CmmInt (narrowU r $ x + y) r)
+ MO_Sub r -> Just $! CmmLit (CmmInt (narrowS r $ x - y) r)
+ MO_Mul r -> Just $! CmmLit (CmmInt (narrowU r $ x * y) r)
MO_U_Quot r | y /= 0 -> Just $! CmmLit (CmmInt (x_u `quot` y_u) r)
MO_U_Rem r | y /= 0 -> Just $! CmmLit (CmmInt (x_u `rem` y_u) r)
MO_S_Quot r | y /= 0 -> Just $! CmmLit (CmmInt (x_s `quot` y_s) r)
@@ -171,7 +172,7 @@ cmmMachOpFoldM platform mop [CmmLit (CmmInt x xrep), CmmLit (CmmInt y _)]
MO_Or r -> Just $! CmmLit (CmmInt (x .|. y) r)
MO_Xor r -> Just $! CmmLit (CmmInt (x `xor` y) r)
- MO_Shl r -> Just $! CmmLit (CmmInt (x `shiftL` fromIntegral y) r)
+ MO_Shl r -> Just $! CmmLit (CmmInt (narrowU r $ x `shiftL` fromIntegral y) r)
MO_U_Shr r -> Just $! CmmLit (CmmInt (x_u `shiftR` fromIntegral y) r)
MO_S_Shr r -> Just $! CmmLit (CmmInt (x_s `shiftR` fromIntegral y) r)
=====================================
testsuite/tests/cmm/opt/T24556.cmm
=====================================
@@ -0,0 +1,12 @@
+#include "Cmm.h"
+
+func(bits64 buffer) {
+ I8[buffer] = %lobits8(255 + 45);
+ I8[buffer+1] = %lobits8(310 - 10);
+ I8[buffer+2] = %lobits8(30 * 10);
+ I8[buffer+3] = %lobits8(150 << 1);
+ // This one comes from test-primops
+ I64[buffer+4] = %zx64(((1 :: bits16) & ((1 :: bits16) & (((516 :: bits16) * (154 :: bits16)) + bits16[buffer + (0 :: bits64)]))));
+ return(1);
+}
+
=====================================
testsuite/tests/cmm/opt/all.T
=====================================
@@ -3,3 +3,8 @@
test('T15188', cmm_src, makefile_test, [])
test('T18141', normal, compile, [''])
test('T20142', normal, compile, [''])
+
+# Cmm opt should not produce oversized literals in the assembly output.
+# We check this by telling the assembler to exit on warnings.
+test('T24556', [only_ways('optasm'), cmm_src], compile, ['-O -opta -Xassembler -opta --fatal-warnings'])
+
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eae742da78e538205ce335ab9f521afcdb390d78
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eae742da78e538205ce335ab9f521afcdb390d78
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/20240701/99419326/attachment-0001.html>
More information about the ghc-commits
mailing list