Skip to content

Commit 419356c

Browse files
committed
[erts] Ensure cleanup of alias table on alias destruction
1 parent fe02a02 commit 419356c

File tree

5 files changed

+90
-2
lines changed

5 files changed

+90
-2
lines changed

erts/emulator/beam/erl_bif_info.c

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4149,6 +4149,16 @@ BIF_RETTYPE erts_debug_get_internal_state_1(BIF_ALIST_1)
41494149
else if (ERTS_IS_ATOM_STR("persistent_term", BIF_ARG_1)) {
41504150
BIF_RET(erts_debug_persistent_term_xtra_info(BIF_P));
41514151
}
4152+
else if (ERTS_IS_ATOM_STR("pid_ref_table_size", BIF_ARG_1)) {
4153+
Uint size = erts_pid_ref_table_size();
4154+
if (IS_SSMALL(size))
4155+
BIF_RET(make_small(size));
4156+
else {
4157+
Uint hsz = BIG_UWORD_HEAP_SIZE(size);
4158+
Eterm *hp = HAlloc(BIF_P, hsz);
4159+
BIF_RET(uword_to_big(size, hp));
4160+
}
4161+
}
41524162
}
41534163
else if (is_tuple(BIF_ARG_1)) {
41544164
Eterm* tp = tuple_val(BIF_ARG_1);

erts/emulator/beam/erl_bif_unique.c

Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -701,6 +701,27 @@ init_pid_ref_tables(void)
701701
}
702702
}
703703

704+
705+
Uint
706+
erts_pid_ref_table_size(void)
707+
{
708+
int i;
709+
Uint sz = 0;
710+
711+
for (i = 0; i <= erts_no_schedulers; i++) {
712+
HashInfo hi;
713+
ErtsPidRefTable *tblp = &pid_ref_table[i].u.table;
714+
erts_rwmtx_rlock(&tblp->rwmtx);
715+
hash_get_info(&hi, &tblp->hash);
716+
erts_rwmtx_runlock(&tblp->rwmtx);
717+
sz += (Uint) hi.objs;
718+
}
719+
720+
return sz;
721+
}
722+
723+
724+
704725
/* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *\
705726
* Unique Integer *
706727
\* */

erts/emulator/beam/erl_bif_unique.h

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ void erts_magic_ref_save_bin__(Eterm ref);
4242
ErtsMagicBinary *erts_magic_ref_lookup_bin__(Uint32 refn[ERTS_REF_NUMBERS]);
4343
void erts_pid_ref_delete(Eterm ref);
4444
Eterm erts_pid_ref_lookup__(Uint32 refn[ERTS_REF_NUMBERS]);
45-
45+
Uint erts_pid_ref_table_size(void);
4646

4747
/* strict monotonic counter */
4848

erts/emulator/beam/erl_monitor_link.c

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1094,6 +1094,16 @@ erts_monitor_destroy__(ErtsMonitorData *mdp)
10941094
|| ((mdp->origin.flags & ERTS_ML_FLGS_SAME)
10951095
== (mdp->u.target.flags & ERTS_ML_FLGS_SAME)));
10961096

1097+
if (mdp->origin.flags & ERTS_ML_STATE_ALIAS_MASK) {
1098+
ASSERT(mdp->origin.type == ERTS_MON_TYPE_ALIAS
1099+
|| mdp->origin.type == ERTS_MON_TYPE_PROC
1100+
|| mdp->origin.type == ERTS_MON_TYPE_PORT
1101+
|| mdp->origin.type == ERTS_MON_TYPE_TIME_OFFSET
1102+
|| mdp->origin.type == ERTS_MON_TYPE_DIST_PROC
1103+
|| mdp->origin.type == ERTS_MON_TYPE_DIST_PORT);
1104+
erts_pid_ref_delete(mdp->ref);
1105+
}
1106+
10971107
switch (mdp->origin.type) {
10981108
case ERTS_MON_TYPE_ALIAS:
10991109
ERTS_ML_ASSERT(!(mdp->origin.flags & ERTS_ML_FLG_TAG));

erts/emulator/test/process_SUITE.erl

Lines changed: 48 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -81,6 +81,7 @@
8181
alias_bif/1,
8282
monitor_alias/1,
8383
spawn_monitor_alias/1,
84+
alias_process_exit/1,
8485
monitor_tag/1]).
8586

8687
-export([prio_server/2, prio_client/2, init/1, handle_event/2]).
@@ -149,7 +150,7 @@ groups() ->
149150
gc_request_when_gc_disabled, gc_request_blast_when_gc_disabled,
150151
otp_16436, otp_16642]},
151152
{alias, [],
152-
[alias_bif, monitor_alias, spawn_monitor_alias]}].
153+
[alias_bif, monitor_alias, spawn_monitor_alias, alias_process_exit]}].
153154

154155
init_per_suite(Config) ->
155156
A0 = case application:start(sasl) of
@@ -168,9 +169,15 @@ end_per_suite(Config) ->
168169
catch erts_debug:set_internal_state(available_internal_state, false),
169170
Config.
170171

172+
init_per_group(alias, Config) ->
173+
erts_debug:set_internal_state(available_internal_state, true),
174+
Config;
171175
init_per_group(_GroupName, Config) ->
172176
Config.
173177

178+
end_per_group(alias, Config) ->
179+
erts_debug:set_internal_state(available_internal_state, false),
180+
Config;
174181
end_per_group(_GroupName, Config) ->
175182
Config.
176183

@@ -4032,11 +4039,25 @@ otp_16642(Config) when is_list(Config) ->
40324039
false = is_process_alive(Pid),
40334040
ok.
40344041

4042+
pid_ref_table_size() ->
4043+
erts_debug:get_internal_state(pid_ref_table_size).
4044+
4045+
check_pid_ref_table_size(PRTSz) ->
4046+
receive after 500 -> ok end,
4047+
case pid_ref_table_size() of
4048+
PRTSz ->
4049+
ok;
4050+
NewPRTSz ->
4051+
ct:fail({port_ref_table_size_mismatch, PRTSz, NewPRTSz})
4052+
end.
4053+
40354054
alias_bif(Config) when is_list(Config) ->
4055+
PRTSz = pid_ref_table_size(),
40364056
alias_bif_test(node()),
40374057
{ok, Node} = start_node(Config),
40384058
alias_bif_test(Node),
40394059
stop_node(Node),
4060+
check_pid_ref_table_size(PRTSz),
40404061
ok.
40414062

40424063
alias_bif_test(Node) ->
@@ -4081,10 +4102,12 @@ alias_bif_test(Node) ->
40814102

40824103

40834104
monitor_alias(Config) when is_list(Config) ->
4105+
PRTSz = pid_ref_table_size(),
40844106
monitor_alias_test(node()),
40854107
{ok, Node} = start_node(Config),
40864108
monitor_alias_test(Node),
40874109
stop_node(Node),
4110+
check_pid_ref_table_size(PRTSz),
40884111
ok.
40894112

40904113
monitor_alias_test(Node) ->
@@ -4168,6 +4191,7 @@ monitor_alias_test(Node) ->
41684191
spawn_monitor_alias(Config) when is_list(Config) ->
41694192
%% Exit signals with immediate exit reasons are sent
41704193
%% in a different manner than compound exit reasons.
4194+
PRTSz = pid_ref_table_size(),
41714195
spawn_monitor_alias_test(node(), spawn_opt, normal),
41724196
spawn_monitor_alias_test(node(), spawn_opt, make_ref()),
41734197
spawn_monitor_alias_test(node(), spawn_request, normal),
@@ -4180,6 +4204,7 @@ spawn_monitor_alias(Config) when is_list(Config) ->
41804204
spawn_monitor_alias_test(Node3, spawn_request, normal),
41814205
{ok, Node4} = start_node(Config),
41824206
spawn_monitor_alias_test(Node4, spawn_request, make_ref()),
4207+
check_pid_ref_table_size(PRTSz),
41834208
ok.
41844209

41854210
spawn_monitor_alias_test(Node, SpawnType, ExitReason) ->
@@ -4320,6 +4345,28 @@ spawn_monitor_alias_test(Node, SpawnType, ExitReason) ->
43204345
ok
43214346
end.
43224347

4348+
alias_process_exit(Config) when is_list(Config) ->
4349+
Tester = self(),
4350+
CreatedAliases = make_ref(),
4351+
PRTSz = pid_ref_table_size(),
4352+
P = spawn_link(fun () ->
4353+
A0 = alias([explicit_unalias]),
4354+
A1 = alias([reply]),
4355+
A2 = monitor(process, Tester, [{alias, explicit_unalias}]),
4356+
A3 = monitor(process, Tester, [{alias, demonitor}]),
4357+
A4 = monitor(process, Tester, [{alias, reply_demonitor}]),
4358+
Tester ! CreatedAliases,
4359+
receive after infinity -> ok end,
4360+
some_module:some_function([A0, A1, A2, A3, A4])
4361+
end),
4362+
receive CreatedAliases -> ok end,
4363+
PRTSz = erts_debug:get_internal_state(pid_ref_table_size) - 5,
4364+
unlink(P),
4365+
exit(P, kill),
4366+
false = is_process_alive(P),
4367+
check_pid_ref_table_size(PRTSz),
4368+
ok.
4369+
43234370
monitor_tag(Config) when is_list(Config) ->
43244371
%% Exit signals with immediate exit reasons are sent
43254372
%% in a different manner than compound exit reasons, and

0 commit comments

Comments
 (0)