Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
  • Loading branch information
sverker committed Aug 22, 2023
2 parents 5bd165d + 269711d commit dec8215
Show file tree
Hide file tree
Showing 7 changed files with 107 additions and 38 deletions.
2 changes: 1 addition & 1 deletion erts/emulator/beam/erl_bif_info.c
Original file line number Diff line number Diff line change
Expand Up @@ -173,7 +173,7 @@ erts_bld_bin_list(Uint **hpp, Uint *szp, ErlOffHeap* oh, Eterm tail)
union erl_off_heap_ptr u;
Eterm res = tail;
Eterm tuple;
struct erts_tmp_aligned_offheap tmp;
union erts_tmp_aligned_offheap tmp;

for (u.hdr = oh->first; u.hdr; u.hdr = u.hdr->next) {
erts_align_offheap(&u, &tmp);
Expand Down
4 changes: 2 additions & 2 deletions erts/emulator/beam/erl_db_util.c
Original file line number Diff line number Diff line change
Expand Up @@ -3723,12 +3723,12 @@ static Uint db_element_size(DbTerm *obj, Eterm* tpl, Uint pos) {
}

/* Our own "cleanup_offheap"
* as refc-binaries may be unaligned in compressed terms
* as ProcBin and ErtsMRefThing may be unaligned in compressed terms
*/
void db_cleanup_offheap_comp(DbTerm* obj)
{
union erl_off_heap_ptr u;
struct erts_tmp_aligned_offheap tmp;
union erts_tmp_aligned_offheap tmp;

for (u.hdr = obj->first_oh; u.hdr; u.hdr = u.hdr->next) {
erts_align_offheap(&u, &tmp);
Expand Down
26 changes: 17 additions & 9 deletions erts/emulator/beam/erl_db_util.h
Original file line number Diff line number Diff line change
Expand Up @@ -577,14 +577,15 @@ ERTS_GLB_INLINE Binary *erts_db_get_match_prog_binary_unchecked(Eterm term);

/** @brief Ensure off-heap header is word aligned, make a temporary copy if
* not. Needed when inspecting ETS off-heap lists that may contain unaligned
* ProcBins if table is 'compressed'.
* ProcBin and ErtsMRefThing if table is 'compressed'.
*/
struct erts_tmp_aligned_offheap
union erts_tmp_aligned_offheap
{
ProcBin proc_bin;
ErtsMRefThing mref_thing;
};
ERTS_GLB_INLINE void erts_align_offheap(union erl_off_heap_ptr*,
struct erts_tmp_aligned_offheap* tmp);
union erts_tmp_aligned_offheap* tmp);

#if ERTS_GLB_INLINE_INCL_FUNC_DEF

Expand Down Expand Up @@ -620,20 +621,27 @@ erts_db_get_match_prog_binary(Eterm term)

ERTS_GLB_INLINE void
erts_align_offheap(union erl_off_heap_ptr* ohp,
struct erts_tmp_aligned_offheap* tmp)
union erts_tmp_aligned_offheap* tmp)
{
if ((UWord)ohp->voidp % sizeof(UWord) != 0) {
/*
* ETS store word unaligned ProcBins in its compressed format.
* Make a temporary aligned copy.
* ETS store word unaligned ProcBin and ErtsMRefThing in its compressed
* format. Make a temporary aligned copy.
*
* Warning, must pass (void*)-variable to memcpy. Otherwise it will
* cause Bus error on Sparc due to false compile time assumptions
* about word aligned memory (type cast is not enough).
*/
sys_memcpy(tmp, ohp->voidp, sizeof(*tmp));
ASSERT(tmp->proc_bin.thing_word == HEADER_PROC_BIN);
ohp->pb = &tmp->proc_bin;
sys_memcpy(tmp, ohp->voidp, sizeof(Eterm)); /* thing_word */
if (tmp->proc_bin.thing_word == HEADER_PROC_BIN) {
sys_memcpy(tmp, ohp->voidp, sizeof(tmp->proc_bin));
ohp->pb = &tmp->proc_bin;
}
else {
sys_memcpy(tmp, ohp->voidp, sizeof(tmp->mref_thing));
ASSERT(is_magic_ref_thing(&tmp->mref_thing));
ohp->mref = &tmp->mref_thing;
}
}
}

Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/erl_node_tables.c
Original file line number Diff line number Diff line change
Expand Up @@ -1527,7 +1527,7 @@ static void
insert_offheap(ErlOffHeap *oh, int type, Eterm id)
{
union erl_off_heap_ptr u;
struct erts_tmp_aligned_offheap tmp;
union erts_tmp_aligned_offheap tmp;
struct insert_offheap2_arg a;
a.type = BIN_REF;

Expand Down
60 changes: 48 additions & 12 deletions erts/emulator/beam/external.c
Original file line number Diff line number Diff line change
Expand Up @@ -3534,6 +3534,20 @@ enc_term_int(TTBEncodeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj, byte* ep,
goto ref_common;

case REF_DEF:
if ((dflags & DFLAG_ETS_COMPRESSED) && is_internal_magic_ref(obj)) {
ErtsMRefThing tmp;
ErtsMRefThing *mrtp = (ErtsMRefThing *) internal_ref_val(obj);

erts_refc_inc(&mrtp->mb->intern.refc, 2);

*ep++ = MAGIC_REF_INTERNAL_REF;
sys_memcpy(&tmp, mrtp, sizeof(ErtsMRefThing));
tmp.next = *off_heap;
sys_memcpy(ep, &tmp, sizeof(ErtsMRefThing));
*off_heap = (struct erl_off_heap_header*) ep;
ep += sizeof(ErtsMRefThing);
break;
}

*ep++ = NEWER_REFERENCE_EXT;

Expand Down Expand Up @@ -5100,6 +5114,19 @@ dec_term(ErtsDistExternal *edep,
*objp = make_binary(sub);
break;
}
case MAGIC_REF_INTERNAL_REF:
{
ErtsMRefThing* mrtp = (ErtsMRefThing*) hp;
sys_memcpy(mrtp, ep, sizeof(ErtsMRefThing));
ep += sizeof(ErtsMRefThing);
erts_refc_inc(&mrtp->mb->intern.refc, 2);
hp += ERTS_MAGIC_REF_THING_SIZE;
mrtp->next = factory->off_heap->first;
factory->off_heap->first = (struct erl_off_heap_header*)mrtp;
*objp = make_internal_ref(mrtp);
ASSERT(is_internal_magic_ref(*objp));
break;
}

case LOCAL_EXT:
internal_nc = !0;
Expand Down Expand Up @@ -5376,20 +5403,24 @@ encode_size_struct_int(TTBSizeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj,
result += (1 + 2 + nlen + 4 + 4*i);
break;
}
case REF_DEF: {
int nlen;
i = internal_ref_no_numbers(obj);
if (dflags & (DFLAG_ETS_COMPRESSED|DFLAG_LOCAL_EXT)) {
nlen = 1;
case REF_DEF:
if ((dflags & DFLAG_ETS_COMPRESSED) && is_internal_magic_ref(obj)) {
result += 1 + sizeof(ErtsMRefThing);
}
else {
nlen = encode_atom_size(acmp,
internal_ref_node_name(obj),
dflags);
int nlen;
i = internal_ref_no_numbers(obj);
if (dflags & (DFLAG_ETS_COMPRESSED|DFLAG_LOCAL_EXT)) {
nlen = 1;
}
else {
nlen = encode_atom_size(acmp,
internal_ref_node_name(obj),
dflags);
}
result += (1 + 2 + nlen + 4 + 4*i);
}
result += (1 + 2 + nlen + 4 + 4*i);
break;
}
break;
case EXTERNAL_PORT_DEF: {
int nlen = encode_atom_size(acmp,
external_port_node_name(obj),
Expand Down Expand Up @@ -6033,7 +6064,12 @@ decoded_size(const byte *ep, const byte* endp, int internal_tags, B2TContext* ct
SKIP(2+sizeof(ProcBin));
heap_size += PROC_BIN_SIZE + ERL_SUB_BIN_SIZE;
break;
CHKSIZE(1);
case MAGIC_REF_INTERNAL_REF:
if (!internal_tags)
goto error;
SKIP(sizeof(ErtsMRefThing));
heap_size += ERTS_MAGIC_REF_THING_SIZE;
break;
case LOCAL_EXT:
/*
* Currently the hash is 4 bytes large...
Expand Down
1 change: 1 addition & 0 deletions erts/emulator/beam/external.h
Original file line number Diff line number Diff line change
Expand Up @@ -68,6 +68,7 @@
#define ATOM_INTERNAL_REF3 'K'
#define BINARY_INTERNAL_REF 'J'
#define BIT_BINARY_INTERNAL_REF 'L'
#define MAGIC_REF_INTERNAL_REF 'N'
#define COMPRESSED 'P'

#if 0
Expand Down
50 changes: 37 additions & 13 deletions lib/stdlib/test/ets_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -100,6 +100,7 @@
-export([otp_9932/1]).
-export([otp_9423/1]).
-export([otp_10182/1]).
-export([compress_magic_ref/1]).
-export([ets_all/1]).
-export([massive_ets_all/1]).
-export([take/1]).
Expand Down Expand Up @@ -173,6 +174,7 @@ all() ->
otp_10182,
otp_9932,
otp_9423,
compress_magic_ref,
ets_all,
massive_ets_all,
take,
Expand Down Expand Up @@ -1110,8 +1112,8 @@ delete_all_objects_trap(Opts, Mode) ->
false;
"delete_all_objects done" ->
ct:fail("No trap detected");
M ->
%%io:format("Ignored msg: ~p\n", [M]),
_M ->
%%io:format("Ignored msg: ~p\n", [_M]),
true
end
end),
Expand Down Expand Up @@ -5528,30 +5530,30 @@ insert_trap_delete_run3(Traps, {Opts, InsertFunc, Mode}, NKeys) ->
%% Rename table during trapping ets:insert
insert_trap_rename(Config) when is_list(Config) ->
repeat_for_opts(fun(Opts) ->
[insert_trap_rename_run1(InsertFunc)
[insert_trap_rename_run1(Opts, InsertFunc)
|| InsertFunc <- [insert, insert_new]]
end,
[all_non_stim_types, write_concurrency, compressed]),
ok.

insert_trap_rename_run1(InsertFunc) ->
insert_trap_rename_run1(Opts, InsertFunc) ->
NKeys = 50_000 + rand:uniform(50_000),
%% First measure how many traps the insert op will do
Traps0 = insert_trap_rename_run3(unlimited, InsertFunc, NKeys),
Traps0 = insert_trap_rename_run3(Opts, unlimited, InsertFunc, NKeys),
%% Then do again and rename table at different moments
Decr = (Traps0 div 5) + 1,
insert_trap_rename_run2(Traps0-1, Decr, InsertFunc, NKeys),
insert_trap_rename_run2(Opts, Traps0-1, Decr, InsertFunc, NKeys),
ok.

insert_trap_rename_run2(Traps, _Decr, InsertFunc, NKeys) when Traps =< 1 ->
insert_trap_rename_run3(1, InsertFunc, NKeys),
insert_trap_rename_run2(Opts, Traps, _Decr, InsertFunc, NKeys) when Traps =< 1 ->
insert_trap_rename_run3(Opts, 1, InsertFunc, NKeys),
ok;
insert_trap_rename_run2(Traps, Decr, InsertFunc, NKeys) ->
insert_trap_rename_run3(Traps, InsertFunc, NKeys),
insert_trap_rename_run2(Traps - Decr, Decr, InsertFunc, NKeys).
insert_trap_rename_run2(Opts, Traps, Decr, InsertFunc, NKeys) ->
insert_trap_rename_run3(Opts, Traps, InsertFunc, NKeys),
insert_trap_rename_run2(Opts, Traps - Decr, Decr, InsertFunc, NKeys).


insert_trap_rename_run3(Traps, InsertFunc, NKeys) ->
insert_trap_rename_run3(Opts, Traps, InsertFunc, NKeys) ->
io:format("insert_trap_rename_run(~p, ~p)\n", [Traps, InsertFunc]),
TabName = insert_trap_rename,
TabRenamed = insert_trap_rename_X,
Expand All @@ -5561,7 +5563,7 @@ insert_trap_rename_run3(Traps, InsertFunc, NKeys) ->
OwnerFun =
fun() ->
erlang:trace(Tester, true, [running]),
ets:new(TabName, [named_table, public]),
ets_new(TabName, [named_table, public | Opts]),
Tester ! {ets_new, ets:whereis(TabName)},
io:format("Wait for ets:~p/2 to yield...\n", [InsertFunc]),
GotTraps = repeat_while(
Expand Down Expand Up @@ -7800,6 +7802,28 @@ otp_10182(Config) when is_list(Config) ->
In = Out
end).

%% Verify magic refs in compressed table are reference counted correctly
compress_magic_ref(Config) when is_list(Config)->
F = fun(Opts) ->
T = ets:new(banana, Opts),
ets:insert(T, {key, atomics:new(2, [])}),
erlang:garbage_collect(), % make really sure no ref on heap
[{_, Ref}] = ets:lookup(T, key),
#{size := 2} = atomics:info(Ref), % Still alive!

%% Now test ets:delete will deallocate if last ref
WeakRef = term_to_binary(Ref),
erlang:garbage_collect(), % make sure no Ref on heap
ets:delete(T, key),
StaleRef = binary_to_term(WeakRef),
badarg = try atomics:info(StaleRef)
catch error:badarg -> badarg end,
ets:delete(T),
ok
end,
repeat_for_opts(F, [[set, ordered_set], compressed]),
ok.

%% Test that ets:all include/exclude tables that we know are created/deleted
ets_all(Config) when is_list(Config) ->
Pids = [spawn_link(fun() -> ets_all_run() end) || _ <- [1,2]],
Expand Down

0 comments on commit dec8215

Please sign in to comment.