Skip to content

Commit 757e922

Browse files
committed
erts: Check process registers during CLA check
1 parent 0418c10 commit 757e922

File tree

2 files changed

+73
-8
lines changed

2 files changed

+73
-8
lines changed

Diff for: erts/emulator/beam/beam_bif_load.c

+18-1
Original file line numberDiff line numberDiff line change
@@ -1092,7 +1092,24 @@ erts_check_copy_literals_gc_need(Process *c_p, int *redsp,
10921092
goto done;
10931093
}
10941094
}
1095-
1095+
1096+
/* Check if there are any *direct* references to literals in the process'
1097+
* registers.
1098+
*
1099+
* These are not guaranteed to be kept up to date, but as we can only land
1100+
* here during signal handling we KNOW that these are either up to date, or
1101+
* they are not actually live (effective arity is 0 in a `receive`). Should
1102+
* any of these registers contain garbage, we merely risk scheduling a
1103+
* pointless garbage collection as `any_heap_ref_ptrs` doesn't follow
1104+
* pointers, it just range-checks them. */
1105+
scanned += c_p->arity;
1106+
if (any_heap_ref_ptrs(&c_p->arg_reg[0],
1107+
&c_p->arg_reg[c_p->arity],
1108+
literals,
1109+
lit_bsize)) {
1110+
goto done;
1111+
}
1112+
10961113
res = 0; /* no need for gc */
10971114

10981115
done: {

Diff for: erts/emulator/test/signal_SUITE.erl

+55-7
Original file line numberDiff line numberDiff line change
@@ -57,12 +57,13 @@
5757
copy_literal_area_signal_recv/1,
5858
copy_literal_area_signal_exit/1,
5959
copy_literal_area_signal_recv_exit/1,
60+
copy_literal_area_signal_registers/1,
6061
simultaneous_signals_basic/1,
6162
simultaneous_signals_recv/1,
6263
simultaneous_signals_exit/1,
6364
simultaneous_signals_recv_exit/1]).
6465

65-
-export([spawn_spammers/3]).
66+
-export([check_literal_conversion/1, spawn_spammers/3]).
6667

6768
init_per_testcase(Func, Config) when is_atom(Func), is_list(Config) ->
6869
[{testcase, Func}|Config].
@@ -107,6 +108,7 @@ groups() ->
107108
copy_literal_area_signal_recv,
108109
copy_literal_area_signal_exit,
109110
copy_literal_area_signal_recv_exit,
111+
copy_literal_area_signal_registers,
110112
simultaneous_signals_basic,
111113
simultaneous_signals_recv,
112114
simultaneous_signals_exit,
@@ -945,6 +947,48 @@ copy_literal_area_signal_exit(Config) when is_list(Config) ->
945947
copy_literal_area_signal_recv_exit(Config) when is_list(Config) ->
946948
copy_literal_area_signal_test(true, true).
947949

950+
%% Tests the case where the literal is only present in the process' saved
951+
%% registers. This is easy to provoke with hibernation, but can also occur
952+
%% if a process happens to be scheduled out on e.g. a function call with a
953+
%% literal argument just as it's being purged.
954+
copy_literal_area_signal_registers(Config) when is_list(Config) ->
955+
persistent_term:put({?MODULE, ?FUNCTION_NAME}, [make_ref()]),
956+
LiteralArgs = persistent_term:get({?MODULE, ?FUNCTION_NAME}),
957+
true = is_list(LiteralArgs),
958+
0 = erts_debug:size_shared(LiteralArgs), %% Should be a literal...
959+
960+
Self = self(),
961+
962+
{Pid, Monitor} =
963+
spawn_monitor(fun() ->
964+
Self ! {sync, LiteralArgs},
965+
erlang:hibernate(?MODULE,
966+
check_literal_conversion,
967+
LiteralArgs)
968+
end),
969+
970+
receive
971+
{sync, LiteralArgs} ->
972+
receive after 500 ->
973+
{current_function,{erlang,hibernate,3}} =
974+
process_info(Pid, current_function)
975+
end
976+
end,
977+
978+
persistent_term:erase({?MODULE, ?FUNCTION_NAME}),
979+
receive after 1 -> ok end,
980+
981+
literal_area_collector_test:check_idle(),
982+
983+
false = (0 =:= erts_debug:size_shared(LiteralArgs)),
984+
Pid ! check_literal_conversion,
985+
986+
receive
987+
{'DOWN', Monitor, process, Pid, R} ->
988+
normal = R,
989+
ok
990+
end.
991+
948992
copy_literal_area_signal_test(RecvPair, Exit) ->
949993
persistent_term:put({?MODULE, ?FUNCTION_NAME}, make_ref()),
950994
Literal = persistent_term:get({?MODULE, ?FUNCTION_NAME}),
@@ -958,12 +1002,7 @@ copy_literal_area_signal_test(RecvPair, Exit) ->
9581002
true ->
9591003
ok
9601004
end,
961-
receive check_literal_conversion -> ok end,
962-
receive
963-
Literal ->
964-
%% Should not be a literal anymore...
965-
false = (0 == erts_debug:size_shared(Literal))
966-
end
1005+
check_literal_conversion(Literal)
9671006
end,
9681007
PMs = lists:map(fun (_) ->
9691008
spawn_opt(ProcF, [link, monitor])
@@ -1014,6 +1053,15 @@ copy_literal_area_signal_test(RecvPair, Exit) ->
10141053
end, PMs),
10151054
ok.
10161055

1056+
%% Exported for optional use with hibernate/3
1057+
check_literal_conversion(Literal) ->
1058+
receive
1059+
check_literal_conversion ->
1060+
%% Should not be a literal anymore...
1061+
false = (0 == erts_debug:size_shared(Literal)),
1062+
ok
1063+
end.
1064+
10171065
simultaneous_signals_basic(Config) when is_list(Config) ->
10181066
simultaneous_signals_test(false, false).
10191067

0 commit comments

Comments
 (0)