Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:26
erlang
1072-erts-Shrink-and-optimize-funs.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 1072-erts-Shrink-and-optimize-funs.patch of Package erlang
From 6fcba0471b736733951b70ea09e5858567b5aa1c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org> Date: Fri, 26 May 2023 22:29:07 +0200 Subject: [PATCH 2/3] erts: Shrink and optimize funs This commit shrinks fun by one word through packing the arity, number of free variables, and whether it's external or not into the header word. As an added bonus, we can now combine function type tests with arity tests, further reducing fun call overhead. --- erts/emulator/beam/beam_common.c | 9 +- erts/emulator/beam/copy.c | 26 ++--- erts/emulator/beam/emu/emu_load.c | 4 +- erts/emulator/beam/erl_bif_info.c | 8 +- erts/emulator/beam/erl_bif_op.c | 2 +- erts/emulator/beam/erl_fun.c | 17 ++-- erts/emulator/beam/erl_fun.h | 27 +++--- erts/emulator/beam/erl_gc.h | 2 +- erts/emulator/beam/erl_process_dump.c | 4 +- erts/emulator/beam/erl_term.h | 38 +++++++- erts/emulator/beam/erl_term_hashing.c | 6 +- erts/emulator/beam/external.c | 17 ++-- erts/emulator/beam/generators.tab | 5 +- erts/emulator/beam/jit/arm/beam_asm.hpp | 3 +- erts/emulator/beam/jit/arm/instr_common.cpp | 17 +--- erts/emulator/beam/jit/arm/instr_fun.cpp | 95 ++++++++++--------- erts/emulator/beam/jit/asm_load.c | 4 +- erts/emulator/beam/jit/x86/beam_asm.hpp | 3 +- erts/emulator/beam/jit/x86/instr_common.cpp | 17 +--- erts/emulator/beam/jit/x86/instr_fun.cpp | 89 +++++++++-------- erts/emulator/beam/utils.c | 14 ++- erts/emulator/test/erts_debug_SUITE.erl | 2 +- .../emulator/test/trace_call_memory_SUITE.erl | 4 +- 23 files changed, 211 insertions(+), 202 deletions(-) diff --git a/erts/emulator/beam/beam_common.c b/erts/emulator/beam/beam_common.c index 878425bf84..f278ca7707 100644 --- a/erts/emulator/beam/beam_common.c +++ b/erts/emulator/beam/beam_common.c @@ -1725,8 +1725,9 @@ call_fun(Process* p, /* Current process. */ code_ix = erts_active_code_ix(); code_ptr = (funp->entry.disp)->addresses[code_ix]; - if (ERTS_LIKELY(code_ptr != beam_unloaded_fun && funp->arity == arity)) { - for (int i = 0, num_free = funp->num_free; i < num_free; i++) { + if (ERTS_LIKELY(code_ptr != beam_unloaded_fun && + fun_arity(funp) == arity)) { + for (int i = 0, num_free = fun_num_free(funp); i < num_free; i++) { reg[i + arity] = funp->env[i]; } @@ -1765,7 +1766,7 @@ call_fun(Process* p, /* Current process. */ } } - if (funp->arity != arity) { + if (fun_arity(funp) != arity) { /* There is a fun defined, but the call has the wrong arity. */ Eterm *hp = HAlloc(p, 3); p->freason = EXC_BADARITY; @@ -1865,7 +1866,7 @@ is_function2(Eterm Term, Uint arity) { if (is_any_fun(Term)) { ErlFunThing *funp = (ErlFunThing*)fun_val(Term); - return funp->arity == arity; + return fun_arity(funp) == arity; } return 0; diff --git a/erts/emulator/beam/copy.c b/erts/emulator/beam/copy.c index 5a5ca58bcf..4c39e4c304 100644 --- a/erts/emulator/beam/copy.c +++ b/erts/emulator/beam/copy.c @@ -142,16 +142,16 @@ Uint size_object_x(Eterm obj, erts_literal_area_t *litopt) const ErlFunThing* funp = (ErlFunThing*)fun_val(obj); ASSERT(ERL_FUN_SIZE == (1 + thing_arityval(hdr))); - sum += ERL_FUN_SIZE + funp->num_free; + sum += ERL_FUN_SIZE + fun_num_free(funp); - for (int i = 1; i < funp->num_free; i++) { + for (int i = 1; i < fun_num_free(funp); i++) { obj = funp->env[i]; if (!IS_CONST(obj)) { ESTACK_PUSH(s, obj); } } - if (funp->num_free > 0) { + if (fun_num_free(funp) > 0) { obj = funp->env[0]; break; } @@ -396,9 +396,9 @@ Uint size_shared(Eterm obj) const ErlFunThing* funp = (ErlFunThing *) ptr; ASSERT(ERL_FUN_SIZE == (1 + thing_arityval(hdr))); - sum += ERL_FUN_SIZE + funp->num_free; + sum += ERL_FUN_SIZE + fun_num_free(funp); - for (int i = 0; i < funp->num_free; i++) { + for (int i = 0; i < fun_num_free(funp); i++) { obj = funp->env[i]; if (!IS_CONST(obj)) { EQUEUE_PUT(s, obj); @@ -558,7 +558,7 @@ cleanup: case FUN_SUBTAG: { const ErlFunThing *funp = (ErlFunThing *) ptr; - for (int i = 0; i < funp->num_free; i++) { + for (int i = 0; i < fun_num_free(funp); i++) { obj = funp->env[i]; if (!IS_CONST(obj)) { EQUEUE_PUT_UNCHECKED(s, obj); @@ -873,12 +873,12 @@ Eterm copy_struct_x(Eterm obj, Uint sz, Eterm** hpp, ErlOffHeap* off_heap, *dst_fun = *src_fun; - for (int i = 0; i < src_fun->num_free; i++) { + for (int i = 0; i < fun_num_free(dst_fun); i++) { dst_fun->env[i] = src_fun->env[i]; } ASSERT(&htop[ERL_FUN_SIZE] == &dst_fun->env[0]); - htop = &dst_fun->env[dst_fun->num_free]; + htop = &dst_fun->env[fun_num_free(dst_fun)]; *argp = make_fun(dst_fun); if (is_local_fun(dst_fun)) { @@ -1266,9 +1266,9 @@ Uint copy_shared_calculate(Eterm obj, erts_shcopy_t *info) const ErlFunThing* funp = (ErlFunThing *) ptr; ASSERT(ERL_FUN_SIZE == (1 + thing_arityval(hdr))); - sum += ERL_FUN_SIZE + funp->num_free; + sum += ERL_FUN_SIZE + fun_num_free(funp); - for (int i = 0; i < funp->num_free; i++) { + for (int i = 0; i < fun_num_free(funp); i++) { obj = funp->env[i]; if (!IS_CONST(obj)) { EQUEUE_PUT(s, obj); @@ -1610,7 +1610,7 @@ Uint copy_shared_perform_x(Eterm obj, Uint size, erts_shcopy_t *info, * restore it. */ dst_fun->thing_word = hdr; - for (int i = 0; i < src_fun->num_free; i++) { + for (int i = 0; i < fun_num_free(dst_fun); i++) { obj = src_fun->env[i]; if (!IS_CONST(obj)) { @@ -1622,7 +1622,7 @@ Uint copy_shared_perform_x(Eterm obj, Uint size, erts_shcopy_t *info, } ASSERT(&hp[ERL_FUN_SIZE] == &dst_fun->env[0]); - hp = &dst_fun->env[dst_fun->num_free]; + hp = &dst_fun->env[fun_num_free(dst_fun)]; *resp = make_fun(dst_fun); if (is_local_fun(dst_fun)) { @@ -1839,7 +1839,7 @@ Uint copy_shared_perform_x(Eterm obj, Uint size, erts_shcopy_t *info, const ErlFunThing* funp = (ErlFunThing *) hscan; ASSERT(ERL_FUN_SIZE == (1 + thing_arityval(*hscan))); hscan += ERL_FUN_SIZE; - remaining = funp->num_free; + remaining = fun_num_free(funp); break; } case MAP_SUBTAG: diff --git a/erts/emulator/beam/emu/emu_load.c b/erts/emulator/beam/emu/emu_load.c index 9a078410d0..3821b797e6 100644 --- a/erts/emulator/beam/emu/emu_load.c +++ b/erts/emulator/beam/emu/emu_load.c @@ -665,14 +665,14 @@ void beam_load_finalize_code(LoaderState* stp, struct erl_module_instance* inst_ literal = beamfile_get_literal(&stp->beam, stp->lambda_literals[i]); funp = (ErlFunThing *)fun_val(literal); - ASSERT(funp->external == 1); funp->entry.fun = fun_entry; funp->next = literal_area->off_heap; literal_area->off_heap = (struct erl_off_heap_header *)funp; - funp->external = 0; + ASSERT(funp->thing_word & (1 << FUN_HEADER_EXTERNAL_OFFS)); + funp->thing_word &= ~(1 << FUN_HEADER_EXTERNAL_OFFS); erts_refc_inc(&fun_entry->refc, 2); } diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c index 649aa19b95..5a24697db7 100644 --- a/erts/emulator/beam/erl_bif_info.c +++ b/erts/emulator/beam/erl_bif_info.c @@ -3702,7 +3702,7 @@ fun_info_2(BIF_ALIST_2) break; case am_env: { - Uint num_free = funp->num_free; + Uint num_free = fun_num_free(funp); int i; hp = HAlloc(p, 3 + 2 * num_free); @@ -3724,7 +3724,7 @@ fun_info_2(BIF_ALIST_2) hp = HAlloc(p, 3); break; case am_arity: - val = make_small(funp->arity); + val = make_small(fun_arity(funp)); hp = HAlloc(p, 3); break; case am_name: @@ -3763,7 +3763,7 @@ fun_info_mfa_1(BIF_ALIST_1) BIF_RET(TUPLE3(hp, funp->entry.fun->module, NIL, - make_small(funp->arity))); + make_small(fun_arity(funp)))); } } else { ASSERT(is_external_fun(funp) && funp->next == NULL); @@ -3773,7 +3773,7 @@ fun_info_mfa_1(BIF_ALIST_1) BIF_RET(TUPLE3(hp, mfa->module, mfa->function, - make_small(funp->arity))); + make_small(fun_arity(funp)))); } BIF_ERROR(p, BADARG); diff --git a/erts/emulator/beam/erl_bif_op.c b/erts/emulator/beam/erl_bif_op.c index 7113d9e890..60243bcc23 100644 --- a/erts/emulator/beam/erl_bif_op.c +++ b/erts/emulator/beam/erl_bif_op.c @@ -254,7 +254,7 @@ Eterm erl_is_function(Process* p, Eterm arg1, Eterm arg2) if (is_any_fun(arg1)) { ErlFunThing* funp = (ErlFunThing *) fun_val(arg1); - if (funp->arity == (Uint) arity) { + if (fun_arity(funp) == (Uint) arity) { BIF_RET(am_true); } } diff --git a/erts/emulator/beam/erl_fun.c b/erts/emulator/beam/erl_fun.c index cdac196472..6c51b57b57 100644 --- a/erts/emulator/beam/erl_fun.c +++ b/erts/emulator/beam/erl_fun.c @@ -304,12 +304,9 @@ ErlFunThing *erts_new_export_fun_thing(Eterm **hpp, Export *exp, int arity) funp = (ErlFunThing*)(*hpp); *hpp += ERL_FUN_SIZE; - funp->thing_word = HEADER_FUN; - funp->next = NULL; + funp->thing_word = MAKE_FUN_HEADER(arity, 0, 1); funp->entry.exp = exp; - funp->num_free = 0; - funp->external = 1; - funp->arity = arity; + funp->next = NULL; #ifdef DEBUG { @@ -330,13 +327,11 @@ ErlFunThing *erts_new_local_fun_thing(Process *p, ErlFunEntry *fe, p->htop += ERL_FUN_SIZE + num_free; erts_refc_inc(&fe->refc, 2); - funp->thing_word = HEADER_FUN; + funp->thing_word = MAKE_FUN_HEADER(arity, num_free, 0); + funp->entry.fun = fe; + funp->next = MSO(p).first; MSO(p).first = (struct erl_off_heap_header*) funp; - funp->entry.fun = fe; - funp->num_free = num_free; - funp->external = 0; - funp->arity = arity; #ifdef DEBUG { @@ -345,7 +340,7 @@ ErlFunThing *erts_new_local_fun_thing(Process *p, ErlFunEntry *fe, * sanity-check the arity at this point. If the fun is called while in * this state, the `error_handler` module will take care of it. */ const ErtsCodeMFA *mfa = erts_get_fun_mfa(fe, erts_active_code_ix()); - ASSERT(!mfa || funp->arity == mfa->arity - num_free); + ASSERT(!mfa || fun_arity(funp) == mfa->arity - num_free); ASSERT(arity == fe->arity); } #endif diff --git a/erts/emulator/beam/erl_fun.h b/erts/emulator/beam/erl_fun.h index 05d27da442..82a944d4a7 100644 --- a/erts/emulator/beam/erl_fun.h +++ b/erts/emulator/beam/erl_fun.h @@ -51,7 +51,9 @@ typedef struct erl_fun_entry { * environment. */ typedef struct erl_fun_thing { - Eterm thing_word; /* Subtag FUN_SUBTAG. */ + /* The header contains FUN_SUBTAG, arity, number of free variables, and + * whether this is an external fun. */ + Eterm thing_word; union { /* Both `ErlFunEntry` and `Export` begin with an `ErtsDispatchable`, so @@ -59,26 +61,29 @@ typedef struct erl_fun_thing { * pointer to improve performance. */ ErtsDispatchable *disp; - /* Pointer to function entry, valid iff `external == 0`.*/ + /* Pointer to function entry, valid iff the external bit is clear.*/ ErlFunEntry *fun; - /* Pointer to export entry, valid iff `external == 1`.*/ + /* Pointer to export entry, valid iff the external bit is set.*/ Export *exp; } entry; /* Next off-heap object, must be NULL when this is an external fun. */ struct erl_off_heap_header *next; - byte arity; /* The _apparent_ arity of the fun. */ - byte num_free; /* Number of free variables (in env). */ - byte external; /* Whether this is an external fun or not */ - - /* -- The following may be compound Erlang terms ---------------------- */ - Eterm env[]; /* Environment (free variables). */ + /* Environment (free variables), may be compound terms. */ + Eterm env[]; } ErlFunThing; -#define is_local_fun(FunThing) ((FunThing)->external == 0) -#define is_external_fun(FunThing) ((FunThing)->external != 0) +#define is_external_fun(FunThing) \ + (!!(((FunThing)->thing_word >> FUN_HEADER_EXTERNAL_OFFS) & 1)) +#define is_local_fun(FunThing) \ + (!(is_external_fun(FunThing))) + +#define fun_arity(FunThing) \ + (((FunThing)->thing_word >> FUN_HEADER_ARITY_OFFS) & 0xFF) +#define fun_num_free(FunThing) \ + (((FunThing)->thing_word >> FUN_HEADER_NUM_FREE_OFFS) & 0xFF) /* ERL_FUN_SIZE does _not_ include space for the environment which is a * C99-style flexible array */ diff --git a/erts/emulator/beam/erl_gc.h b/erts/emulator/beam/erl_gc.h index 2b21f9e7be..3556ad1168 100644 --- a/erts/emulator/beam/erl_gc.h +++ b/erts/emulator/beam/erl_gc.h @@ -82,7 +82,7 @@ ERTS_GLB_INLINE Eterm* move_boxed(Eterm *ERTS_RESTRICT ptr, Eterm hdr, Eterm **h if (is_flatmap_header(hdr)) nelts+=flatmap_get_size(ptr) + 1; else nelts += hashmap_bitcount(MAP_HEADER_VAL(hdr)); break; - case FUN_SUBTAG: nelts+=((ErlFunThing*)(ptr))->num_free; break; + case FUN_SUBTAG: nelts+=fun_num_free((ErlFunThing*)(ptr)); break; } gval = make_boxed(htop); *orig = gval; diff --git a/erts/emulator/beam/erl_process_dump.c b/erts/emulator/beam/erl_process_dump.c index df3e21386f..7fb3e0ded2 100644 --- a/erts/emulator/beam/erl_process_dump.c +++ b/erts/emulator/beam/erl_process_dump.c @@ -729,7 +729,7 @@ dump_externally(fmtfn_t to, void *to_arg, Eterm term) * The crashdump_viewer does not allow inspection of them anyway. */ ErlFunThing* funp = (ErlFunThing *) fun_val(term); - Uint num_free = funp->num_free; + Uint num_free = fun_num_free(funp); Uint i; for (i = 0; i < num_free; i++) { @@ -1035,7 +1035,7 @@ dump_module_literals(fmtfn_t to, void *to_arg, ErtsLiteralArea* lit_area) size = 1 + header_arity(w); switch (w & _HEADER_SUBTAG_MASK) { case FUN_SUBTAG: - size += 1 + ((ErlFunThing*)(htop))->num_free; + size += 1 + fun_num_free((ErlFunThing*)(htop)); break; case MAP_SUBTAG: if (is_flatmap_header(w)) { diff --git a/erts/emulator/beam/erl_term.h b/erts/emulator/beam/erl_term.h index d8f48bbef2..97f755388a 100644 --- a/erts/emulator/beam/erl_term.h +++ b/erts/emulator/beam/erl_term.h @@ -299,8 +299,10 @@ _ET_DECLARE_CHECKED(Uint,atom_val,Eterm) /* header (arityval or thing) access methods */ #define _make_header(sz,tag) ((Uint)(((Uint)(sz) << _HEADER_ARITY_OFFS) + (tag))) #define is_header(x) (((x) & _TAG_PRIMARY_MASK) == TAG_PRIMARY_HEADER) -#define _unchecked_header_arity(x) \ - (is_map_header(x) ? MAP_HEADER_ARITY(x) : ((x) >> _HEADER_ARITY_OFFS)) +#define _unchecked_header_arity(x) \ + (is_map_header(x) ? MAP_HEADER_ARITY(x) : \ + (is_fun_header(x) ? (ERL_FUN_SIZE - 1) : \ + ((x) >> _HEADER_ARITY_OFFS))) _ET_DECLARE_CHECKED(Uint,header_arity,Eterm) #define header_arity(x) _ET_APPLY(header_arity,(x)) @@ -386,9 +388,35 @@ _ET_DECLARE_CHECKED(Eterm*,binary_val,Wterm) /* process binaries stuff (special case of binaries) */ #define HEADER_PROC_BIN _make_header(PROC_BIN_SIZE-1,_TAG_HEADER_REFC_BIN) -/* fun objects */ -#define HEADER_FUN _make_header(ERL_FUN_SIZE-1,_TAG_HEADER_FUN) -#define is_fun_header(x) ((x) == HEADER_FUN) +/* Fun objects. + * + * This has a special tag scheme to make the representation as compact as + * possible. For normal headers, we have: + * + * aaaaaaaaaaaaaaaa aaaaaaaaaatttt00 arity:26, tag:4 + * + * Since the arity and number of free variables are both limited to 255, and we + * only need one bit to signify whether the fun is local or external, we can + * fit all of that information in the header word. + * + * 0000000effffffff aaaaaaaa00010100 external:1, free:8, arity:8 + * + * Note that the lowest byte contains only the function subtag, and the next + * byte after that contains only the arity. This lets us combine the type + * and/or arity check into a single comparison without masking, by using 8- or + * 16-bit operations on the header word. */ + +#define FUN_HEADER_ARITY_OFFS (_HEADER_ARITY_OFFS + 2) +#define FUN_HEADER_NUM_FREE_OFFS (FUN_HEADER_ARITY_OFFS + 8) +#define FUN_HEADER_EXTERNAL_OFFS (FUN_HEADER_NUM_FREE_OFFS + 8) + +#define MAKE_FUN_HEADER(Arity, NumFree, External) \ + (_TAG_HEADER_FUN | \ + (((Arity)) << FUN_HEADER_ARITY_OFFS) | \ + (((NumFree)) << FUN_HEADER_NUM_FREE_OFFS) | \ + ((!!(External)) << FUN_HEADER_EXTERNAL_OFFS)) + +#define is_fun_header(x) (((x) & _HEADER_SUBTAG_MASK) == FUN_SUBTAG) #define make_fun(x) make_boxed((Eterm*)(x)) #define is_any_fun(x) (is_boxed((x)) && is_fun_header(*boxed_val((x)))) #define is_not_any_fun(x) (!is_any_fun((x))) diff --git a/erts/emulator/beam/erl_term_hashing.c b/erts/emulator/beam/erl_term_hashing.c index e13c5e9773..7aa10c9a85 100644 --- a/erts/emulator/beam/erl_term_hashing.c +++ b/erts/emulator/beam/erl_term_hashing.c @@ -231,7 +231,7 @@ tail_recur: if (is_local_fun(funp)) { ErlFunEntry* fe = funp->entry.fun; - Uint num_free = funp->num_free; + Uint num_free = fun_num_free(funp); hash = hash * FUNNY_NUMBER10 + num_free; hash = hash*FUNNY_NUMBER1 + @@ -1160,7 +1160,7 @@ make_hash2_helper(Eterm term_param, const int can_trap, Eterm* state_mref_write_ if (is_local_fun(funp)) { ErlFunEntry* fe = funp->entry.fun; ErtsMakeHash2Context_FUN_SUBTAG ctx = { - .num_free = funp->num_free, + .num_free = fun_num_free(funp), .bptr = NULL}; UINT32_HASH_2 @@ -1901,7 +1901,7 @@ make_internal_hash(Eterm term, erts_ihash_t salt) if (is_local_fun(funp)) { const ErlFunEntry *fe = funp->entry.fun; - Uint num_free = funp->num_free; + Uint num_free = fun_num_free(funp); IHASH_MIX_ALPHA_2F32(IHASH_TYPE_LOCAL_FUN, num_free); IHASH_MIX_BETA_2F32(fe->index, fe->old_uniq); diff --git a/erts/emulator/beam/external.c b/erts/emulator/beam/external.c index 085d9ba603..5babb7c26e 100644 --- a/erts/emulator/beam/external.c +++ b/erts/emulator/beam/external.c @@ -3882,20 +3882,20 @@ enc_term_int(TTBEncodeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj, byte* ep, WSTACK_PUSH2(s, ENC_PATCH_FUN_SIZE, (UWord) ep); /* Position for patching in size */ ep += 4; - *ep = funp->arity; + *ep = fun_arity(funp); ep += 1; sys_memcpy(ep, fe->uniq, 16); ep += 16; put_int32(fe->index, ep); ep += 4; - put_int32((Uint32)funp->num_free, ep); + put_int32((Uint32)fun_num_free(funp), ep); ep += 4; ep = enc_atom(acmp, fe->module, ep, dflags); ep = enc_term(acmp, make_small(fe->old_index), ep, dflags, off_heap); ep = enc_term(acmp, make_small(fe->old_uniq), ep, dflags, off_heap); ep = enc_pid(acmp, erts_init_process_id, ep, dflags); - for (ei = funp->num_free-1; ei >= 0; ei--) { + for (ei = fun_num_free(funp)-1; ei >= 0; ei--) { WSTACK_PUSH2(s, ENC_TERM, (UWord) funp->env[ei]); } } else { @@ -4979,9 +4979,7 @@ dec_term_atom_common: ep += 4; hp += ERL_FUN_SIZE; hp += num_free; - funp->thing_word = HEADER_FUN; - funp->num_free = num_free; - funp->external = 0; + funp->thing_word = MAKE_FUN_HEADER(arity, num_free, 0); *objp = make_fun(funp); /* Module */ @@ -5026,7 +5024,6 @@ dec_term_atom_common: funp->entry.fun = erts_put_fun_entry2(module, old_uniq, old_index, uniq, index, arity); - funp->arity = arity; hp = factory->hp; /* Environment */ @@ -5596,11 +5593,11 @@ encode_size_struct_int(TTBSizeContext* ctx, ErtsAtomCacheMap *acmp, Eterm obj, result += encode_pid_size(acmp, erts_init_process_id, dflags); result += encode_atom_size(acmp, funp->entry.fun->module, dflags); result += 2 * (1+4); /* Index, Uniq */ - if (funp->num_free > 1) { + if (fun_num_free(funp) > 1) { WSTACK_PUSH2(s, (UWord) (funp->env + 1), - (UWord) TERM_ARRAY_OP(funp->num_free-1)); + (UWord) TERM_ARRAY_OP(fun_num_free(funp)-1)); } - if (funp->num_free != 0) { + if (fun_num_free(funp) != 0) { obj = funp->env[0]; continue; /* big loop */ } diff --git a/erts/emulator/beam/generators.tab b/erts/emulator/beam/generators.tab index ae806e2062..435590c613 100644 --- a/erts/emulator/beam/generators.tab +++ b/erts/emulator/beam/generators.tab @@ -318,12 +318,9 @@ MakeLiteralLambda(Op, Index, DstType, DstVal) { * created by the user. We also disable deduplication to prevent it * from colliding with other placeholder lambdas of the same arity. */ funp = (ErlFunThing*)tmp_hp; - funp->thing_word = HEADER_FUN; + funp->thing_word = MAKE_FUN_HEADER(entry->arity, 0, 1); funp->entry.exp = NULL; funp->next = NULL; - funp->arity = entry->arity; - funp->num_free = 0; - funp->external = 1; literal = beamfile_add_literal(&S->beam, make_fun(tmp_hp), 0); S->lambda_literals[$Index] = literal; diff --git a/erts/emulator/beam/jit/arm/beam_asm.hpp b/erts/emulator/beam/jit/arm/beam_asm.hpp index a35c4a543f..ab162f951a 100644 --- a/erts/emulator/beam/jit/arm/beam_asm.hpp +++ b/erts/emulator/beam/jit/arm/beam_asm.hpp @@ -1091,8 +1091,7 @@ protected: arm::Mem emit_fixed_apply(const ArgWord &arity, bool includeI); arm::Gp emit_call_fun(bool skip_box_test = false, - bool skip_fun_test = false, - bool skip_arity_test = false); + bool skip_header_test = false); void emit_is_boxed(Label Fail, arm::Gp Src) { BeamAssembler::emit_is_boxed(Fail, Src); diff --git a/erts/emulator/beam/jit/arm/instr_common.cpp b/erts/emulator/beam/jit/arm/instr_common.cpp index f131e44b89..dc74eb27fe 100644 --- a/erts/emulator/beam/jit/arm/instr_common.cpp +++ b/erts/emulator/beam/jit/arm/instr_common.cpp @@ -1015,8 +1015,8 @@ void BeamModuleAssembler::emit_is_function(const ArgLabel &Fail, comment("skipped header test since we know it's a fun when boxed"); } else { arm::Gp boxed_ptr = emit_ptr_val(TMP1, src.reg); - a.ldur(TMP1, emit_boxed_val(boxed_ptr)); - a.cmp(TMP1, imm(HEADER_FUN)); + a.ldurb(TMP1.w(), emit_boxed_val(boxed_ptr)); + a.cmp(TMP1, imm(FUN_SUBTAG)); a.b_ne(resolve_beam_label(Fail, disp1MB)); } } @@ -1058,16 +1058,9 @@ void BeamModuleAssembler::emit_is_function2(const ArgLabel &Fail, arm::Gp boxed_ptr = emit_ptr_val(TMP1, src.reg); - if (masked_types<BeamTypeId::MaybeBoxed>(Src) == BeamTypeId::Fun) { - comment("skipped header test since we know it's a fun when boxed"); - } else { - a.ldur(TMP2, emit_boxed_val(boxed_ptr)); - a.cmp(TMP2, imm(HEADER_FUN)); - a.b_ne(resolve_beam_label(Fail, disp1MB)); - } - - a.ldurb(TMP2.w(), emit_boxed_val(boxed_ptr, offsetof(ErlFunThing, arity))); - emit_branch_if_ne(TMP2, arity, resolve_beam_label(Fail, dispUnknown)); + a.ldurh(TMP2.w(), emit_boxed_val(boxed_ptr)); + a.cmp(TMP2, imm(MAKE_FUN_HEADER(arity, 0, 0) & 0xFFFF)); + a.b_ne(resolve_beam_label(Fail, disp1MB)); } void BeamModuleAssembler::emit_is_integer(const ArgLabel &Fail, diff --git a/erts/emulator/beam/jit/arm/instr_fun.cpp b/erts/emulator/beam/jit/arm/instr_fun.cpp index c7a32188cb..fd6bce467c 100644 --- a/erts/emulator/beam/jit/arm/instr_fun.cpp +++ b/erts/emulator/beam/jit/arm/instr_fun.cpp @@ -25,7 +25,7 @@ * Keep in mind that this runs in the limbo between caller and callee. It must * not clobber LR (x30). * - * ARG3 = arity + * ARG3 = lower 16 bits of expected header, containing FUN_SUBTAG and arity * ARG4 = fun thing * ARG5 = address of the call_fun instruction that got us here. Note that we * can't use LR (x30) for this because tail calls point elsewhere. */ @@ -40,7 +40,8 @@ void BeamGlobalAssembler::emit_unloaded_fun() { a.mov(ARG1, c_p); load_x_reg_array(ARG2); - /* ARG3 and ARG4 have already been set. */ + a.lsr(ARG3, ARG3, imm(FUN_HEADER_ARITY_OFFS)); + /* ARG4 has already been set. */ runtime_call<4>(beam_jit_handle_unloaded_fun); emit_leave_runtime<Update::eHeapAlloc | Update::eXRegs | @@ -63,7 +64,7 @@ void BeamGlobalAssembler::emit_unloaded_fun() { /* Handles errors for `call_fun`. Assumes that we're running on the Erlang * stack with a valid stack frame. * - * ARG3 = arity + * ARG3 = lower 16 bits of expected header, containing FUN_SUBTAG and arity * ARG4 = fun thing * ARG5 = address of the call_fun instruction that got us here. Note that we * can't use LR (x30) for this because tail calls point elsewhere. */ @@ -73,8 +74,8 @@ void BeamGlobalAssembler::emit_handle_call_fun_error() { emit_is_boxed(bad_fun, ARG4); arm::Gp fun_thing = emit_ptr_val(TMP1, ARG4); - a.ldur(TMP1, emit_boxed_val(fun_thing)); - a.cmp(TMP1, imm(HEADER_FUN)); + a.ldurb(TMP1.w(), emit_boxed_val(fun_thing)); + a.cmp(TMP1, imm(FUN_SUBTAG)); a.b_eq(bad_arity); a.bind(bad_fun); @@ -96,7 +97,7 @@ void BeamGlobalAssembler::emit_handle_call_fun_error() { a.mov(ARG1, c_p); load_x_reg_array(ARG2); - /* ARG3 is already set */ + a.lsr(ARG3, ARG3, imm(FUN_HEADER_ARITY_OFFS)); runtime_call<3>(beam_jit_build_argument_list); emit_leave_runtime<Update::eHeapAlloc | Update::eXRegs>(); @@ -312,6 +313,11 @@ void BeamGlobalAssembler::emit_apply_fun_shared() { a.bind(finished); { + /* Make the lower 16 bits of ARG3 equal those of the header word of all + * funs with the same arity. */ + a.lsl(ARG3, ARG3, imm(FUN_HEADER_ARITY_OFFS)); + a.add(ARG3, ARG3, imm(FUN_SUBTAG)); + emit_leave_runtime<Update::eXRegs>(); a.ret(a64::x30); } @@ -334,67 +340,56 @@ void BeamModuleAssembler::emit_i_apply_fun_only() { } /* Assumes that: - * ARG3 = arity + * ARG3 = lower 16 bits of expected header, containing FUN_SUBTAG and arity * ARG4 = fun thing */ arm::Gp BeamModuleAssembler::emit_call_fun(bool skip_box_test, - bool skip_fun_test, - bool skip_arity_test) { - const bool never_fails = skip_box_test && skip_fun_test && skip_arity_test; + bool skip_header_test) { + const bool can_fail = !(skip_box_test && skip_header_test); Label next = a.newLabel(); /* Speculatively untag the ErlFunThing. */ emit_untag_ptr(TMP2, ARG4); - if (!never_fails) { - /* Load the error fragment into TMP3 so we can CSEL ourselves there on + if (can_fail) { + /* Load the error fragment into TMP1 so that we'll land there on any * error. */ - a.adr(TMP3, resolve_fragment(ga->get_handle_call_fun_error(), disp1MB)); + a.adr(TMP1, resolve_fragment(ga->get_handle_call_fun_error(), disp1MB)); } /* The `handle_call_fun_error` and `unloaded_fun` fragments expect current - * PC in ARG5. */ + * PC in ARG5. Note that the latter requires that we do this even if we + * know the call never fails. */ a.adr(ARG5, next); - if (!skip_box_test) { + if (skip_box_test) { + comment("skipped box test since source is always boxed"); + } else { /* As emit_is_boxed(), but explicitly sets ZF so we can rely on that * for error checking in `next`. */ a.tst(ARG4, imm(_TAG_PRIMARY_MASK - TAG_PRIMARY_BOXED)); a.b_ne(next); - } else { - comment("skipped box test since source is always boxed"); } - if (!skip_fun_test) { + if (skip_header_test) { + comment("skipped fun/arity test since source is always a fun of the " + "right arity when boxed"); + a.ldr(ARG1, arm::Mem(TMP2, offsetof(ErlFunThing, entry))); + } else { /* Load header word and `ErlFunThing->entry`. We can safely do this * before testing the header because boxed terms are guaranteed to be * at least two words long. */ ERTS_CT_ASSERT_FIELD_PAIR(ErlFunThing, thing_word, entry); - a.ldp(TMP1, ARG1, arm::Mem(TMP2)); + a.ldp(TMP2, ARG1, arm::Mem(TMP2)); - a.cmp(TMP1, imm(HEADER_FUN)); + /* Combined fun type and arity test. */ + a.cmp(ARG3, TMP2, arm::uxth(0)); a.b_ne(next); - } else { - comment("skipped fun test since source is always a fun when boxed"); - a.ldr(ARG1, arm::Mem(TMP2, offsetof(ErlFunThing, entry))); - } - - if (!skip_arity_test) { - a.ldrb(TMP2.w(), arm::Mem(TMP2, offsetof(ErlFunThing, arity))); - a.cmp(TMP2, ARG3); - } else { - comment("skipped arity test since source always has right arity"); } a.ldr(TMP1, emit_setup_dispatchable_call(ARG1)); - /* Assumes that ZF is set on success and clear on error, overwriting our - * destination with the error fragment's address. */ a.bind(next); - if (!never_fails) { - a.csel(TMP1, TMP1, TMP3, imm(arm::CondCode::kEQ)); - } - return TMP1; } @@ -404,12 +399,15 @@ void BeamModuleAssembler::emit_i_call_fun2(const ArgVal &Tag, mov_arg(ARG4, Func); if (Tag.isAtom()) { - mov_imm(ARG3, Arity.get()); + /* Make the lower 16 bits of ARG3 equal those of the header word of all + * funs with the same arity. */ + mov_imm(ARG3, MAKE_FUN_HEADER(Arity.get(), 0, 0) & 0xFFFF); - auto target = emit_call_fun( - always_one_of<BeamTypeId::AlwaysBoxed>(Func), - masked_types<BeamTypeId::MaybeBoxed>(Func) == BeamTypeId::Fun, - Tag.as<ArgAtom>().get() == am_safe); + ASSERT(Tag.as<ArgImmed>().get() != am_safe || + exact_type<BeamTypeId::Fun>(Func)); + auto target = + emit_call_fun(always_one_of<BeamTypeId::AlwaysBoxed>(Func), + Tag.as<ArgAtom>().get() == am_safe); erlang_call(target); } else { @@ -425,12 +423,15 @@ void BeamModuleAssembler::emit_i_call_fun2_last(const ArgVal &Tag, mov_arg(ARG4, Func); if (Tag.isAtom()) { - mov_imm(ARG3, Arity.get()); - - auto target = emit_call_fun( - always_one_of<BeamTypeId::AlwaysBoxed>(Func), - masked_types<BeamTypeId::MaybeBoxed>(Func) == BeamTypeId::Fun, - Tag.as<ArgAtom>().get() == am_safe); + /* Make the lower 16 bits of ARG3 equal those of the header word of all + * funs with the same arity. */ + mov_imm(ARG3, MAKE_FUN_HEADER(Arity.get(), 0, 0) & 0xFFFF); + + ASSERT(Tag.as<ArgImmed>().get() != am_safe || + exact_type<BeamTypeId::Fun>(Func)); + auto target = + emit_call_fun(always_one_of<BeamTypeId::AlwaysBoxed>(Func), + Tag.as<ArgAtom>().get() == am_safe); emit_deallocate(Deallocate); emit_leave_erlang_frame(); diff --git a/erts/emulator/beam/jit/asm_load.c b/erts/emulator/beam/jit/asm_load.c index f6e1f1c6ab..93a5971a21 100644 --- a/erts/emulator/beam/jit/asm_load.c +++ b/erts/emulator/beam/jit/asm_load.c @@ -997,14 +997,14 @@ void beam_load_finalize_code(LoaderState *stp, literal = beamfile_get_literal(&stp->beam, stp->lambda_literals[i]); funp = (ErlFunThing *)fun_val(literal); - ASSERT(funp->external == 1); funp->entry.fun = fun_entry; funp->next = literal_area->off_heap; literal_area->off_heap = (struct erl_off_heap_header *)funp; - funp->external = 0; + ASSERT(funp->thing_word & (1 << FUN_HEADER_EXTERNAL_OFFS)); + funp->thing_word &= ~(1 << FUN_HEADER_EXTERNAL_OFFS); erts_refc_inc(&fun_entry->refc, 2); } diff --git a/erts/emulator/beam/jit/x86/beam_asm.hpp b/erts/emulator/beam/jit/x86/beam_asm.hpp index dc34ef4635..8163ceec06 100644 --- a/erts/emulator/beam/jit/x86/beam_asm.hpp +++ b/erts/emulator/beam/jit/x86/beam_asm.hpp @@ -1196,8 +1196,7 @@ protected: x86::Mem emit_fixed_apply(const ArgWord &arity, bool includeI); x86::Gp emit_call_fun(bool skip_box_test = false, - bool skip_fun_test = false, - bool skip_arity_test = false); + bool skip_header_test = false); void emit_is_boxed(Label Fail, x86::Gp Src, Distance dist = dLong) { BeamAssembler::emit_is_boxed(Fail, Src, dist); diff --git a/erts/emulator/beam/jit/x86/instr_common.cpp b/erts/emulator/beam/jit/x86/instr_common.cpp index 9bcbfe685e..5b3e595bbc 100644 --- a/erts/emulator/beam/jit/x86/instr_common.cpp +++ b/erts/emulator/beam/jit/x86/instr_common.cpp @@ -1009,8 +1009,7 @@ void BeamModuleAssembler::emit_is_function(const ArgLabel &Fail, comment("skipped header test since we know it's a fun when boxed"); } else { x86::Gp boxed_ptr = emit_ptr_val(RET, RET); - a.mov(RETd, emit_boxed_val(boxed_ptr, 0, sizeof(Uint32))); - a.cmp(RET, imm(HEADER_FUN)); + a.cmp(emit_boxed_val(boxed_ptr, 0, sizeof(byte)), imm(FUN_SUBTAG)); a.jne(resolve_beam_label(Fail)); } } @@ -1048,16 +1047,10 @@ void BeamModuleAssembler::emit_is_function2(const ArgLabel &Fail, x86::Gp boxed_ptr = emit_ptr_val(ARG1, ARG1); - if (masked_types<BeamTypeId::MaybeBoxed>(Src) == BeamTypeId::Fun) { - comment("skipped header test since we know it's a fun when boxed"); - } else { - a.mov(RETd, emit_boxed_val(boxed_ptr, 0, sizeof(Uint32))); - a.cmp(RETd, imm(HEADER_FUN)); - a.jne(resolve_beam_label(Fail)); - } - - a.cmp(emit_boxed_val(boxed_ptr, offsetof(ErlFunThing, arity), sizeof(byte)), - imm(arity)); + /* Combined header word and arity check: both the tag and arity live in the + * lowest 16 bits. */ + a.cmp(emit_boxed_val(boxed_ptr, 0, sizeof(Uint16)), + imm(MAKE_FUN_HEADER(arity, 0, 0) & 0xFFFF)); a.jne(resolve_beam_label(Fail)); } diff --git a/erts/emulator/beam/jit/x86/instr_fun.cpp b/erts/emulator/beam/jit/x86/instr_fun.cpp index 903ecef49b..e0413977c2 100644 --- a/erts/emulator/beam/jit/x86/instr_fun.cpp +++ b/erts/emulator/beam/jit/x86/instr_fun.cpp @@ -22,7 +22,7 @@ /* Calls to functions that are being purged (but haven't finished) land here. * - * ARG3 = arity + * ARG3 = lower 16 bits of expected header, containing FUN_SUBTAG and arity * ARG4 = fun thing * ARG5 = current PC */ void BeamGlobalAssembler::emit_unloaded_fun() { @@ -36,7 +36,8 @@ void BeamGlobalAssembler::emit_unloaded_fun() { a.mov(ARG1, c_p); load_x_reg_array(ARG2); - /* ARG3 and ARG4 have already been set. */ + a.shr(ARG3, imm(FUN_HEADER_ARITY_OFFS)); + /* ARG4 has already been set. */ runtime_call<4>(beam_jit_handle_unloaded_fun); emit_leave_runtime<Update::eHeapAlloc | Update::eReductions | @@ -60,18 +61,17 @@ void BeamGlobalAssembler::emit_unloaded_fun() { /* Handles errors for `call_fun`. * - * ARG3 = arity + * ARG3 = lower 16 bits of expected header, containing FUN_SUBTAG and arity * ARG4 = fun thing * ARG5 = current PC */ void BeamGlobalAssembler::emit_handle_call_fun_error() { Label bad_arity = a.newLabel(), bad_fun = a.newLabel(); emit_enter_frame(); - emit_is_boxed(bad_fun, ARG4); x86::Gp fun_thing = emit_ptr_val(RET, ARG4); - a.cmp(emit_boxed_val(fun_thing), imm(HEADER_FUN)); + a.cmp(emit_boxed_val(fun_thing, 0, sizeof(byte)), imm(FUN_SUBTAG)); a.short_().je(bad_arity); a.bind(bad_fun); @@ -97,7 +97,7 @@ void BeamGlobalAssembler::emit_handle_call_fun_error() { a.mov(ARG1, c_p); load_x_reg_array(ARG2); - /* ARG3 is already set. */ + a.shr(ARG3, imm(FUN_HEADER_ARITY_OFFS)); runtime_call<3>(beam_jit_build_argument_list); emit_leave_runtime<Update::eHeapAlloc>(); @@ -285,6 +285,11 @@ void BeamGlobalAssembler::emit_apply_fun_shared() { a.bind(finished); + /* Make the lower 16 bits of ARG3 equal those of the header word of all + * funs with the same arity. */ + a.shl(ARG3, imm(FUN_HEADER_ARITY_OFFS)); + a.or_(ARG3, imm(FUN_SUBTAG)); + emit_leave_frame(); a.ret(); } @@ -311,63 +316,49 @@ void BeamModuleAssembler::emit_i_apply_fun_only() { } /* Assumes that: - * ARG3 = arity + * ARG3 = lower 16 bits of expected header, containing FUN_SUBTAG and arity * ARG4 = fun thing */ x86::Gp BeamModuleAssembler::emit_call_fun(bool skip_box_test, - bool skip_fun_test, - bool skip_arity_test) { - const bool never_fails = skip_box_test && skip_fun_test && skip_arity_test; + bool skip_header_test) { + const bool can_fail = !(skip_box_test && skip_header_test); Label next = a.newLabel(); /* Speculatively strip the literal tag when needed. */ x86::Gp fun_thing = emit_ptr_val(RET, ARG4); - if (!never_fails) { - /* Load the error fragment into ARG2 so we can CMOV ourselves there on + if (can_fail) { + /* Load the error fragment into ARG1 so that we'll land there on any * error. */ - a.mov(ARG2, ga->get_handle_call_fun_error()); + a.mov(ARG1, ga->get_handle_call_fun_error()); } /* The `handle_call_fun_error` and `unloaded_fun` fragments expect current - * PC in ARG5. */ + * PC in ARG5. Note that the latter requires that we do this even if we + * know the call never fails. */ a.lea(ARG5, x86::qword_ptr(next)); - if (!skip_box_test) { + if (skip_box_test) { + comment("skipped box test since source is always boxed"); + } else { /* As emit_is_boxed(), but explicitly sets ZF so we can rely on that * for error checking in `next`. */ a.test(ARG4d, imm(_TAG_PRIMARY_MASK - TAG_PRIMARY_BOXED)); a.short_().jne(next); - } else { - comment("skipped box test since source is always boxed"); } - if (skip_fun_test) { - comment("skipped fun test since source is always a fun when boxed"); + if (skip_header_test) { + comment("skipped fun/arity test since source is always a fun of the " + "right arity when boxed"); } else { - a.cmp(emit_boxed_val(fun_thing), imm(HEADER_FUN)); + a.cmp(emit_boxed_val(fun_thing, 0, sizeof(Uint16)), ARG3.r16()); a.short_().jne(next); } - if (skip_arity_test) { - comment("skipped arity test since source always has right arity"); - } else { - a.cmp(emit_boxed_val(fun_thing, - offsetof(ErlFunThing, arity), - sizeof(byte)), - ARG3.r8()); - } - a.mov(RET, emit_boxed_val(fun_thing, offsetof(ErlFunThing, entry))); a.mov(ARG1, emit_setup_dispatchable_call(RET)); a.bind(next); - if (!never_fails) { - /* Assumes that ZF is set on success and clear on error, overwriting - * our destination with the error fragment's address. */ - a.cmovne(ARG1, ARG2); - } - return ARG1; } @@ -377,12 +368,15 @@ void BeamModuleAssembler::emit_i_call_fun2(const ArgVal &Tag, mov_arg(ARG4, Func); if (Tag.isImmed()) { - mov_imm(ARG3, Arity.get()); + /* Make the lower 16 bits of ARG3 equal those of the header word of all + * funs with the same arity. */ + mov_imm(ARG3, MAKE_FUN_HEADER(Arity.get(), 0, 0) & 0xFFFF); - auto target = emit_call_fun( - always_one_of<BeamTypeId::AlwaysBoxed>(Func), - masked_types<BeamTypeId::MaybeBoxed>(Func) == BeamTypeId::Fun, - Tag.as<ArgImmed>().get() == am_safe); + ASSERT(Tag.as<ArgImmed>().get() != am_safe || + exact_type<BeamTypeId::Fun>(Func)); + auto target = + emit_call_fun(always_one_of<BeamTypeId::AlwaysBoxed>(Func), + Tag.as<ArgImmed>().get() == am_safe); erlang_call(target, ARG6); } else { @@ -398,12 +392,15 @@ void BeamModuleAssembler::emit_i_call_fun2_last(const ArgVal &Tag, mov_arg(ARG4, Func); if (Tag.isImmed()) { - mov_imm(ARG3, Arity.get()); - - auto target = emit_call_fun( - always_one_of<BeamTypeId::AlwaysBoxed>(Func), - masked_types<BeamTypeId::MaybeBoxed>(Func) == BeamTypeId::Fun, - Tag.as<ArgImmed>().get() == am_safe); + /* Make the lower 16 bits of ARG3 equal those of the header word of all + * funs with the same arity. */ + mov_imm(ARG3, MAKE_FUN_HEADER(Arity.get(), 0, 0) & 0xFFFF); + + ASSERT(Tag.as<ArgImmed>().get() != am_safe || + exact_type<BeamTypeId::Fun>(Func)); + auto target = + emit_call_fun(always_one_of<BeamTypeId::AlwaysBoxed>(Func), + Tag.as<ArgImmed>().get() == am_safe); emit_deallocate(Deallocate); emit_leave_frame(); diff --git a/erts/emulator/beam/utils.c b/erts/emulator/beam/utils.c index 8e2b13136b..208675f865 100644 --- a/erts/emulator/beam/utils.c +++ b/erts/emulator/beam/utils.c @@ -1220,6 +1220,10 @@ tailrecur_ne: f1 = (ErlFunThing *) fun_val(a); f2 = (ErlFunThing *) fun_val(b); + if (f1->thing_word != f2->thing_word) { + goto not_equal; + } + if (is_local_fun(f1) && is_local_fun(f2)) { ErlFunEntry *fe1, *fe2; @@ -1228,12 +1232,11 @@ tailrecur_ne: if (fe1->module != fe2->module || fe1->index != fe2->index || - fe1->old_uniq != fe2->old_uniq || - f1->num_free != f2->num_free) { + fe1->old_uniq != fe2->old_uniq) { goto not_equal; } - if ((sz = f1->num_free) == 0) { + if ((sz = fun_num_free(f1)) == 0) { goto pop_next; } @@ -2057,13 +2060,14 @@ tailrecur_ne: RETURN_NEQ(diff); } - diff = f1->num_free - f2->num_free; + diff = fun_num_free(f1) - fun_num_free(f2); if (diff != 0) { RETURN_NEQ(diff); } - i = f1->num_free; + i = fun_num_free(f1); if (i == 0) goto pop_next; + aa = f1->env; bb = f2->env; goto term_array; diff --git a/erts/emulator/test/erts_debug_SUITE.erl b/erts/emulator/test/erts_debug_SUITE.erl index 3240b800d6..d794cade2c 100644 --- a/erts/emulator/test/erts_debug_SUITE.erl +++ b/erts/emulator/test/erts_debug_SUITE.erl @@ -82,7 +82,7 @@ test_size(Config) when is_list(Config) -> %% Fun environment size = 0 (the smallest fun possible) SimplestFun = fun() -> ok end, - FunSz0 = 4, + FunSz0 = 3, FunSz0 = do_test_size(SimplestFun), %% Fun environment size = 1 diff --git a/erts/emulator/test/trace_call_memory_SUITE.erl b/erts/emulator/test/trace_call_memory_SUITE.erl index a18dbdabf1..e8cec4e999 100644 --- a/erts/emulator/test/trace_call_memory_SUITE.erl +++ b/erts/emulator/test/trace_call_memory_SUITE.erl @@ -308,8 +308,8 @@ spawn_memory_lambda(Config) when is_list(Config) -> MRef = monitor(process, Pid), receive {'DOWN', MRef, process, Pid, _} -> ok end, 1 = erlang:trace(self(), false, [all]), - %% 16-elements list translates into 34-words for spawn, and 6 more words for apply itself - {call_memory, [{Pid, 1, 39}]} = erlang:trace_info({erlang, apply, 2}, call_memory). + %% 16-elements list translates into 34-words for spawn, and 4 more words for apply itself + {call_memory, [{Pid, 1, 38}]} = erlang:trace_info({erlang, apply, 2}, call_memory). spawn_memory_internal(Array) -> Array. -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor