Skip to content

Commit

Permalink
Merge PR-7970 from juhlig/ets_no_heir_gift_data
Browse files Browse the repository at this point in the history
OTP-19512
  • Loading branch information
sverker authored Feb 27, 2025
2 parents 745717a + 74cf856 commit 633e287
Show file tree
Hide file tree
Showing 4 changed files with 90 additions and 33 deletions.
58 changes: 37 additions & 21 deletions erts/emulator/beam/erl_db.c
Original file line number Diff line number Diff line change
Expand Up @@ -423,7 +423,7 @@ static int db_max_tabs;

static void fix_table_locked(Process* p, DbTable* tb);
static void unfix_table_locked(Process* p, DbTable* tb, db_lock_kind_t* kind);
static void set_heir(Process* me, DbTable* tb, Eterm heir, UWord heir_data);
static void set_heir(Process* me, DbTable* tb, Eterm heir, Eterm heir_data);
static void free_heir_data(DbTable*);
static SWord free_fixations_locked(Process* p, DbTable *tb);

Expand Down Expand Up @@ -2479,7 +2479,7 @@ BIF_RETTYPE ets_new_2(BIF_ALIST_2)
Eterm val;
Eterm ret;
Eterm heir;
UWord heir_data;
Eterm heir_data;
Uint32 status;
Sint keypos;
bool is_named, is_compressed;
Expand Down Expand Up @@ -2507,7 +2507,7 @@ BIF_RETTYPE ets_new_2(BIF_ALIST_2)
is_decentralized_counters = false;
decentralized_counters_option = -1;
heir = am_none;
heir_data = (UWord) am_undefined;
heir_data = am_undefined;
is_compressed = erts_ets_always_compress;
number_of_locks = 0;
is_explicit_lock_granularity = false;
Expand Down Expand Up @@ -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;
Expand Down Expand Up @@ -3065,10 +3069,11 @@ BIF_RETTYPE ets_setopts_2(BIF_ALIST_2)
Eterm* tp;
Eterm opt;
Eterm heir = THE_NON_VALUE;
UWord heir_data = (UWord) THE_NON_VALUE;
Eterm heir_data = THE_NON_VALUE;
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) {
Expand All @@ -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:
Expand All @@ -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);
}
Expand Down Expand Up @@ -4780,7 +4789,7 @@ static int give_away_to_heir(Process* p, DbTable* tb)
Process* to_proc;
ErtsProcLocks to_locks = ERTS_PROC_LOCK_MAIN;
Eterm to_pid;
UWord heir_data;
Eterm heir_data;

ASSERT(tb->common.owner == p->common.id);
ASSERT(is_internal_pid(tb->common.heir));
Expand Down Expand Up @@ -4830,12 +4839,17 @@ static int give_away_to_heir(Process* p, DbTable* tb)

db_unlock(tb,LCK_WRITE);
heir_data = tb->common.heir_data;
if (!is_immed(heir_data)) {
Eterm* tpv = ((DbTerm*)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;
}
Expand All @@ -4851,6 +4865,8 @@ send_ets_transfer_message(Process *c_p, Process *proc,
ErlOffHeap *ohp;
Eterm tid, hd_copy, msg, sender;

ASSERT(is_value(heir_data));

hsz = 5;
if (!is_table_named(tb))
hsz += ERTS_MAGIC_REF_THING_SIZE;
Expand Down Expand Up @@ -5218,8 +5234,8 @@ static SWord free_fixations_locked(Process* p, DbTable *tb)
return ctx.cnt;
}

static void set_heir(Process* me, DbTable* tb, Eterm heir, UWord heir_data)
{
static void set_heir(Process* me, DbTable* tb, Eterm heir, Eterm heir_data)
{
tb->common.heir = heir;
if (heir == am_none) {
return;
Expand All @@ -5238,15 +5254,14 @@ static void set_heir(Process* me, DbTable* tb, Eterm heir, UWord heir_data)
}
}

if (!is_immed(heir_data)) {
DeclareTmpHeap(tmp,2,me);
if (is_value(heir_data) && !is_immed(heir_data)) {
Eterm tmp[2];
Eterm wrap_tpl;
int size;
DbTerm* dbterm;
Eterm* top;
ErlOffHeap tmp_offheap;

UseTmpHeap(2,me);
/* Make a dummy 1-tuple around data to use DbTerm */
wrap_tpl = TUPLE1(tmp,heir_data);
size = size_object(wrap_tpl);
Expand All @@ -5257,17 +5272,18 @@ static void set_heir(Process* me, DbTable* tb, Eterm heir, UWord heir_data)
tmp_offheap.first = NULL;
copy_struct(wrap_tpl, size, &top, &tmp_offheap);
dbterm->first_oh = tmp_offheap.first;
heir_data = (UWord)dbterm;
UnUseTmpHeap(2,me);
ASSERT(!is_immed(heir_data));
heir_data = make_boxed((Eterm*)dbterm);
}
tb->common.heir_data = heir_data;
}

static void free_heir_data(DbTable* tb)
{
if (tb->common.heir != am_none && !is_immed(tb->common.heir_data)) {
DbTerm* p = (DbTerm*) 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,
sizeof(DbTerm) + (p->size-1)*sizeof(Eterm));
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/erl_db_util.h
Original file line number Diff line number Diff line change
Expand Up @@ -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 */
UWord heir_data; /* To send in ETS-TRANSFER (is_immed or (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 */
Expand Down
20 changes: 14 additions & 6 deletions lib/stdlib/src/ets.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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 }
Expand Down Expand Up @@ -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,
Expand All @@ -1141,6 +1147,7 @@ same as specifying
| {decentralized_counters, boolean()}
| compressed,
Pos :: pos_integer(),
Pid :: pid(),
HeirData :: term().

new(_, _) ->
Expand Down Expand Up @@ -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(_, _) ->
Expand Down
43 changes: 38 additions & 5 deletions lib/stdlib/test/ets_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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]).
Expand Down Expand Up @@ -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,
Expand Down Expand Up @@ -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).
Expand Down Expand Up @@ -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"})),
Expand Down

0 comments on commit 633e287

Please sign in to comment.