File 6301-Fix-bit-syntax-creation-of-a-bignum-in-a-short-non-a.patch of Package erlang

From 0da697c17faded2f59009156053682a2961735ac Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 26 Jun 2023 13:15:21 +0200
Subject: [PATCH] Fix bit syntax creation of a bignum in a short non-aligned
 segment

This bug was introduced in 9256aad02f77bc4ca8c2ed5a4b41d5cad834fad1.
---
 erts/emulator/beam/erl_bits.c             | 27 ++++++++++++++++++-----
 erts/emulator/test/bs_construct_SUITE.erl |  8 ++++++-
 2 files changed, 28 insertions(+), 7 deletions(-)

diff --git a/erts/emulator/beam/erl_bits.c b/erts/emulator/beam/erl_bits.c
index 0dc1d84627..d1bf243620 100644
--- a/erts/emulator/beam/erl_bits.c
+++ b/erts/emulator/beam/erl_bits.c
@@ -775,7 +775,7 @@ erts_new_bs_put_integer(ERL_BITS_PROTO_3(Eterm arg, Uint num_bits, unsigned flag
 	     */
 	    iptr = erts_current_bin+BYTE_OFFSET(bin_offset);
 	    b = *iptr & (0xff << rbits);
-	    b |= (signed_val(arg) & ((1 << num_bits)-1)) << (8-bit_offset-num_bits);
+	    b |= (signed_val(arg) & ((1 << num_bits)-1)) << (rbits-num_bits);
 	    *iptr = b;
 	} else if (bit_offset == 0) {
 	    /*
@@ -791,8 +791,8 @@ erts_new_bs_put_integer(ERL_BITS_PROTO_3(Eterm arg, Uint num_bits, unsigned flag
             Sint val = signed_val(arg);
             Uint rshift = bit_offset;
             Uint lshift = rbits;
-            Uint lmask = MAKE_MASK(8 - bit_offset);
-            Uint count = (num_bits - (8 - bit_offset)) / 8;
+            Uint lmask = MAKE_MASK(rbits);
+            Uint count = (num_bits - rbits) / 8;
             Uint bits, bits1;
 
             iptr = erts_current_bin+BYTE_OFFSET(bin_offset);
@@ -881,6 +881,19 @@ erts_new_bs_put_integer(ERL_BITS_PROTO_3(Eterm arg, Uint num_bits, unsigned flag
 	 */
 	fmt_big(erts_current_bin+BYTE_OFFSET(bin_offset),
                 NBYTES(num_bits), arg, num_bits, flags);
+    } else if (is_big(arg) && bit_offset + num_bits <= 8) {
+        /*
+         * All bits are in the same byte.
+         */
+        Uint rbits = 8 - bit_offset;
+        Sint sign = big_sign(arg);
+        ErtsDigit* dp = big_v(arg);
+        Uint val = sign ? -*dp : *dp;
+
+        iptr = erts_current_bin+BYTE_OFFSET(bin_offset);
+        b = *iptr & (0xff << rbits);
+        b |= (val & ((1 << num_bits)-1)) << (rbits-num_bits);
+        *iptr = b;
     } else if (is_big(arg)) {
         /*
          * Big number, not aligned on a byte boundary.
@@ -890,12 +903,14 @@ erts_new_bs_put_integer(ERL_BITS_PROTO_3(Eterm arg, Uint num_bits, unsigned flag
         Uint deoffs = BIT_OFFSET(bit_offset + num_bits);
         Uint lmask = MAKE_MASK(8 - bit_offset);
         Uint rmask = (deoffs) ? (MAKE_MASK(deoffs)<<(8-deoffs)) : 0;
-        Uint count = (num_bits - (8 - bit_offset)) / 8;
+        Uint count = (num_bits - lshift) / 8;
         Uint bits, bits1;
 
+        ASSERT(num_bits - lshift >= 0);
+
         /*
-         * Format it byte-aligned using the binary itself as a
-         * temporary buffer.
+         * Format the integer byte-aligned using the binary itself as
+         * a temporary buffer.
          */
         iptr = erts_current_bin + BYTE_OFFSET(bin_offset);
         b = *iptr;
diff --git a/erts/emulator/test/bs_construct_SUITE.erl b/erts/emulator/test/bs_construct_SUITE.erl
index 0e9a39b976..a346ec2ed6 100644
--- a/erts/emulator/test/bs_construct_SUITE.erl
+++ b/erts/emulator/test/bs_construct_SUITE.erl
@@ -779,10 +779,16 @@ dynamic_3(Bef, N, {Int0,Lpad,Rpad,Dynamic}=Data, Count) ->
     Dynamic(Bef, N, Int1, Lpad, Rpad),
     Dynamic(Bef, N, -Int1, Lpad, Rpad),
 
-    %% OTP-7085: Test a small number in a wide field.
+    %% OTP-7085: Test a small number in a wide segment.
     Int2 = Int0 band 16#FFFFFF,
     Dynamic(Bef, N, Int2, Lpad, Rpad),
     Dynamic(Bef, N, -Int2, Lpad, Rpad),
+
+    %% Test a bignum in a short segment.
+    Int4 = ((Lpad bxor Rpad) bsl N) bor Int0,
+    Dynamic(Bef, N, Int4, Lpad, Rpad),
+    Dynamic(Bef, N, -Int4, Lpad, Rpad),
+
     dynamic_3(Bef, N-1, Data, Count+1).
 
 dynamic_big(Bef, N, Int, Lpad, Rpad) ->
-- 
2.35.3

openSUSE Build Service is sponsored by