[Git][ghc/ghc][wip/supersven/imulMayOflo_x86] Add test(s) for %mulmayoflo primop

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Fri Jul 7 15:48:51 UTC 2023



Sven Tennie pushed to branch wip/supersven/imulMayOflo_x86 at Glasgow Haskell Compiler / GHC


Commits:
5ae09143 by Sven Tennie at 2023-07-07T17:45:10+02:00
Add test(s) for %mulmayoflo primop

One test checks the minimal contract (see MulMayOflo.hs), the other
checks a perfect implementation.

- - - - -


5 changed files:

- compiler/GHC/Cmm/MachOp.hs
- + testsuite/tests/codeGen/should_run/MulMayOflo.hs
- + testsuite/tests/codeGen/should_run/MulMayOflo_full.cmm
- + testsuite/tests/codeGen/should_run/MulMayOflo_minimal.cmm
- testsuite/tests/codeGen/should_run/all.T


Changes:

=====================================
compiler/GHC/Cmm/MachOp.hs
=====================================
@@ -56,6 +56,25 @@ Note that there are variety of places in the native code generator where we
 assume that the code produced for a MachOp does not introduce new blocks.
 -}
 
+-- Note [MO_S_MulMayOflo significant width]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+--
+-- There are two interpretations in the code about what a multiplication
+-- overflow exactly means:
+--
+-- 1. The result does not fit into the specified width (of type Width.)
+-- 2. The result does not fit into a register.
+--
+-- (2) has some flaws: A following MO_Mul has a width, too. So MO_S_MulMayOflo
+-- may signal no overflow, while MO_Mul truncates the result. There are
+-- architectures with several register widths and it might be hard to decide
+-- what's an overflow and what not. Both attributes can easily lead to subtle
+-- bugs.
+--
+-- (1) has the benefit that its interpretation is completely independent of the
+-- architecture. So, the mid-term plan is to migrate to this
+-- interpretation/sematics.
+
 data MachOp
   -- Integer operations (insensitive to signed/unsigned)
   = MO_Add Width
@@ -65,7 +84,8 @@ data MachOp
   | MO_Mul Width                -- low word of multiply
 
   -- Signed multiply/divide
-  | MO_S_MulMayOflo Width       -- nonzero if signed multiply overflows
+  | MO_S_MulMayOflo Width       -- nonzero if signed multiply overflows. See
+                                -- Note [MO_S_MulMayOflo significant width]
   | MO_S_Quot Width             -- signed / (same semantics as IntQuotOp)
   | MO_S_Rem  Width             -- signed % (same semantics as IntRemOp)
   | MO_S_Neg  Width             -- unary -


=====================================
testsuite/tests/codeGen/should_run/MulMayOflo.hs
=====================================
@@ -0,0 +1,27 @@
+{-# LANGUAGE ForeignFunctionInterface #-}
+{-# LANGUAGE GHCForeignImportPrim #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+
+{-
+ N.B. the contract of '%mulmayoflo' is a bit weak: "Return non-zero if there is
+ any possibility that the signed multiply of a and b might overflow. Return zero
+ only if you are absolutely sure that it won't overflow. If in doubt, return
+ non-zero." (Stg.h)
+
+ So, this test is split into two parts:
+  - the minimal contract
+  - for architectures which have a perfect implementation, also assert that
+ The decission which variant to run is made in `all.T`.
+-}
+
+module Main where
+
+import GHC.Exts
+
+-- The argument and return types are unimportant: They're only used to force
+-- evaluation, but carry no information.
+foreign import prim "runCmmzh" runCmmzh# :: Word# -> Word#
+
+main :: IO ()
+main = print . show $ W# (runCmmzh# 42##)


=====================================
testsuite/tests/codeGen/should_run/MulMayOflo_full.cmm
=====================================
@@ -0,0 +1,98 @@
+// Suppress empty ASSERT() optimization
+#define USE_ASSERTS_ALL_WAYS 1
+
+#include "Cmm.h"
+#include "MachDeps.h"
+
+runCmmzh() {
+// BEWARE: Cmm isn't really type checked. I.e. you may construct
+// 256::I8, which is obviously wrong and let's to strange behaviour.
+
+  // --- I8
+  ASSERT(%mulmayoflo(64::I8, 2::I8) > 0::I8);
+  ASSERT(%mulmayoflo(2::I8, 64::I8) > 0::I8);
+  ASSERT(%mulmayoflo(-65::I8, 2::I8) > 0::I8);
+  ASSERT(%mulmayoflo(2::I8, -65::I8) > 0::I8);
+
+  // --- I16
+  ASSERT(%mulmayoflo(16384::I16, 2::I16) > 0::I16);
+  ASSERT(%mulmayoflo(2::I16, 16384::I16) > 0::I16);
+  ASSERT(%mulmayoflo(-16385::I16, 2::I16) > 0::I16);
+  ASSERT(%mulmayoflo(2::I16, -16385::I16) > 0::I16);
+
+
+  // -- I32
+  ASSERT(%mulmayoflo(2::I32, 1073741824::I32) > 0::I32);
+  ASSERT(%mulmayoflo(1073741824::I32, 2::I32) > 0::I32);
+  ASSERT(%mulmayoflo(2::I32, -1073741825::I32) > 0::I32);
+  ASSERT(%mulmayoflo(-1073741825::I32, 2::I32) > 0::I32);
+
+#if WORD_SIZE_IN_BITS >= 64
+  // -- I64
+  ASSERT(%mulmayoflo(4611686018427387904::I64, 2::I64) > 0::I64);
+  ASSERT(%mulmayoflo(2::I64, 4611686018427387904::I64) > 0::I64);
+  ASSERT(%mulmayoflo(-4611686018427387905::I64, 2::I64) > 0::I64);
+  ASSERT(%mulmayoflo(2::I64, -4611686018427387905::I64) > 0::I64);
+#endif
+
+  // --- I8
+  ASSERT(%mulmayoflo(1::I8, 1::I8) == 0::I8);
+  ASSERT(%mulmayoflo(0::I8, 0::I8) == 0::I8);
+  ASSERT(%mulmayoflo(-1::I8, 1::I8) == 0::I8);
+  ASSERT(%mulmayoflo(1::I8, -1::I8) == 0::I8);
+  ASSERT(%mulmayoflo(127::I8, 1::I8) == 0::I8);
+  ASSERT(%mulmayoflo(1::I8, 127::I8) == 0::I8);
+  ASSERT(%mulmayoflo(63::I8, 2::I8) == 0::I8);
+  ASSERT(%mulmayoflo(2::I8, 63::I8) == 0::I8);
+  ASSERT(%mulmayoflo(127::I8, -1::I8) == 0::I8);
+  ASSERT(%mulmayoflo(-1::I8, 127::I8) == 0::I8);
+  ASSERT(%mulmayoflo(-128::I8, 1::I8) == 0::I8);
+  ASSERT(%mulmayoflo(-64::I8, 2::I8) == 0::I8);
+  ASSERT(%mulmayoflo(2::I8, -64::I8) == 0::I8);
+
+  // --- I16
+  ASSERT(%mulmayoflo(1::I16, 1::I16) == 0::I16);
+  ASSERT(%mulmayoflo(0::I16, 0::I16) == 0::I16);
+  ASSERT(%mulmayoflo(-1::I16, 1::I16) == 0::I16);
+  ASSERT(%mulmayoflo(1::I16, -1::I16) == 0::I16);
+  ASSERT(%mulmayoflo(32767::I16, 1::I16) == 0::I16);
+  ASSERT(%mulmayoflo(1::I16,32767 ::I16) == 0::I16);
+  ASSERT(%mulmayoflo(16383::I16, 2::I16) == 0::I16);
+  ASSERT(%mulmayoflo(2::I16, 16383::I16) == 0::I16);
+  ASSERT(%mulmayoflo(-16384::I16, 2::I16) == 0::I16);
+  ASSERT(%mulmayoflo(2::I16, -16384::I16) == 0::I16);
+  ASSERT(%mulmayoflo(-32768::I16, 1::I16) == 0::I16);
+  ASSERT(%mulmayoflo(1::I16, -32768::I16) == 0::I16);
+
+  // -- I32
+  ASSERT(%mulmayoflo(1::I32, 1::I32) == 0::I32);
+  ASSERT(%mulmayoflo(0::I32, 0::I32) == 0::I32);
+  ASSERT(%mulmayoflo(-1::I32, 1::I32) == 0::I32);
+  ASSERT(%mulmayoflo(1::I32, -1::I32) == 0::I32);
+  ASSERT(%mulmayoflo(2147483647::I32, 1::I32) == 0::I32);
+  ASSERT(%mulmayoflo(1::I32, 2147483647::I32) == 0::I32);
+  ASSERT(%mulmayoflo(-2147483648::I32, 1::I32) == 0::I32);
+  ASSERT(%mulmayoflo(1::I32, -2147483648::I32) == 0::I32);
+  ASSERT(%mulmayoflo(2::I32, 1073741823::I32) == 0::I32);
+  ASSERT(%mulmayoflo(1073741823::I32, 2::I32) == 0::I32);
+  ASSERT(%mulmayoflo(2::I32, -1073741824::I32) == 0::I32);
+  ASSERT(%mulmayoflo(-1073741824::I32, 2::I32) == 0::I32);
+
+#if WORD_SIZE_IN_BITS >= 64
+  // -- I64
+  ASSERT(%mulmayoflo(1::I64, 1::I64) == 0::I64);
+  ASSERT(%mulmayoflo(0::I64, 0::I64) == 0::I64);
+  ASSERT(%mulmayoflo(-1::I64, 1::I64) == 0::I64);
+  ASSERT(%mulmayoflo(1::I64, -1::I64) == 0::I64);
+  ASSERT(%mulmayoflo(9223372036854775807::I64, 1::I64) == 0::I64);
+  ASSERT(%mulmayoflo(1::I64, 9223372036854775807::I64) == 0::I64);
+  ASSERT(%mulmayoflo(-9223372036854775808::I64, 1::I64) == 0::I64);
+  ASSERT(%mulmayoflo(1::I64, -9223372036854775808::I64) == 0::I64);
+  ASSERT(%mulmayoflo(4611686018427387903::I64, 2::I64) == 0::I64);
+  ASSERT(%mulmayoflo(2::I64, 4611686018427387903::I64) == 0::I64);
+  ASSERT(%mulmayoflo(-4611686018427387904::I64, 2::I64) == 0::I64);
+  ASSERT(%mulmayoflo(2::I64, -4611686018427387904::I64) == 0::I64);
+#endif
+
+  return(0);
+}


=====================================
testsuite/tests/codeGen/should_run/MulMayOflo_minimal.cmm
=====================================
@@ -0,0 +1,30 @@
+// Suppress empty ASSERT() optimization
+#define USE_ASSERTS_ALL_WAYS 1
+
+#include "Cmm.h"
+#include "MachDeps.h"
+
+runCmmzh() {
+// BEWARE: Cmm isn't really type checked. I.e. you may construct
+// 256::I8, which is obviously wrong and let's to strange behaviour.
+
+// Why aren't I8 and I16 tested here? Because many code generation backends only
+// check for register overflows, not overflows regarding a smaller width.
+// See Note [MO_S_MulMayOflo significant width]
+
+  // -- I32
+  ASSERT(%mulmayoflo(2::I32, 1073741824::I32) > 0::I32);
+  ASSERT(%mulmayoflo(1073741824::I32, 2::I32) > 0::I32);
+  ASSERT(%mulmayoflo(2::I32, -1073741825::I32) > 0::I32);
+  ASSERT(%mulmayoflo(-1073741825::I32, 2::I32) > 0::I32);
+
+#if WORD_SIZE_IN_BITS >= 64
+  // -- I64
+  ASSERT(%mulmayoflo(4611686018427387904::I64, 2::I64) > 0::I64);
+  ASSERT(%mulmayoflo(2::I64, 4611686018427387904::I64) > 0::I64);
+  ASSERT(%mulmayoflo(-4611686018427387905::I64, 2::I64) > 0::I64);
+  ASSERT(%mulmayoflo(2::I64, -4611686018427387905::I64) > 0::I64);
+#endif
+
+  return(0);
+}


=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -225,3 +225,18 @@ test('T22296',[only_ways(llvm_ways)
               ,unless(arch('x86_64'), skip)],compile_and_run,[''])
 test('T22798', expect_broken_for(23272, ['ghci-opt']), compile_and_run, ['-fregs-graph'])
 test('CheckBoundsOK', normal, compile_and_run, ['-fcheck-prim-bounds'])
+
+test('MulMayOflo_minimal',
+     [extra_files(['MulMayOflo.hs']),ignore_stdout],
+     multi_compile_and_run,
+     ['MulMayOflo', [('MulMayOflo_minimal.cmm', '')], ''])
+test('MulMayOflo_full',
+     [ extra_files(['MulMayOflo.hs']),
+       when(unregisterised(), skip),
+       unless(arch('x86_64') or arch('i386')
+              or arch('aarch64')
+              or arch('powerpc') or arch('powerpc64'),
+              skip),
+        ignore_stdout],
+     multi_compile_and_run,
+     ['MulMayOflo', [('MulMayOflo_full.cmm', '')], ''])



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5ae09143dcabf5125949ee4e2c6ee2ca8a5a42d1
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/20230707/7a428411/attachment-0001.html>


More information about the ghc-commits mailing list