File 2062-erts-Add-ability-to-suppress-ETS-TRANSFER-message.patch of Package erlang
From 74cf8566e4fad9244258fa566191ae9da5c5d124 Mon Sep 17 00:00:00 2001
From: Jan Uhlig <juhlig@hnc-agency.org>
Date: Tue, 25 Feb 2025 17:54:10 +0100
Subject: [PATCH 2/2] erts: Add ability to suppress ETS-TRANSFER message
Co-authored-by: Maria Scott <maria-12648430@hnc-agency.org>
---
erts/emulator/beam/erl_db.c | 37 +++++++++++++++++++--------
erts/emulator/beam/erl_db_util.h | 2 +-
lib/stdlib/src/ets.erl | 20 ++++++++++-----
lib/stdlib/test/ets_SUITE.erl | 43 ++++++++++++++++++++++++++++----
4 files changed, 79 insertions(+), 23 deletions(-)
diff --git a/erts/emulator/beam/erl_db.c b/erts/emulator/beam/erl_db.c
index eddc201637..c1ef19fba3 100644
--- a/erts/emulator/beam/erl_db.c
+++ b/erts/emulator/beam/erl_db.c
@@ -2587,6 +2587,10 @@ BIF_RETTYPE ets_new_2(BIF_ALIST_2)
heir = am_none;
heir_data = am_undefined;
}
+ else if (tp[1] == am_heir && is_internal_pid(tp[2])) {
+ heir = tp[2];
+ heir_data = THE_NON_VALUE;
+ }
else if (tp[1] == am_decentralized_counters) {
if (tp[2] == am_true) {
decentralized_counters_option = 1;
@@ -3069,6 +3073,7 @@ BIF_RETTYPE ets_setopts_2(BIF_ALIST_2)
Uint32 protection = 0;
DeclareTmpHeap(fakelist,2,BIF_P);
Eterm tail;
+ bool do_update_heir = false;
DB_BIF_GET_TABLE(tb, DB_WRITE, LCK_WRITE, BIF_ets_setopts_2);
if (tb == NULL) {
@@ -3091,11 +3096,15 @@ BIF_RETTYPE ets_setopts_2(BIF_ALIST_2)
heir = tp[2];
if (arityval(tp[0]) == 2 && heir == am_none) {
heir_data = am_undefined;
+ }
+ else if (arityval(tp[0]) == 2 && is_internal_pid(heir)) {
+ heir_data = THE_NON_VALUE;
}
else if (arityval(tp[0]) == 3 && is_internal_pid(heir)) {
heir_data = tp[3];
}
else goto badarg;
+ do_update_heir = true;
break;
case am_protection:
@@ -3118,7 +3127,7 @@ BIF_RETTYPE ets_setopts_2(BIF_ALIST_2)
if (tb->common.owner != BIF_P->common.id)
goto badarg;
- if (heir_data != THE_NON_VALUE) {
+ if (do_update_heir) {
free_heir_data(tb);
set_heir(BIF_P, tb, heir, heir_data);
}
@@ -4830,12 +4839,17 @@ retry:
db_unlock(tb,LCK_WRITE);
heir_data = tb->common.heir_data;
- if (is_boxed(heir_data)) {
- Eterm* tpv = ((DbTerm*)boxed_val(heir_data))->tpl; /* tuple_val */
- ASSERT(arityval(*tpv) == 1);
- heir_data = tpv[1];
+ if (is_value(heir_data)) {
+ if (is_boxed(heir_data)) {
+ Eterm* tpv = ((DbTerm*)boxed_val(heir_data))->tpl; /* tuple_val */
+ ASSERT(arityval(*tpv) == 1);
+ heir_data = tpv[1];
+ }
+ else {
+ ASSERT(is_immed(heir_data));
+ }
+ send_ets_transfer_message(p, to_proc, &to_locks, tb, heir_data);
}
- send_ets_transfer_message(p, to_proc, &to_locks, tb, heir_data);
erts_proc_unlock(to_proc, to_locks);
return !0;
}
@@ -5222,8 +5236,6 @@ static SWord free_fixations_locked(Process* p, DbTable *tb)
static void set_heir(Process* me, DbTable* tb, Eterm heir, Eterm heir_data)
{
- ASSERT(is_value(heir_data));
-
tb->common.heir = heir;
if (heir == am_none) {
return;
@@ -5242,8 +5254,8 @@ static void set_heir(Process* me, DbTable* tb, Eterm heir, Eterm heir_data)
}
}
- if (!is_immed(heir_data)) {
- Eterm tmp[2];
+ if (is_value(heir_data) && !is_immed(heir_data)) {
+ Eterm tmp[2];
Eterm wrap_tpl;
int size;
DbTerm* dbterm;
@@ -5267,7 +5279,10 @@ static void set_heir(Process* me, DbTable* tb, Eterm heir, Eterm heir_data)
static void free_heir_data(DbTable* tb)
{
- if (tb->common.heir != am_none && is_boxed(tb->common.heir_data)) {
+ if (tb->common.heir != am_none
+ && is_value(tb->common.heir_data)
+ && is_boxed(tb->common.heir_data)) {
+
DbTerm* p = (DbTerm*) boxed_val(tb->common.heir_data);
db_cleanup_offheap_comp(p);
erts_db_free(ERTS_ALC_T_DB_HEIR_DATA, tb, (void *)p,
diff --git a/erts/emulator/beam/erl_db_util.h b/erts/emulator/beam/erl_db_util.h
index e2540f33d8..3fad3aa6cc 100644
--- a/erts/emulator/beam/erl_db_util.h
+++ b/erts/emulator/beam/erl_db_util.h
@@ -321,7 +321,7 @@ typedef struct db_table_common {
Uint32 type; /* table type, *read only* after creation */
Eterm owner; /* Pid of the creator */
Eterm heir; /* Pid of the heir */
- Eterm heir_data; /* To send in ETS-TRANSFER (immed or boxed(DbTerm*) */
+ Eterm heir_data; /* To send in ETS-TRANSFER (immed, boxed(DbTerm*) or THE_NON_VALUE */
Uint64 heir_started_interval; /* To further identify the heir */
Eterm the_name; /* an atom */
Binary *btid; /* table magic ref, read only after creation */
diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl
index 56c44aed54..36a8736159 100644
--- a/lib/stdlib/src/ets.erl
+++ b/lib/stdlib/src/ets.erl
@@ -1019,10 +1019,15 @@ same as specifying
[](){: #heir }
-- **`{heir,Pid,HeirData} | {heir,none}`** - Set a process as heir. The heir
- inherits the table if the owner terminates. Message
- `{'ETS-TRANSFER',tid(),FromPid,HeirData}` is sent to the heir when that
- occurs. The heir must be a local process. Default heir is `none`, which
+- **`{heir,Pid,HeirData} | {heir,Pid} | {heir,none}`** - Set a process as heir.
+ The heir inherits the table if the owner terminates. If `HeirData` is given, a
+ message `{'ETS-TRANSFER',tid(),FromPid,HeirData}` is sent to the heir when
+ that occurs. If `{heir,Pid}` is given, no `'ETS-TRANSFER'` message is
+ sent. The user must then make sure the heir gets notified some other way
+ (through a link or monitor for example) to avoid the table being left unnoticed
+ by its new owner.
+
+ The heir must be a local process. Default heir is `none`, which
destroys the table when the owner terminates.
[](){: #new_2_write_concurrency }
@@ -1132,7 +1137,8 @@ same as specifying
Name :: atom(),
Options :: [Option],
Option :: Type | Access | named_table | {keypos,Pos}
- | {heir, Pid :: pid(), HeirData} | {heir, none} | Tweaks,
+ | {heir, Pid} | {heir, Pid, HeirData} | {heir, none}
+ | Tweaks,
Type :: table_type(),
Access :: table_access(),
WriteConcurrencyAlternative :: boolean() | auto,
@@ -1141,6 +1147,7 @@ same as specifying
| {decentralized_counters, boolean()}
| compressed,
Pos :: pos_integer(),
+ Pid :: pid(),
HeirData :: term().
new(_, _) ->
@@ -1629,7 +1636,8 @@ created is [`heir`](`m:ets#heir`). The calling process must be the table owner.
-spec setopts(Table, Opts) -> true when
Table :: table(),
Opts :: Opt | [Opt],
- Opt :: {heir, pid(), HeirData} | {heir,none},
+ Opt :: {heir, Pid} | {heir, Pid, HeirData} | {heir,none},
+ Pid :: pid(),
HeirData :: term().
setopts(_, _) ->
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index db151e9d14..cc6731eb08 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -99,7 +99,7 @@
exit_many_large_table_owner/1,
exit_many_tables_owner/1,
exit_many_many_tables_owner/1]).
--export([write_concurrency/1, heir/1, give_away/1, setopts/1]).
+-export([write_concurrency/1, heir/1, heir_2/1, give_away/1, setopts/1]).
-export([bad_table/1, types/1]).
-export([otp_9932/1]).
-export([otp_9423/1]).
@@ -178,7 +178,7 @@ all() ->
smp_ordered_iteration,
smp_select_delete, otp_8166, exit_large_table_owner,
exit_many_large_table_owner, exit_many_tables_owner,
- exit_many_many_tables_owner, write_concurrency, heir,
+ exit_many_many_tables_owner, write_concurrency, heir, heir_2,
give_away, setopts, bad_table, types,
otp_10182,
otp_9932,
@@ -3537,6 +3537,38 @@ heir_1(HeirData,Mode,Opts) ->
Founder ! {go, Heir},
{'DOWN', Mref, process, Heir, normal} = receive_any().
+
+%% Test the heir option without gift data
+heir_2(Config) when is_list(Config) ->
+ repeat_for_opts(fun heir_2_do/1).
+
+
+heir_2_do(Opts) ->
+ Parent = self(),
+
+ FounderFn = fun() ->
+ Tab = ets:new(foo, [private, {heir, Parent} | Opts]),
+ true = ets:insert(Tab, {key, 1}),
+ get_tab = receive_any(),
+ Parent ! {tab, Tab},
+ die_please = receive_any(),
+ ok
+ end,
+
+ {Founder, FounderRef} = my_spawn_monitor(FounderFn),
+
+ Founder ! get_tab,
+ {tab, Tab} = receive_any(),
+ {'EXIT', {badarg, _}} = (catch ets:lookup(Tab, key)),
+
+ Founder ! die_please,
+ {'DOWN', FounderRef, process, Founder, normal} = receive_any(),
+ [{key, 1}] = ets:lookup(Tab, key),
+
+ true = ets:delete(Tab),
+ ok.
+
+
%% Test ets:give_way/3.
give_away(Config) when is_list(Config) ->
repeat_for_opts(fun give_away_do/1).
@@ -3627,17 +3659,18 @@ setopts_do(Opts) ->
T = ets_new(foo,[named_table, private | Opts]),
none = ets:info(T,heir),
Heir = my_spawn_link(fun()->heir_heir(Self) end),
- ets:setopts(T,{heir,Heir,"Data"}),
+ ets:setopts(T,{heir,Heir}),
Heir = ets:info(T,heir),
- ets:setopts(T,{heir,self(),"Data"}),
+ ets:setopts(T,{heir,self()}),
Self = ets:info(T,heir),
ets:setopts(T,[{heir,Heir,"Data"}]),
Heir = ets:info(T,heir),
+ ets:setopts(T,[{heir,self(),"Data"}]),
+ Self = ets:info(T,heir),
ets:setopts(T,[{heir,none}]),
none = ets:info(T,heir),
{'EXIT',{badarg,_}} = (catch ets:setopts(T,[{heir,self(),"Data"},false])),
- {'EXIT',{badarg,_}} = (catch ets:setopts(T,{heir,self()})),
{'EXIT',{badarg,_}} = (catch ets:setopts(T,{heir,false})),
{'EXIT',{badarg,_}} = (catch ets:setopts(T,heir)),
{'EXIT',{badarg,_}} = (catch ets:setopts(T,{heir,false,"Data"})),
--
2.43.0