File 2991-beam_emu-Fixed-point-optimize-the-rem-instruction.patch of Package erlang
From 964f3cc03be11b80901aa1730cd648f0559d5d6c Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Wed, 19 Feb 2020 09:38:29 +0100
Subject: [PATCH] beam_emu: Fixed-point optimize the 'rem' instruction
---
erts/emulator/beam/arith_instrs.tab | 14 +++++++++++++-
erts/emulator/test/small_SUITE.erl | 12 ++++++++++++
2 files changed, 25 insertions(+), 1 deletion(-)
diff --git a/erts/emulator/beam/arith_instrs.tab b/erts/emulator/beam/arith_instrs.tab
index 29f761286f..335b121ad8 100644
--- a/erts/emulator/beam/arith_instrs.tab
+++ b/erts/emulator/beam/arith_instrs.tab
@@ -217,6 +217,11 @@ i_int_div(Fail, Op1, Op2, Dst) {
$BIF_ERROR_ARITY_2($Fail, BIF_intdiv_2, op1, op2);
} else if (ERTS_LIKELY(is_both_small(op1, op2))) {
Sint ires = signed_val(op1) / signed_val(op2);
+
+ /* We could skip this check if it weren't for the fact that dividing
+ * MIN_SMALL by -1 causes an overflow, and we have nothing to gain from
+ * fixed-point optimizing this instruction since there's no
+ * __builtin_div_overflow. */
if (ERTS_LIKELY(IS_SSMALL(ires))) {
$Dst = make_small(ires);
$NEXT0();
@@ -241,7 +246,14 @@ rem.execute(Fail, Dst) {
c_p->freason = BADARITH;
$BIF_ERROR_ARITY_2($Fail, BIF_rem_2, RemOp1, RemOp2);
} else if (ERTS_LIKELY(is_both_small(RemOp1, RemOp2))) {
- $Dst = make_small(signed_val(RemOp1) % signed_val(RemOp2));
+ Sint lhs_untagged, rhs_untagged, untagged_result;
+
+ /* See plus.execute */
+ lhs_untagged = (RemOp1 & ~_TAG_IMMED1_MASK);
+ rhs_untagged = (RemOp2 & ~_TAG_IMMED1_MASK);
+ untagged_result = lhs_untagged % rhs_untagged;
+
+ $Dst = untagged_result | _TAG_IMMED1_SMALL;
$NEXT0();
} else {
$OUTLINED_ARITH_2($Fail, int_rem, BIF_rem_2, RemOp1, RemOp2, $Dst);
diff --git a/erts/emulator/test/small_SUITE.erl b/erts/emulator/test/small_SUITE.erl
index 00a02e5560..7dbe1fb4f4 100644
--- a/erts/emulator/test/small_SUITE.erl
+++ b/erts/emulator/test/small_SUITE.erl
@@ -78,6 +78,15 @@ sp2_1(N, MinS, MaxS) when N > 0 ->
[N | sp2_1(N bsl 1, MinS, MaxS)].
arith_test(A, B, MinS, MaxS) ->
+ try arith_test_1(A, B, MinS, MaxS) of
+ ok -> ok
+ catch
+ error:Reason:Stk ->
+ ct:fail("arith_test failed with ~p~n\tA = ~p~n\tB = ~p\n\t~p",
+ [Reason, A, B, Stk])
+ end.
+
+arith_test_1(A, B, MinS, MaxS) ->
verify_kind(A + B, MinS, MaxS),
verify_kind(B + A, MinS, MaxS),
verify_kind(A - B, MinS, MaxS),
@@ -97,6 +106,9 @@ arith_test(A, B, MinS, MaxS) ->
true = B =:= 0 orelse ((A * B) div id(B) =:= A),
true = A =:= 0 orelse ((B * A) div id(A) =:= B),
+ true = B =:= 0 orelse (((A div id(B)) * id(B) + A rem id(B)) =:= A),
+ true = A =:= 0 orelse (((B div id(A)) * id(A) + B rem id(A)) =:= B),
+
ok.
%% Verifies that N is a small when it should be
--
2.16.4