Skip to content

Commit

Permalink
Merge pull request #8674 from jhogberg/john/erts/versioned-fun-tables
Browse files Browse the repository at this point in the history
erts: Refactor the export table, and optimize fun table inserts

OTP-19185
  • Loading branch information
jhogberg authored Aug 9, 2024
2 parents a9c6285 + e53d572 commit dc17a15
Show file tree
Hide file tree
Showing 62 changed files with 1,050 additions and 1,204 deletions.
5 changes: 3 additions & 2 deletions erts/emulator/beam/beam_bif_load.c
Original file line number Diff line number Diff line change
Expand Up @@ -1762,8 +1762,9 @@ erts_purge_state_add_fun(ErlFunEntry *fe)
purge_state.funs[purge_state.fe_count++] = fe;
}

Export *
erts_suspend_process_on_pending_purge_lambda(Process *c_p, ErlFunEntry* fe)
const Export *
erts_suspend_process_on_pending_purge_lambda(Process *c_p,
const ErlFunEntry* fe)
{
erts_mtx_lock(&purge_state.mtx);
if (purge_state.module == fe->module) {
Expand Down
5 changes: 3 additions & 2 deletions erts/emulator/beam/beam_code.h
Original file line number Diff line number Diff line change
Expand Up @@ -145,8 +145,9 @@ void erts_release_literal_area(struct ErtsLiteralArea_* literal_area);

struct erl_fun_entry;
void erts_purge_state_add_fun(struct erl_fun_entry *fe);
Export *erts_suspend_process_on_pending_purge_lambda(Process *c_p,
struct erl_fun_entry*);
const Export *
erts_suspend_process_on_pending_purge_lambda(Process *c_p,
const struct erl_fun_entry*);

/*
* MFA event debug "tracing" usage:
Expand Down
35 changes: 16 additions & 19 deletions erts/emulator/beam/beam_common.c
Original file line number Diff line number Diff line change
Expand Up @@ -1275,11 +1275,13 @@ build_stacktrace(Process* c_p, Eterm exc) {
return res;
}

Export*
call_error_handler(Process* p, const ErtsCodeMFA *mfa, Eterm* reg, Eterm func)
const Export *call_error_handler(Process* p,
const ErtsCodeMFA *mfa,
Eterm* reg,
Eterm func)
{
const Export* ep;
Eterm* hp;
Export* ep;
int arity;
Eterm args;
Uint sz;
Expand Down Expand Up @@ -1323,10 +1325,10 @@ call_error_handler(Process* p, const ErtsCodeMFA *mfa, Eterm* reg, Eterm func)
return ep;
}

static Export*
static const Export *
apply_setup_error_handler(Process* p, Eterm module, Eterm function, Uint arity, Eterm* reg)
{
Export* ep;
const Export *ep;

/*
* Find the export table index for the error handler. Return NULL if
Expand Down Expand Up @@ -1364,7 +1366,7 @@ apply_setup_error_handler(Process* p, Eterm module, Eterm function, Uint arity,
}

static ERTS_INLINE void
apply_bif_error_adjustment(Process *p, Export *ep,
apply_bif_error_adjustment(Process *p, const Export *ep,
Eterm *reg, Uint arity,
ErtsCodePtr I, Uint stack_offset)
{
Expand Down Expand Up @@ -1452,11 +1454,11 @@ apply_bif_error_adjustment(Process *p, Export *ep,
}
}

Export*
const Export *
apply(Process* p, Eterm* reg, ErtsCodePtr I, Uint stack_offset)
{
const Export *ep;
int arity;
Export* ep;
Eterm tmp;
Eterm module = reg[0];
Eterm function = reg[1];
Expand Down Expand Up @@ -1552,11 +1554,11 @@ apply(Process* p, Eterm* reg, ErtsCodePtr I, Uint stack_offset)
return ep;
}

Export*
const Export *
fixed_apply(Process* p, Eterm* reg, Uint arity,
ErtsCodePtr I, Uint stack_offset)
{
Export* ep;
const Export *ep;
Eterm module;
Eterm function;

Expand Down Expand Up @@ -1733,12 +1735,7 @@ call_fun(Process* p, /* Current process. */

if (ERTS_LIKELY(code_ptr != beam_unloaded_fun &&
fun_arity(funp) == arity)) {
/* Copy the free variables, skipping the FunRef in the environment.
*
* Note that we avoid using fun_num_free as it asserts that the
* argument is a local function, which we don't need to care about
* here. */
for (int i = 0, num_free = fun_env_size(funp) - 1; i < num_free; i++) {
for (int i = 0; i < fun_num_free(funp); i++) {
reg[i + arity] = funp->env[i];
}

Expand Down Expand Up @@ -1783,10 +1780,10 @@ call_fun(Process* p, /* Current process. */
p->fvalue = TUPLE2(hp, fun, args);
return NULL;
} else {
ErlFunEntry *fe;
const ErlFunEntry *fe;
const Export *ep;
Eterm module;
Module *modp;
Export *ep;

/* There is no module loaded that defines the fun, either because
* the fun is newly created from the external representation (the
Expand Down Expand Up @@ -2468,8 +2465,8 @@ int catchlevel(Process *p)
int
erts_is_builtin(Eterm Mod, Eterm Name, int arity)
{
const Export *ep;
Export e;
Export* ep;

if (Mod == am_erlang) {
/*
Expand Down
6 changes: 3 additions & 3 deletions erts/emulator/beam/beam_common.h
Original file line number Diff line number Diff line change
Expand Up @@ -250,11 +250,11 @@ do { \
ErtsCodeMFA *ubif2mfa(void* uf);
ErtsCodePtr handle_error(Process* c_p, ErtsCodePtr pc,
Eterm* reg, const ErtsCodeMFA* bif_mfa);
Export* call_error_handler(Process* p, const ErtsCodeMFA* mfa,
const Export *call_error_handler(Process* p, const ErtsCodeMFA* mfa,
Eterm* reg, Eterm func);
Export* fixed_apply(Process* p, Eterm* reg, Uint arity,
const Export *fixed_apply(Process* p, Eterm* reg, Uint arity,
ErtsCodePtr I, Uint offs);
Export* apply(Process* p, Eterm* reg, ErtsCodePtr I, Uint offs);
const Export *apply(Process* p, Eterm* reg, ErtsCodePtr I, Uint offs);
ErtsCodePtr call_fun(Process* p, int arity, Eterm* reg, Eterm args);
ErtsCodePtr apply_fun(Process* p, Eterm fun, Eterm args, Eterm* reg);
int is_function2(Eterm Term, Uint arity);
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/beam_debug.c
Original file line number Diff line number Diff line change
Expand Up @@ -346,10 +346,10 @@ erts_debug_disassemble_1(BIF_ALIST_1)
}
} else if (is_tuple(addr)) {
ErtsCodeIndex code_ix;
const Export *ep;
Module* modp;
Eterm mod;
Eterm name;
Export* ep;
Sint arity;
int n;

Expand Down
7 changes: 2 additions & 5 deletions erts/emulator/beam/beam_file.c
Original file line number Diff line number Diff line change
Expand Up @@ -1513,11 +1513,8 @@ static int marshal_allocation_list(BeamReader *reader, Sint *res) {
sum += FLOAT_SIZE_OBJECT * number;
break;
case 2:
LoadAssert(sum <= (ERTS_SINT32_MAX - (ERL_FUN_SIZE + 1) * number));

/* This is always a local fun, so we need to add one word to
* reserve space for its `FunRef`. */
sum += (ERL_FUN_SIZE + 1) * number;
LoadAssert(sum <= (ERTS_SINT32_MAX - ERL_FUN_SIZE * number));
sum += ERL_FUN_SIZE * number;
break;
default:
LoadError("Invalid allocation tag");
Expand Down
18 changes: 0 additions & 18 deletions erts/emulator/beam/beam_load.c
Original file line number Diff line number Diff line change
Expand Up @@ -679,24 +679,6 @@ erts_release_literal_area(ErtsLiteralArea* literal_area)
erts_bin_release(bin);
break;
}
case FUN_REF_SUBTAG:
{
ErlFunEntry* fe = ((FunRef*)oh)->entry;

/* All fun entries are NULL during module loading, before the
* code is finalized, so we need to tolerate it to avoid
* crashing in the prepared code destructor.
*
* Strictly speaking it would be nice to crash when we see this
* outside of loading, but it's too complicated to keep track
* of whether we are. */
if (fe != NULL) {
if (erts_refc_dectest(&fe->refc, 0) == 0) {
erts_erase_fun_entry(fe);
}
}
break;
}
case REF_SUBTAG:
{
ErtsMagicBinary *bptr;
Expand Down
25 changes: 18 additions & 7 deletions erts/emulator/beam/code_ix.c
Original file line number Diff line number Diff line change
Expand Up @@ -119,14 +119,25 @@ void erts_end_staging_code_ix(void)

void erts_commit_staging_code_ix(void)
{
/* We need these locks as we are about to make the next code index
* active. */
extern void export_staged_write_lock(void);
extern void export_staged_write_unlock(void);
extern void fun_staged_write_lock(void);
extern void fun_staged_write_unlock(void);
ErtsCodeIndex ix;
/* We need to this lock as we are now making the staging export table active */
export_staging_lock();
ix = erts_staging_code_ix();
erts_atomic32_set_nob(&the_active_code_index, ix);
ix = (ix + 1) % ERTS_NUM_CODE_IX;
erts_atomic32_set_nob(&the_staging_code_index, ix);
export_staging_unlock();

export_staged_write_lock();
fun_staged_write_lock();
{
ix = erts_staging_code_ix();
erts_atomic32_set_nob(&the_active_code_index, ix);
ix = (ix + 1) % ERTS_NUM_CODE_IX;
erts_atomic32_set_nob(&the_staging_code_index, ix);
}
fun_staged_write_unlock();
export_staged_write_unlock();

erts_tracer_nif_clear();
CIX_TRACE("activate");
}
Expand Down
Loading

0 comments on commit dc17a15

Please sign in to comment.