File 2491-Introduce-erts_debug-unaligned_bitstring-2.patch of Package erlang
From 8f40ded22a98bd206565f2f7f663d84e6bcb9fc7 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 14 Aug 2025 05:58:37 +0200
Subject: [PATCH] Introduce erts_debug:unaligned_bitstring/2
Several test suites use the following trick to create a sub binary
that is not anligned on byte boundaries:
make_unaligned_sub_binary(Bin0) ->
Bin1 = <<0:3,Bin0/binary,31:5>>,
Size = size(Bin0),
<<0:3,Bin:Size/binary,31:5>> = Bin1,
Bin.
Such binaries are used to test that BIFs properly handle unaligned
sub binaries.
This trick no longer works for binaries smaller than 64 bytes, because
the runtime system will no longer create sub binaries referencing heap
binaries.
To ensure that we still can check that BIFs handle unaligned binaries,
this commit adds the `erts_debug:unaligned_bitstring/2` BIF. Using
that BIF, the example above can be rewritten like so:
make_unaligned_sub_binary(Bin) ->
erts_debug:unaligned_bitstring(Bin, 3).
---
erts/emulator/beam/beam_debug.c | 69 +++++++++++++++++++++++
erts/emulator/beam/bif.tab | 5 ++
erts/emulator/test/binary_SUITE.erl | 7 +--
erts/emulator/test/bs_match_bin_SUITE.erl | 7 +--
erts/emulator/test/bs_utf_SUITE.erl | 7 +--
erts/emulator/test/code_SUITE.erl | 7 +--
erts/emulator/test/hash_SUITE.erl | 22 ++------
erts/emulator/test/nif_SUITE.erl | 6 +-
erts/emulator/test/num_bif_SUITE.erl | 38 ++++++++++---
erts/emulator/test/process_SUITE.erl | 7 +--
lib/kernel/src/erts_debug.erl | 11 +++-
lib/stdlib/test/binary_module_SUITE.erl | 15 ++---
lib/stdlib/test/ets_SUITE.erl | 7 +--
lib/stdlib/test/unicode_SUITE.erl | 7 +--
14 files changed, 140 insertions(+), 75 deletions(-)
diff --git a/erts/emulator/beam/beam_debug.c b/erts/emulator/beam/beam_debug.c
index 520127d6b8..f4ae933adb 100644
--- a/erts/emulator/beam/beam_debug.c
+++ b/erts/emulator/beam/beam_debug.c
@@ -97,6 +97,75 @@ erts_debug_size_shared_1(BIF_ALIST_1)
}
}
+BIF_RETTYPE
+erts_debug_unaligned_bitstring_2(BIF_ALIST_2)
+{
+ Eterm bitstring;
+ Uint offset;
+
+ byte *source_bytes;
+ Uint source_offset;
+ Uint source_size;
+
+ byte *target_bytes;
+ Eterm target_size;
+
+ Eterm *hp;
+ Eterm refc_binary;
+ ErlSubBits *sb;
+
+ Uint inner_offset, inner_size;
+ Eterm br_flags;
+ BinRef *br;
+ const byte *base;
+
+ bitstring = BIF_ARG_1;
+ if (is_not_bitstring(bitstring)) {
+ BIF_ERROR(BIF_P, BADARG);
+ }
+
+ if (is_not_small(BIF_ARG_2)) {
+ BIF_ERROR(BIF_P, BADARG);
+ }
+ offset = unsigned_val(BIF_ARG_2);
+ if (!(0 < offset && offset < 8)) {
+ BIF_ERROR(BIF_P, BADARG);
+ }
+
+ ERTS_GET_BITSTRING(bitstring,
+ source_bytes,
+ source_offset,
+ source_size);
+
+ target_size = MAX(source_size + offset, ERL_ONHEAP_BITS_LIMIT + 1);
+ refc_binary = erts_new_bitstring(BIF_P, target_size, &target_bytes);
+
+ copy_binary_to_buffer(target_bytes, offset,
+ source_bytes, source_offset,
+ source_size);
+
+ hp = HAlloc(BIF_P, ERL_SUB_BITS_SIZE);
+ sb = (ErlSubBits*)hp;
+
+ ERTS_GET_BITSTRING_REF(refc_binary,
+ br_flags,
+ br,
+ base,
+ inner_offset,
+ inner_size);
+ (void)inner_offset;
+ (void)inner_size;
+
+ erl_sub_bits_init(sb,
+ br_flags,
+ ((Eterm)br) | br_flags,
+ base,
+ offset,
+ source_size);
+
+ BIF_RET(make_bitstring(sb));
+}
+
BIF_RETTYPE
erts_debug_copy_shared_2(BIF_ALIST_2)
{
diff --git a/erts/emulator/beam/bif.tab b/erts/emulator/beam/bif.tab
index 20c469620f..6575599d58 100644
--- a/erts/emulator/beam/bif.tab
+++ b/erts/emulator/beam/bif.tab
@@ -828,3 +828,8 @@ bif erl_debugger:stack_frames/2
bif erts_internal:system_monitor/1
bif erts_internal:system_monitor/3
bif erts_internal:processes_next/1
+
+#
+# New in 28.1.
+#
+bif erts_debug:unaligned_bitstring/2
diff --git a/erts/emulator/test/binary_SUITE.erl b/erts/emulator/test/binary_SUITE.erl
index e1514c2ba5..d7b61fa340 100644
--- a/erts/emulator/test/binary_SUITE.erl
+++ b/erts/emulator/test/binary_SUITE.erl
@@ -2207,11 +2207,8 @@ make_sub_binary(Bin) when is_binary(Bin) ->
make_sub_binary(List) ->
make_sub_binary(list_to_binary(List)).
-make_unaligned_sub_binary(Bin0) when is_binary(Bin0) ->
- Bin1 = <<0:3,Bin0/binary,31:5>>,
- Sz = size(Bin0),
- <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
- Bin;
+make_unaligned_sub_binary(Bin) when is_binary(Bin) ->
+ erts_debug:unaligned_bitstring(Bin, 3);
make_unaligned_sub_binary(List) ->
make_unaligned_sub_binary(list_to_binary(List)).
diff --git a/erts/emulator/test/bs_match_bin_SUITE.erl b/erts/emulator/test/bs_match_bin_SUITE.erl
index 2dd360feac..db5922445d 100644
--- a/erts/emulator/test/bs_match_bin_SUITE.erl
+++ b/erts/emulator/test/bs_match_bin_SUITE.erl
@@ -348,10 +348,7 @@ rand_seed() ->
io:format("\n*** rand:export_seed() = ~w\n\n", [rand:export_seed()]),
ok.
-make_unaligned_sub_binary(Bin0) ->
- Bin1 = <<0:3,Bin0/binary,31:5>>,
- Sz = size(Bin0),
- <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
- Bin.
+make_unaligned_sub_binary(Bin) ->
+ erts_debug:unaligned_bitstring(Bin, 3).
id(I) -> I.
diff --git a/erts/emulator/test/bs_utf_SUITE.erl b/erts/emulator/test/bs_utf_SUITE.erl
index d514ef7051..f3c30334ec 100644
--- a/erts/emulator/test/bs_utf_SUITE.erl
+++ b/erts/emulator/test/bs_utf_SUITE.erl
@@ -459,11 +459,8 @@ int_to_utf8(I, 4) ->
B1 = (I bsr 18),
<<1:1,1:1,1:1,1:1,0:1,B1:3,1:1,0:1,B2:6,1:1,0:1,B3:6,1:1,0:1,B4:6>>.
-make_unaligned(Bin0) when is_binary(Bin0) ->
- Bin1 = <<0:3,Bin0/binary,31:5>>,
- Sz = byte_size(Bin0),
- <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
- Bin.
+make_unaligned(Bin) ->
+ erts_debug:unaligned_bitstring(Bin, 3).
fail_check({'EXIT',{badarg,_}}, Str, Vars) ->
try evaluate(Str, Vars) of
diff --git a/erts/emulator/test/code_SUITE.erl b/erts/emulator/test/code_SUITE.erl
index 1a1a81288e..590673fe81 100644
--- a/erts/emulator/test/code_SUITE.erl
+++ b/erts/emulator/test/code_SUITE.erl
@@ -1278,11 +1278,8 @@ make_sub_binary(Bin) when is_binary(Bin) ->
make_sub_binary(List) ->
make_sub_binary(list_to_binary(List)).
-make_unaligned_sub_binary(Bin0) ->
- Bin1 = <<0:3,Bin0/binary,31:5>>,
- Sz = size(Bin0),
- <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
- Bin.
+make_unaligned_sub_binary(Bin) ->
+ erts_debug:unaligned_bitstring(Bin, 3).
%% Add 1 bit to the size of the binary.
bit_sized_binary(Bin0) ->
diff --git a/erts/emulator/test/hash_SUITE.erl b/erts/emulator/test/hash_SUITE.erl
index bfd05bcc9e..20c76954bc 100644
--- a/erts/emulator/test/hash_SUITE.erl
+++ b/erts/emulator/test/hash_SUITE.erl
@@ -1278,25 +1278,15 @@ get_map(Size) ->
%% Copied from binary_SUITE
-make_unaligned_sub_binary(Bin0) when is_binary(Bin0) ->
- Bin1 = <<0:3,Bin0/binary,31:5>>,
- Sz = size(Bin0),
- <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
- Bin.
+make_unaligned_sub_binary(Bin) when is_binary(Bin) ->
+ erts_debug:unaligned_bitstring(Bin, 3).
-%% This functions is written very carefully so that the bitstrings
-%% created are released as quickly as possible. If they are not released
-%% then the memory consumption going through the roof and systems will need
-%% lots of memory.
+%% This function is written very carefully so that the bitstrings
+%% created are released as quickly as possible. If they are not released,
+%% the memory consumption will go through the roof.
make_unaligned_sub_bitstring(Bin0) ->
- Sz = erlang:bit_size(Bin0),
- Bin1 = <<0:3,Bin0/bitstring,31:5>>,
- make_unaligned_sub_bitstring2(Sz, Bin1).
-
-make_unaligned_sub_bitstring2(Sz, Bin1) ->
- %% Make sure to release Bin0 if possible
+ Bin = erts_debug:unaligned_bitstring(Bin0, 3),
erlang:garbage_collect(),
- <<0:3,Bin:Sz/bitstring,31:5>> = id(Bin1),
Bin.
make_random_bin(Size) ->
diff --git a/erts/emulator/test/nif_SUITE.erl b/erts/emulator/test/nif_SUITE.erl
index cdbaf41a80..1722f4e7a4 100644
--- a/erts/emulator/test/nif_SUITE.erl
+++ b/erts/emulator/test/nif_SUITE.erl
@@ -4467,10 +4467,8 @@ nif_ioq_payload(refcbin) ->
nif_ioq_payload(Else) ->
Else.
-make_unaligned_binary(Bin0) ->
- Size = byte_size(Bin0),
- <<0:3,Bin:Size/binary,31:5>> = id(<<0:3,Bin0/binary,31:5>>),
- Bin.
+make_unaligned_binary(Bin) ->
+ erts_debug:unaligned_bitstring(Bin, 3).
pid(Config) ->
ensure_lib_loaded(Config),
diff --git a/erts/emulator/test/num_bif_SUITE.erl b/erts/emulator/test/num_bif_SUITE.erl
index 99c22ca692..f32583c58c 100644
--- a/erts/emulator/test/num_bif_SUITE.erl
+++ b/erts/emulator/test/num_bif_SUITE.erl
@@ -556,7 +556,7 @@ t_integer_to_string(Config) when is_list(Config) ->
%% Bignums.
BigBin = id(list_to_binary(lists:duplicate(2000, id($1)))),
- Big = erlang:binary_to_integer(BigBin),
+ Big = bin_to_int(BigBin),
BigBin = erlang:integer_to_binary(Big),
%% Invalid types
@@ -607,9 +607,9 @@ t_string_to_integer(Config) when is_list(Config) ->
_ = rand:uniform(), %Seed generator
io:format("Seed: ~p", [rand:export_seed()]),
- 0 = erlang:binary_to_integer(id(<<"00">>)),
- 0 = erlang:binary_to_integer(id(<<"-0">>)),
- 0 = erlang:binary_to_integer(id(<<"+0">>)),
+ 0 = bin_to_int(id(<<"00">>)),
+ 0 = bin_to_int(id(<<"-0">>)),
+ 0 = bin_to_int(id(<<"+0">>)),
test_sti(0),
test_sti(1),
@@ -636,12 +636,12 @@ t_string_to_integer(Config) when is_list(Config) ->
Str = <<"10">>,
UnalignStr = <<0:3, (id(Str))/binary, 0:5>>,
<<_:3, SomeStr:2/binary, _:5>> = id(UnalignStr),
- 10 = binary_to_integer(SomeStr),
+ 10 = bin_to_int(SomeStr),
%% Invalid types
lists:foreach(fun(Value) ->
{'EXIT', {badarg, _}} =
- (catch binary_to_integer(Value)),
+ (catch bin_to_int(Value)),
{'EXIT', {badarg, _}} =
(catch list_to_integer(Value))
end,[atom,1.2,0.0,[$1,[$2]]]),
@@ -649,7 +649,7 @@ t_string_to_integer(Config) when is_list(Config) ->
%% Default base error cases
lists:foreach(fun(Value) ->
{'EXIT', {badarg, _}} =
- (catch binary_to_integer(list_to_binary(Value))),
+ (catch bin_to_int(list_to_binary(Value))),
{'EXIT', {badarg, _}} =
(catch list_to_integer(Value))
end,["1.0"," 1"," -1","","+"]),
@@ -762,8 +762,8 @@ test_sti(Num, Base) ->
Base =:= 10 ->
Num = list_to_integer(NumList),
Neg = list_to_integer(NegNumList),
- Num = binary_to_integer(iolist_to_binary(NumList)),
- Neg = binary_to_integer(iolist_to_binary(NegNumList));
+ Num = bin_to_int(iolist_to_binary(NumList)),
+ Neg = bin_to_int(iolist_to_binary(NegNumList));
true ->
ok
end,
@@ -778,3 +778,23 @@ id(X) -> X.
%% Use the printing library to convert to list.
int2list(Int, Base) when is_integer(Base), 2 =< Base, Base =< 36 ->
lists:flatten(io_lib:format("~."++integer_to_list(Base)++"B",[Int])).
+
+bin_to_int(Bin) ->
+ Unaligned = erts_debug:unaligned_bitstring(Bin, 3),
+ try binary_to_integer(Bin) of
+ Int ->
+ Int = binary_to_integer(Unaligned),
+ Int
+ catch
+ C:E ->
+ try binary_to_integer(Unaligned) of
+ _ ->
+ exit(should_fail)
+ catch
+ OtherC:OtherE when C =/= OtherC; E =/= OtherE ->
+ exit(exceptions_different)
+ end
+ end.
+
+make_unaligned_sub_binary(Bin) ->
+ erts_debug:unaligned_bitstring(Bin, 3).
diff --git a/erts/emulator/test/process_SUITE.erl b/erts/emulator/test/process_SUITE.erl
index 8db932d288..cade3ee4c6 100644
--- a/erts/emulator/test/process_SUITE.erl
+++ b/erts/emulator/test/process_SUITE.erl
@@ -1942,11 +1942,8 @@ make_sub_binary(Bin) when is_binary(Bin) ->
make_sub_binary(List) ->
make_sub_binary(list_to_binary(List)).
-make_unaligned_sub_binary(Bin0) ->
- Bin1 = <<0:3,Bin0/binary,31:5>>,
- Sz = size(Bin0),
- <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
- Bin.
+make_unaligned_sub_binary(Bin) ->
+ erts_debug:unaligned_bitstring(Bin, 3).
%% Tests erlang:yield/1
yield(Config) when is_list(Config) ->
diff --git a/lib/kernel/src/erts_debug.erl b/lib/kernel/src/erts_debug.erl
index 0b37ba9cd0..27bc7594be 100644
--- a/lib/kernel/src/erts_debug.erl
+++ b/lib/kernel/src/erts_debug.erl
@@ -43,7 +43,8 @@
lcnt_control/1, lcnt_control/2, lcnt_collect/0, lcnt_clear/0,
lc_graph/0, lc_graph_to_dot/2,
lc_graph_merge/0, lc_graph_merge/1, lc_graph_merge/2,
- alloc_blocks_size/1]).
+ alloc_blocks_size/1,
+ unaligned_bitstring/2]).
%% Reroutes calls to the given MFA to error_handler:breakpoint/3
%%
@@ -232,6 +233,14 @@ dirty_io(_, _) ->
dirty(_, _, _) ->
erlang:nif_error(undef).
+-spec unaligned_bitstring(Bin0, Offset) -> Bin1 when
+ Bin0 :: bitstring(),
+ Offset :: 1..7,
+ Bin1 :: bitstring().
+
+unaligned_bitstring(_, _) ->
+ erlang:nif_error(undef).
+
%%% End of BIFs
%% size(Term)
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl
index 48a7b3115b..6689a93e37 100644
--- a/lib/stdlib/test/binary_module_SUITE.erl
+++ b/lib/stdlib/test/binary_module_SUITE.erl
@@ -1408,16 +1408,11 @@ mask_error({'EXIT',{Err,_}}) ->
mask_error(Else) ->
Else.
-make_unaligned(Bin0) when is_binary(Bin0) ->
- Bin1 = <<0:3,Bin0/binary,31:5>>,
- Sz = byte_size(Bin0),
- <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
- Bin.
-make_unaligned2(Bin0) when is_binary(Bin0) ->
- Bin1 = <<31:5,Bin0/binary,0:3>>,
- Sz = byte_size(Bin0),
- <<31:5,Bin:Sz/binary,0:3>> = id(Bin1),
- Bin.
+make_unaligned(Bin) when is_binary(Bin) ->
+ erts_debug:unaligned_bitstring(Bin, 3).
+
+make_unaligned2(Bin) when is_binary(Bin) ->
+ erts_debug:unaligned_bitstring(Bin, 5).
check_no_invalid_read_bug(Config) when is_list(Config) ->
check_no_invalid_read_bug(24);
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 42ca1b5135..c7f63b98df 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -10043,11 +10043,8 @@ make_sub_binary(Bin) when is_binary(Bin) ->
make_sub_binary(List) ->
make_sub_binary(list_to_binary(List)).
-make_unaligned_sub_binary(Bin0) when is_binary(Bin0) ->
- Bin1 = <<0:3,Bin0/binary,31:5>>,
- Sz = size(Bin0),
- <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
- Bin;
+make_unaligned_sub_binary(Bin) when is_binary(Bin) ->
+ erts_debug:unaligned_bitstring(Bin, 3);
make_unaligned_sub_binary(List) ->
make_unaligned_sub_binary(list_to_binary(List)).
diff --git a/lib/stdlib/test/unicode_SUITE.erl b/lib/stdlib/test/unicode_SUITE.erl
index b0d92b074b..e852b28f57 100644
--- a/lib/stdlib/test/unicode_SUITE.erl
+++ b/lib/stdlib/test/unicode_SUITE.erl
@@ -1406,11 +1406,8 @@ list_to_x_bsyntax({utf32,little},L,Enc) ->
list_to_utf32_little_bsyntax(L,Enc).
-make_unaligned(Bin0) when is_binary(Bin0) ->
- Bin1 = <<0:3,Bin0/binary,31:5>>,
- Sz = byte_size(Bin0),
- <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
- Bin.
+make_unaligned(Bin) when is_binary(Bin) ->
+ erts_debug:unaligned_bitstring(Bin, 3).
bin_is_7bit(_Config) ->
%% This BIF is undocumented, but the unicode module uses it to
--
2.43.0