File 0509-Fix-reading-beyond-end-of-bignum-in-integer-squaring.patch of Package erlang

From c5bb52143bd28c8ce34e427dbf7f024b6e6a65e1 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Wed, 12 Dec 2018 14:53:40 +0100
Subject: [PATCH] Fix reading beyond end of bignum in integer squaring

The multiplication of two bignums is specially optimized when the two
operands have the same address, because squaring can be done more
efficiently than multiplication of two arbitrary integers.  That is,
expressions such as `I * I` will be calculated by squaring the value
of `I`.

The optimized function for squaring would read one word beyond the
end of the bignum in the last iteration of a loop. The garbage
value would never be used. In almost all circumstances that would
be harmless. Only if the read word happened to fall on the start
of an unmapped page would the runtime crash. That is unlikely
to happen because most bignums are stored on a process heap, and
since the stack is located at the other end of the block that the
heap is located in, the word beyond the end of bignum is guaranteed
to be readable.
---
 erts/emulator/beam/big.c         | 12 +++++-------
 erts/emulator/test/big_SUITE.erl | 18 +++++++++++++++++-
 2 files changed, 22 insertions(+), 8 deletions(-)

diff --git a/erts/emulator/beam/big.c b/erts/emulator/beam/big.c
index 84338769e0..dac9574fa5 100644
--- a/erts/emulator/beam/big.c
+++ b/erts/emulator/beam/big.c
@@ -668,27 +668,25 @@ static dsize_t I_mul(ErtsDigit* x, dsize_t xl, ErtsDigit* y, dsize_t yl, ErtsDig
 
 static dsize_t I_sqr(ErtsDigit* x, dsize_t xl, ErtsDigit* r)
 {
-    ErtsDigit d_next = *x;
     ErtsDigit d;
     ErtsDigit* r0 = r;
     ErtsDigit* s = r;
 
     if ((r + xl) == x)	/* "Inline" operation */
 	*x = 0;
-    x++;
 	
     while(xl--) {
-	ErtsDigit* y = x;
+	ErtsDigit* y;
 	ErtsDigit y_0 = 0, y_1 = 0, y_2 = 0, y_3 = 0;
 	ErtsDigit b0, b1;
 	ErtsDigit z0, z1, z2;
 	ErtsDigit t;
 	dsize_t y_l = xl;
-		
+
+        d = *x;
+        x++;
+        y = x;
 	s = r;
-	d = d_next;
-	d_next = *x; 
-	x++;
 
 	DMUL(d, d, b1, b0);
 	DSUMc(*s, b0, y_3, t);
diff --git a/erts/emulator/test/big_SUITE.erl b/erts/emulator/test/big_SUITE.erl
index 0a42b09903..5b602dd4dc 100644
--- a/erts/emulator/test/big_SUITE.erl
+++ b/erts/emulator/test/big_SUITE.erl
@@ -168,7 +168,11 @@ eval({op,_,Op,A0,B0}, LFH) ->
     Res = eval_op(Op, A, B),
     erlang:garbage_collect(),
     Res;
-eval({integer,_,I}, _) -> I;
+eval({integer,_,I}, _) ->
+    %% "Parasitic" ("symbiotic"?) test of squaring all numbers
+    %% found in the test data.
+    test_squaring(I),
+    I;
 eval({call,_,{atom,_,Local},Args0}, LFH) ->
     Args = eval_list(Args0, LFH),
     LFH(Local, Args).
@@ -192,6 +196,18 @@ eval_op('bxor', A, B) -> A bxor B;
 eval_op('bsl', A, B) -> A bsl B;
 eval_op('bsr', A, B) -> A bsr B.
 
+test_squaring(I) ->
+    %% Multiplying an integer by itself is specially optimized, so we
+    %% should take special care to test squaring.  The optimization
+    %% will kick in when the two operands have the same address.
+    Sqr = I * I,
+
+    %% This expression will be multiplied in the usual way, because
+    %% the the two operands for '*' are stored at different addresses.
+    Sqr = I * ((I + id(1)) - id(1)),
+
+    ok.
+
 %% Built in test functions
 
 fac(0) -> 1;
-- 
2.16.4

openSUSE Build Service is sponsored by