Skip to content

Commit

Permalink
Merge pull request #9478 from frazze-jobb/frazze/erts/erl_re_bif_bina…
Browse files Browse the repository at this point in the history
…ry_offset_bug/GH-9438/OTP-19507

erts: fix sub binary bug in erl_bif_re
OTP-19507
  • Loading branch information
frazze-jobb authored Feb 26, 2025
2 parents d708174 + 31849d0 commit 0e7082b
Show file tree
Hide file tree
Showing 2 changed files with 44 additions and 2 deletions.
1 change: 1 addition & 0 deletions erts/emulator/beam/erl_bif_re.c
Original file line number Diff line number Diff line change
Expand Up @@ -629,6 +629,7 @@ static bool get_iolist_as_bytes(Eterm iolist,

ERTS_GET_BITSTRING(iolist, *bytes_p, bit_offs, bit_sz);
if (!BIT_OFFSET(bit_offs) && !TAIL_BITS(bit_sz)) {
*bytes_p += BYTE_OFFSET(bit_offs);
*slen_p = BYTE_SIZE(bit_sz);
*tmp_buf_p = NULL;
return true;
Expand Down
45 changes: 43 additions & 2 deletions lib/stdlib/test/re_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@
opt_no_start_optimize/1,opt_never_utf/1,opt_ucp/1,
match_limit/1,sub_binaries/1,copt/1,global_unicode_validation/1,
yield_on_subject_validation/1, bad_utf8_subject/1,
error_info/1]).
error_info/1, subject_is_sub_binary/1, pattern_is_sub_binary/1]).

-include_lib("common_test/include/ct.hrl").
-include_lib("kernel/include/file.hrl").
Expand All @@ -53,7 +53,7 @@ all() ->
inspect, opt_no_start_optimize,opt_never_utf,opt_ucp,
match_limit, sub_binaries, re_version, global_unicode_validation,
yield_on_subject_validation, bad_utf8_subject,
error_info].
error_info, subject_is_sub_binary, pattern_is_sub_binary].

groups() ->
[].
Expand Down Expand Up @@ -1115,3 +1115,44 @@ error_info(_Config) ->
{urun, 3} %Internal.
],
error_info_lib:test_error_info(re, L).

pattern_is_sub_binary(Config) when is_list(Config) ->
%% Aligned sub binary - will not copy the binary
Bin = <<"pattern = ^((:|(0?|([1-9a-f][0-9a-f]{0,3}))):)((0?|([1-9a-f][0-9a-f]{0,3})):){0,6}(:|(0?|([1-9a-f][0-9a-f]{0,3})))$">>,
Subject = <<"::1">>,
{_,RE} = split_binary(Bin, 10),
{ok,REC} = re:compile(RE),
match = re:run(Subject, REC, [{capture, none}]),
match = re:run(Subject, RE, [{capture, none}]),
nomatch = re:run(Subject, Bin, [{capture, none}]),
%% Unaligned sub binary - will result in a copy operation
<<0:1, RE2/binary>> = Bin2 = <<0:1, "^((:|(0?|([1-9a-f][0-9a-f]{0,3}))):)((0?|([1-9a-f][0-9a-f]{0,3})):){0,6}(:|(0?|([1-9a-f][0-9a-f]{0,3})))$">>,
{ok,REC2} = re:compile(RE2),
match = re:run(Subject, REC2, [{capture, none}]),
match = re:run(Subject, RE2, [{capture, none}]),
ok = try
_ = re:run(Subject, Bin2, [{capture, none}])
catch error:badarg ->
%% *** argument 2: neither an iodata term nor a compiled regular expression
ok
end.

subject_is_sub_binary(Config) when is_list(Config) ->
%% Aligned subject sub binary
Bin = <<"subject = ::1">>,
RE = <<"^((:|(0?|([1-9a-f][0-9a-f]{0,3}))):)((0?|([1-9a-f][0-9a-f]{0,3})):){0,6}(:|(0?|([1-9a-f][0-9a-f]{0,3})))$">>,
{_,Subject} = split_binary(Bin, 10),
{ok,REC} = re:compile(RE),
match = re:run(Subject, REC, [{capture, none}]),
match = re:run(Subject, RE, [{capture, none}]),
nomatch = re:run(Bin, RE, [{capture, none}]),
%% Unaligned subject sub binary
<<0:1, Subject2/binary>> = Bin2 = <<0:1,"::1">>,
match = re:run(Subject2, REC, [{capture, none}]),
match = re:run(Subject2, RE, [{capture, none}]),
ok = try
_ = re:run(Bin2, RE, [{capture, none}])
catch error:badarg ->
%% *** argument 1: not an iodata term
ok
end.

0 comments on commit 0e7082b

Please sign in to comment.