Skip to content

Commit eb92447

Browse files
committed
Merge branch 'rickard/alias-cleanup-fix/24.3/GH-6947/OTP-18496' into rickard/alias-cleanup-fix/25.2.3/GH-6947/OTP-18496
* rickard/alias-cleanup-fix/24.3/GH-6947/OTP-18496: [erts] Ensure cleanup of alias table on alias destruction
2 parents 07cf1c5 + 419356c commit eb92447

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
@@ -4266,6 +4266,16 @@ BIF_RETTYPE erts_debug_get_internal_state_1(BIF_ALIST_1)
42664266
BIF_RET(am_ok);
42674267
}
42684268
#endif
4269+
else if (ERTS_IS_ATOM_STR("pid_ref_table_size", BIF_ARG_1)) {
4270+
Uint size = erts_pid_ref_table_size();
4271+
if (IS_SSMALL(size))
4272+
BIF_RET(make_small(size));
4273+
else {
4274+
Uint hsz = BIG_UWORD_HEAP_SIZE(size);
4275+
Eterm *hp = HAlloc(BIF_P, hsz);
4276+
BIF_RET(uword_to_big(size, hp));
4277+
}
4278+
}
42694279
}
42704280
else if (is_tuple(BIF_ARG_1)) {
42714281
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
@@ -1095,6 +1095,16 @@ erts_monitor_destroy__(ErtsMonitorData *mdp)
10951095
|| ((mdp->origin.flags & ERTS_ML_FLGS_SAME)
10961096
== (mdp->u.target.flags & ERTS_ML_FLGS_SAME)));
10971097

1098+
if (mdp->origin.flags & ERTS_ML_STATE_ALIAS_MASK) {
1099+
ASSERT(mdp->origin.type == ERTS_MON_TYPE_ALIAS
1100+
|| mdp->origin.type == ERTS_MON_TYPE_PROC
1101+
|| mdp->origin.type == ERTS_MON_TYPE_PORT
1102+
|| mdp->origin.type == ERTS_MON_TYPE_TIME_OFFSET
1103+
|| mdp->origin.type == ERTS_MON_TYPE_DIST_PROC
1104+
|| mdp->origin.type == ERTS_MON_TYPE_DIST_PORT);
1105+
erts_pid_ref_delete(mdp->ref);
1106+
}
1107+
10981108
switch (mdp->origin.type) {
10991109
case ERTS_MON_TYPE_ALIAS:
11001110
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
@@ -94,6 +94,7 @@
9494
alias_bif/1,
9595
monitor_alias/1,
9696
spawn_monitor_alias/1,
97+
alias_process_exit/1,
9798
monitor_tag/1]).
9899

99100
-export([prio_server/2, prio_client/2, init/1, handle_event/2]).
@@ -180,7 +181,7 @@ groups() ->
180181
gc_request_when_gc_disabled, gc_request_blast_when_gc_disabled,
181182
otp_16436, otp_16642]},
182183
{alias, [],
183-
[alias_bif, monitor_alias, spawn_monitor_alias]}].
184+
[alias_bif, monitor_alias, spawn_monitor_alias, alias_process_exit]}].
184185

185186
init_per_suite(Config) ->
186187
A0 = case application:start(sasl) of
@@ -199,9 +200,15 @@ end_per_suite(Config) ->
199200
catch erts_debug:set_internal_state(available_internal_state, false),
200201
Config.
201202

203+
init_per_group(alias, Config) ->
204+
erts_debug:set_internal_state(available_internal_state, true),
205+
Config;
202206
init_per_group(_GroupName, Config) ->
203207
Config.
204208

209+
end_per_group(alias, Config) ->
210+
erts_debug:set_internal_state(available_internal_state, false),
211+
Config;
205212
end_per_group(_GroupName, Config) ->
206213
Config.
207214

@@ -4575,11 +4582,25 @@ otp_16642(Config) when is_list(Config) ->
45754582
false = is_process_alive(Pid),
45764583
ok.
45774584

4585+
pid_ref_table_size() ->
4586+
erts_debug:get_internal_state(pid_ref_table_size).
4587+
4588+
check_pid_ref_table_size(PRTSz) ->
4589+
receive after 500 -> ok end,
4590+
case pid_ref_table_size() of
4591+
PRTSz ->
4592+
ok;
4593+
NewPRTSz ->
4594+
ct:fail({port_ref_table_size_mismatch, PRTSz, NewPRTSz})
4595+
end.
4596+
45784597
alias_bif(Config) when is_list(Config) ->
4598+
PRTSz = pid_ref_table_size(),
45794599
alias_bif_test(node()),
45804600
{ok, Peer, Node} = ?CT_PEER(),
45814601
alias_bif_test(Node),
45824602
stop_node(Peer, Node),
4603+
check_pid_ref_table_size(PRTSz),
45834604
ok.
45844605

45854606
alias_bif_test(Node) ->
@@ -4624,10 +4645,12 @@ alias_bif_test(Node) ->
46244645

46254646

46264647
monitor_alias(Config) when is_list(Config) ->
4648+
PRTSz = pid_ref_table_size(),
46274649
monitor_alias_test(node()),
46284650
{ok, Peer, Node} = ?CT_PEER(),
46294651
monitor_alias_test(Node),
46304652
stop_node(Peer, Node),
4653+
check_pid_ref_table_size(PRTSz),
46314654
ok.
46324655

46334656
monitor_alias_test(Node) ->
@@ -4711,6 +4734,7 @@ monitor_alias_test(Node) ->
47114734
spawn_monitor_alias(Config) when is_list(Config) ->
47124735
%% Exit signals with immediate exit reasons are sent
47134736
%% in a different manner than compound exit reasons.
4737+
PRTSz = pid_ref_table_size(),
47144738
spawn_monitor_alias_test(undefined, node(), spawn_opt, normal),
47154739
spawn_monitor_alias_test(undefined, node(), spawn_opt, make_ref()),
47164740
spawn_monitor_alias_test(undefined, node(), spawn_request, normal),
@@ -4723,6 +4747,7 @@ spawn_monitor_alias(Config) when is_list(Config) ->
47234747
spawn_monitor_alias_test(Peer3, Node3, spawn_request, normal),
47244748
{ok, Peer4, Node4} = ?CT_PEER(),
47254749
spawn_monitor_alias_test(Peer4, Node4, spawn_request, make_ref()),
4750+
check_pid_ref_table_size(PRTSz),
47264751
ok.
47274752

47284753
spawn_monitor_alias_test(Peer, Node, SpawnType, ExitReason) ->
@@ -4863,6 +4888,28 @@ spawn_monitor_alias_test(Peer, Node, SpawnType, ExitReason) ->
48634888
ok
48644889
end.
48654890

4891+
alias_process_exit(Config) when is_list(Config) ->
4892+
Tester = self(),
4893+
CreatedAliases = make_ref(),
4894+
PRTSz = pid_ref_table_size(),
4895+
P = spawn_link(fun () ->
4896+
A0 = alias([explicit_unalias]),
4897+
A1 = alias([reply]),
4898+
A2 = monitor(process, Tester, [{alias, explicit_unalias}]),
4899+
A3 = monitor(process, Tester, [{alias, demonitor}]),
4900+
A4 = monitor(process, Tester, [{alias, reply_demonitor}]),
4901+
Tester ! CreatedAliases,
4902+
receive after infinity -> ok end,
4903+
some_module:some_function([A0, A1, A2, A3, A4])
4904+
end),
4905+
receive CreatedAliases -> ok end,
4906+
PRTSz = erts_debug:get_internal_state(pid_ref_table_size) - 5,
4907+
unlink(P),
4908+
exit(P, kill),
4909+
false = is_process_alive(P),
4910+
check_pid_ref_table_size(PRTSz),
4911+
ok.
4912+
48664913
monitor_tag(Config) when is_list(Config) ->
48674914
%% Exit signals with immediate exit reasons are sent
48684915
%% in a different manner than compound exit reasons, and

0 commit comments

Comments
 (0)