Skip to content

Commit 3b4916c

Browse files
author
Erlang/OTP
committed
Merge branch 'john/erts/fix-cla-check-proc-registers/OTP-19599' into maint-27
* john/erts/fix-cla-check-proc-registers/OTP-19599: erts: Check process registers during CLA check
2 parents cdd2fce + 757e922 commit 3b4916c

File tree

2 files changed

+73
-8
lines changed

2 files changed

+73
-8
lines changed

erts/emulator/beam/beam_bif_load.c

Lines changed: 18 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1082,7 +1082,24 @@ erts_check_copy_literals_gc_need(Process *c_p, int *redsp,
10821082
goto done;
10831083
}
10841084
}
1085-
1085+
1086+
/* Check if there are any *direct* references to literals in the process'
1087+
* registers.
1088+
*
1089+
* These are not guaranteed to be kept up to date, but as we can only land
1090+
* here during signal handling we KNOW that these are either up to date, or
1091+
* they are not actually live (effective arity is 0 in a `receive`). Should
1092+
* any of these registers contain garbage, we merely risk scheduling a
1093+
* pointless garbage collection as `any_heap_ref_ptrs` doesn't follow
1094+
* pointers, it just range-checks them. */
1095+
scanned += c_p->arity;
1096+
if (any_heap_ref_ptrs(&c_p->arg_reg[0],
1097+
&c_p->arg_reg[c_p->arity],
1098+
literals,
1099+
lit_bsize)) {
1100+
goto done;
1101+
}
1102+
10861103
res = 0; /* no need for gc */
10871104

10881105
done: {

erts/emulator/test/signal_SUITE.erl

Lines changed: 55 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -59,6 +59,7 @@
5959
copy_literal_area_signal_recv/1,
6060
copy_literal_area_signal_exit/1,
6161
copy_literal_area_signal_recv_exit/1,
62+
copy_literal_area_signal_registers/1,
6263
simultaneous_signals_basic/1,
6364
simultaneous_signals_recv/1,
6465
simultaneous_signals_exit/1,
@@ -67,7 +68,7 @@
6768
parallel_signal_enqueue_race_2/1,
6869
dirty_schedule/1]).
6970

70-
-export([spawn_spammers/3]).
71+
-export([check_literal_conversion/1, spawn_spammers/3]).
7172

7273
init_per_testcase(Func, Config) when is_atom(Func), is_list(Config) ->
7374
[{testcase, Func}|Config].
@@ -120,6 +121,7 @@ groups() ->
120121
copy_literal_area_signal_recv,
121122
copy_literal_area_signal_exit,
122123
copy_literal_area_signal_recv_exit,
124+
copy_literal_area_signal_registers,
123125
simultaneous_signals_basic,
124126
simultaneous_signals_recv,
125127
simultaneous_signals_exit,
@@ -1067,6 +1069,48 @@ copy_literal_area_signal_exit(Config) when is_list(Config) ->
10671069
copy_literal_area_signal_recv_exit(Config) when is_list(Config) ->
10681070
copy_literal_area_signal_test(true, true).
10691071

1072+
%% Tests the case where the literal is only present in the process' saved
1073+
%% registers. This is easy to provoke with hibernation, but can also occur
1074+
%% if a process happens to be scheduled out on e.g. a function call with a
1075+
%% literal argument just as it's being purged.
1076+
copy_literal_area_signal_registers(Config) when is_list(Config) ->
1077+
persistent_term:put({?MODULE, ?FUNCTION_NAME}, [make_ref()]),
1078+
LiteralArgs = persistent_term:get({?MODULE, ?FUNCTION_NAME}),
1079+
true = is_list(LiteralArgs),
1080+
0 = erts_debug:size_shared(LiteralArgs), %% Should be a literal...
1081+
1082+
Self = self(),
1083+
1084+
{Pid, Monitor} =
1085+
spawn_monitor(fun() ->
1086+
Self ! {sync, LiteralArgs},
1087+
erlang:hibernate(?MODULE,
1088+
check_literal_conversion,
1089+
LiteralArgs)
1090+
end),
1091+
1092+
receive
1093+
{sync, LiteralArgs} ->
1094+
receive after 500 ->
1095+
{current_function,{erlang,hibernate,3}} =
1096+
process_info(Pid, current_function)
1097+
end
1098+
end,
1099+
1100+
persistent_term:erase({?MODULE, ?FUNCTION_NAME}),
1101+
receive after 1 -> ok end,
1102+
1103+
literal_area_collector_test:check_idle(),
1104+
1105+
false = (0 =:= erts_debug:size_shared(LiteralArgs)),
1106+
Pid ! check_literal_conversion,
1107+
1108+
receive
1109+
{'DOWN', Monitor, process, Pid, R} ->
1110+
normal = R,
1111+
ok
1112+
end.
1113+
10701114
copy_literal_area_signal_test(RecvPair, Exit) ->
10711115
persistent_term:put({?MODULE, ?FUNCTION_NAME}, make_ref()),
10721116
Literal = persistent_term:get({?MODULE, ?FUNCTION_NAME}),
@@ -1080,12 +1124,7 @@ copy_literal_area_signal_test(RecvPair, Exit) ->
10801124
true ->
10811125
ok
10821126
end,
1083-
receive check_literal_conversion -> ok end,
1084-
receive
1085-
Literal ->
1086-
%% Should not be a literal anymore...
1087-
false = (0 == erts_debug:size_shared(Literal))
1088-
end
1127+
check_literal_conversion(Literal)
10891128
end,
10901129
PMs = lists:map(fun (_) ->
10911130
spawn_opt(ProcF, [link, monitor])
@@ -1136,6 +1175,15 @@ copy_literal_area_signal_test(RecvPair, Exit) ->
11361175
end, PMs),
11371176
ok.
11381177

1178+
%% Exported for optional use with hibernate/3
1179+
check_literal_conversion(Literal) ->
1180+
receive
1181+
check_literal_conversion ->
1182+
%% Should not be a literal anymore...
1183+
false = (0 == erts_debug:size_shared(Literal)),
1184+
ok
1185+
end.
1186+
11391187
simultaneous_signals_basic(Config) when is_list(Config) ->
11401188
simultaneous_signals_test(false, false).
11411189

0 commit comments

Comments
 (0)