Skip to content

Commit

Permalink
Merge pull request #7915 from rickard-green/rickard/frag-unaliased-le…
Browse files Browse the repository at this point in the history
…ak/OTP-18885

Fix memory leak and crash due to fragmented message to unaliased process
  • Loading branch information
rickard-green committed Dec 5, 2023
2 parents 82424cc + ceb208a commit cf4f6e1
Show file tree
Hide file tree
Showing 3 changed files with 93 additions and 12 deletions.
3 changes: 2 additions & 1 deletion erts/emulator/beam/dist.c
Original file line number Diff line number Diff line change
Expand Up @@ -2587,11 +2587,12 @@ int erts_net_message(Port *prt,
if (!is_external_pid(watcher))
goto invalid_message;
if (erts_this_dist_entry == external_pid_dist_entry(watcher))
break;
goto monitored_process_not_alive;
goto invalid_message;
}

if (!erts_proc_lookup(watcher)) {
monitored_process_not_alive:
if (ede_hfrag != NULL) {
erts_free_dist_ext_copy(erts_get_dist_ext(ede_hfrag));
free_message_buffer(ede_hfrag);
Expand Down
18 changes: 9 additions & 9 deletions erts/emulator/beam/erl_proc_sig_queue.c
Original file line number Diff line number Diff line change
Expand Up @@ -2075,8 +2075,14 @@ erts_proc_sig_send_dist_to_alias(Eterm from, Eterm alias,

ASSERT(is_ref(alias));
pid = erts_get_pid_of_ref(alias);
if (!is_internal_pid(pid))
if (!is_internal_pid(pid)) {
if (hfrag) {
/* Fragmented message... */
erts_free_dist_ext_copy(erts_get_dist_ext(hfrag));
free_message_buffer(hfrag);
}
return;
}

/*
* The receiver can distinguish between these two scenarios by
Expand Down Expand Up @@ -5600,8 +5606,6 @@ handle_alias_message(Process *c_p, ErtsMessage *sig, ErtsMessage ***next_nm_sig)
ASSERT(is_internal_pid(from) || is_atom(from));
ASSERT(is_internal_pid_ref(alias));

ERL_MESSAGE_FROM(sig) = from;

mon = erts_monitor_tree_lookup(ERTS_P_MONITORS(c_p), alias);
flags = mon ? mon->flags : (Uint16) 0;
if (!(flags & ERTS_ML_STATE_ALIAS_MASK)
Expand All @@ -5611,17 +5615,13 @@ handle_alias_message(Process *c_p, ErtsMessage *sig, ErtsMessage ***next_nm_sig)
* drop message...
*/
remove_nm_sig(c_p, sig, next_nm_sig);
/* restored as message... */
ERL_MESSAGE_TERM(sig) = msg;
if (type == ERTS_SIG_Q_TYPE_DIST)
sig->data.heap_frag = &sig->hfrag;
else
sig->data.attached = data_attached;
sig->next = NULL;;
erts_cleanup_messages(sig);
return 2;
}

ERL_MESSAGE_FROM(sig) = from;

if ((flags & ERTS_ML_STATE_ALIAS_MASK) == ERTS_ML_STATE_ALIAS_ONCE) {
mon->flags &= ~ERTS_ML_STATE_ALIAS_MASK;

Expand Down
84 changes: 82 additions & 2 deletions erts/emulator/test/process_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,8 @@
spawn_request_reply_option/1,
dist_spawn_arg_list_mixup/1,
alias_bif/1,
dist_frag_alias/1,
dist_frag_unaliased/1,
monitor_alias/1,
spawn_monitor_alias/1,
demonitor_aliasmonitor/1,
Expand Down Expand Up @@ -193,7 +195,8 @@ groups() ->
otp_16436, otp_16642]},
{alias, [],
[alias_bif, monitor_alias, spawn_monitor_alias,
demonitor_aliasmonitor, down_aliasmonitor]}].
demonitor_aliasmonitor, down_aliasmonitor,
dist_frag_alias, dist_frag_unaliased]}].

init_per_suite(Config) ->
A0 = case application:start(sasl) of
Expand Down Expand Up @@ -5080,7 +5083,84 @@ alias_bif_test(Node) ->
end),
[{A3,1},{'DOWN', M3, _, _, _}] = recv_msgs(2),
ok.


dist_frag_alias(Config) when is_list(Config) ->
Tester = self(),
{ok, Peer, Node} = ?CT_PEER(),
{P,M} = spawn_monitor(Node,
fun () ->
Alias = alias(),
Tester ! {alias, Alias},
receive
{data, Data} ->
garbage_collect(),
Tester ! {received_data, Data}
end,
exit(end_of_test)
end),
Data = term_to_binary(lists:seq(1, 1000000)),
receive
{alias, Alias} ->
Alias ! {data, Data},
receive
{received_data, RecvData} ->
Data = RecvData;
{'DOWN', M, process, P, R2} ->
ct:fail(R2)
end;
{'DOWN', M, process, P, R1} ->
ct:fail(R1)
end,
receive
{'DOWN', M, process, P, R3} ->
end_of_test = R3
end,
peer:stop(Peer),
ok.

dist_frag_unaliased(Config) when is_list(Config) ->
%% Leak fixed by PR-7915 would have been detected using asan or valgrind
%% when running this test...
Tester = self(),
{ok, Peer, Node} = ?CT_PEER(),
{P,M} = spawn_monitor(Node,
fun () ->
Alias = alias(),
Tester ! {alias, Alias},
receive
{data, Data} ->
garbage_collect(),
unalias(Alias),
Tester ! {received_data, Data},
receive
{data, _Data} ->
exit(received_data_again);
end_of_test ->
exit(end_of_test)
end
end
end),
Data = term_to_binary(lists:seq(1, 1000000)),
receive
{alias, Alias} ->
Alias ! {data, Data},
receive
{received_data, RecvData} ->
Data = RecvData;
{'DOWN', M, process, P, R2} ->
ct:fail(R2)
end,
Alias ! {data, Data},
P ! end_of_test;
{'DOWN', M, process, P, R1} ->
ct:fail(R1)
end,
receive
{'DOWN', M, process, P, R3} ->
end_of_test = R3
end,
peer:stop(Peer),
ok.

monitor_alias(Config) when is_list(Config) ->
monitor_alias_test(node()),
Expand Down

0 comments on commit cf4f6e1

Please sign in to comment.