File 0805-erts-Fix-bug-for-enable-sharing-preserving-and-bit-s.patch of Package erlang

From 38cc08e241a8be720608d8e2532b5bb451c413c5 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Fri, 1 Nov 2019 15:21:06 +0100
Subject: [PATCH] erts: Fix bug for --enable-sharing-preserving and bit strings

when sending (copying) a term that contains both
a sub bit string of a heap binary
AND more than one direct reference to the same heap binary.

Example:

<<SubBin:Bits/bits, _/bits>> = HeapBin,
Receiver ! {HeapBin, SubBin, HeapBin}
---
 erts/emulator/beam/copy.c           | 52 ++++++++++++++++++++++++++++---------
 erts/emulator/test/binary_SUITE.erl | 38 +++++++++++++++++++++++++++
 2 files changed, 78 insertions(+), 12 deletions(-)

diff --git a/erts/emulator/beam/copy.c b/erts/emulator/beam/copy.c
index ccc4cbad43..ed5badfdf5 100644
--- a/erts/emulator/beam/copy.c
+++ b/erts/emulator/beam/copy.c
@@ -1199,11 +1199,25 @@ Uint copy_shared_calculate(Eterm obj, erts_shcopy_t *info)
 		} else {
 		    extra_bytes = 0;
 		}
-		ASSERT(is_boxed(real_bin) &&
-		       (((*boxed_val(real_bin)) &
-			 (_TAG_HEADER_MASK - _BINARY_XXX_MASK - BOXED_VISITED_MASK))
-			== _TAG_HEADER_REFC_BIN));
-		hdr = *_unchecked_binary_val(real_bin) & ~BOXED_VISITED_MASK;
+                ASSERT(is_boxed(real_bin));
+                hdr = *_unchecked_binary_val(real_bin);
+                switch (primary_tag(hdr)) {
+                case TAG_PRIMARY_HEADER:
+                    /* real_bin is untouched, only referred by sub-bins so far */
+                    break;
+                case BOXED_VISITED:
+                    /* real_bin referred directly once so far */
+                    hdr = (hdr - BOXED_VISITED) + TAG_PRIMARY_HEADER;
+                    break;
+                case BOXED_SHARED_PROCESSED:
+                case BOXED_SHARED_UNPROCESSED:
+                    /* real_bin referred directly more than once */
+                    e = hdr >> _TAG_PRIMARY_SIZE;
+                    hdr = SHTABLE_X(t, e);
+                    hdr = (hdr & ~BOXED_VISITED_MASK) + TAG_PRIMARY_HEADER;
+                    break;
+                }
+
 		if (thing_subtag(hdr) == HEAP_BINARY_SUBTAG) {
 		    sum += heap_bin_size(size+extra_bytes);
 		} else {
@@ -1569,11 +1583,6 @@ Uint copy_shared_perform(Eterm obj, Uint size, erts_shcopy_t *info,
 		    extra_bytes = 0;
 		}
 		real_size = size+extra_bytes;
-		ASSERT(is_boxed(real_bin) &&
-		       (((*boxed_val(real_bin)) &
-			 (_TAG_HEADER_MASK - _BINARY_XXX_MASK - BOXED_VISITED_MASK))
-			== _TAG_HEADER_REFC_BIN));
-		ptr = _unchecked_binary_val(real_bin);
 		*resp = make_binary(hp);
 		if (extra_bytes != 0) {
 		    ErlSubBin* res = (ErlSubBin *) hp;
@@ -1586,7 +1595,26 @@ Uint copy_shared_perform(Eterm obj, Uint size, erts_shcopy_t *info,
 		    res->is_writable = 0;
 		    res->orig = make_binary(hp);
 		}
-		if (thing_subtag(*ptr & ~BOXED_VISITED_MASK) == HEAP_BINARY_SUBTAG) {
+                ASSERT(is_boxed(real_bin));
+                ptr = _unchecked_binary_val(real_bin);
+                hdr = *ptr;
+                switch (primary_tag(hdr)) {
+                case TAG_PRIMARY_HEADER:
+                    /* real_bin is untouched, ie only referred by sub-bins */
+                    break;
+                case BOXED_VISITED:
+                    /* real_bin referred directly once */
+                    hdr = (hdr - BOXED_VISITED) + TAG_PRIMARY_HEADER;
+                    break;
+                case BOXED_SHARED_PROCESSED:
+                case BOXED_SHARED_UNPROCESSED:
+                    /* real_bin referred directly more than once */
+                    e = hdr >> _TAG_PRIMARY_SIZE;
+                    hdr = SHTABLE_X(t, e);
+                    hdr = (hdr & ~BOXED_VISITED_MASK) + TAG_PRIMARY_HEADER;
+                    break;
+                }
+		if (thing_subtag(hdr) == HEAP_BINARY_SUBTAG) {
 		    ErlHeapBin* from = (ErlHeapBin *) ptr;
 		    ErlHeapBin* to = (ErlHeapBin *) hp;
 		    hp += heap_bin_size(real_size);
@@ -1596,7 +1624,7 @@ Uint copy_shared_perform(Eterm obj, Uint size, erts_shcopy_t *info,
 		} else {
 		    ProcBin* from = (ProcBin *) ptr;
 		    ProcBin* to = (ProcBin *) hp;
-		    ASSERT(thing_subtag(*ptr & ~BOXED_VISITED_MASK) == REFC_BINARY_SUBTAG);
+		    ASSERT(thing_subtag(hdr) == REFC_BINARY_SUBTAG);
 		    if (from->flags) {
 			erts_emasculate_writable_binary(from);
 		    }
diff --git a/erts/emulator/test/binary_SUITE.erl b/erts/emulator/test/binary_SUITE.erl
index 1c7d278bb0..4726d167ba 100644
--- a/erts/emulator/test/binary_SUITE.erl
+++ b/erts/emulator/test/binary_SUITE.erl
@@ -51,6 +51,7 @@
 	 terms/1, terms_float/1, float_middle_endian/1,
 	 external_size/1, t_iolist_size/1,
 	 t_hash/1,
+         sub_bin_copy/1,
 	 bad_size/1,
 	 bad_term_to_binary/1,
 	 bad_binary_to_term_2/1,safe_binary_to_term2/1,
@@ -75,6 +76,7 @@ all() ->
      terms_float, float_middle_endian, external_size, t_iolist_size,
      bad_binary_to_term_2, safe_binary_to_term2,
      bad_binary_to_term, bad_terms, t_hash, bad_size,
+     sub_bin_copy,
      bad_term_to_binary, more_bad_terms, otp_5484, otp_5933,
      ordering, unaligned_order, gc_test,
      bit_sized_binary_sizes, otp_6817, otp_8117, deep,
@@ -1556,6 +1558,42 @@ cmp_old_impl(Config) when is_list(Config) ->
 	    ok
     end.
 
+%% OTP-16265
+%% This testcase is mainly targeted toward --enable-sharing-preserving.
+sub_bin_copy(Config) when is_list(Config) ->
+    Papa = self(),
+    Echo = spawn_link(fun() -> echo(Papa) end),
+    HeapBin = list_to_binary(lists:seq(1,3)),
+    sub_bin_copy_1(HeapBin, Echo),
+    ProcBin = list_to_binary(lists:seq(1,65)),
+    sub_bin_copy_1(ProcBin, Echo),
+    unlink(Echo),
+    exit(Echo, kill),
+    ok.
+
+sub_bin_copy_1(RealBin, Echo) ->
+    Bits = bit_size(RealBin) - 1,
+    <<SubBin:Bits/bits, _/bits>> = RealBin,
+
+    %% Send (copy) messages consisting of combinations of both
+    %% the SubBin and the RealBin it refers to.
+    [begin
+         Echo ! Combo,
+         {_, Combo} = {Combo, receive M -> M end}
+     end
+     || Len <- lists:seq(2,5), Combo <- combos([RealBin, SubBin], Len)],
+    ok.
+
+combos(_, 0) ->
+    [[]];
+combos(Elements, Len) ->
+    [[E | C] || E <- Elements, C <- combos(Elements,Len-1)].
+
+echo(Papa) ->
+    receive M -> Papa ! M end,
+    echo(Papa).
+
+
 %% Utilities.
 
 huge_iolist(Lim) ->
-- 
2.16.4

openSUSE Build Service is sponsored by