Skip to content

Commit

Permalink
Merge pull request #9406 from jhogberg/john/erts/hibernation-improvem…
Browse files Browse the repository at this point in the history
…ents

erts: Introduce hibernate/0 and simplify hibernate/3

OTP-19503
  • Loading branch information
jhogberg authored Feb 25, 2025
2 parents d24c732 + e3028f6 commit 2c47049
Show file tree
Hide file tree
Showing 14 changed files with 345 additions and 308 deletions.
92 changes: 11 additions & 81 deletions erts/emulator/beam/beam_common.c
Original file line number Diff line number Diff line change
Expand Up @@ -1612,88 +1612,19 @@ fixed_apply(Process* p, Eterm* reg, Uint arity,
return ep;
}

int
erts_hibernate(Process* c_p, Eterm* reg)
{
int arity;
Eterm tmp;
Eterm module = reg[0];
Eterm function = reg[1];
Eterm args = reg[2];

if (is_not_atom(module) || is_not_atom(function)) {
/*
* No need to test args here -- done below.
*/
error:
c_p->freason = BADARG;

error2:
reg[0] = module;
reg[1] = function;
reg[2] = args;
return 0;
}

arity = 0;
tmp = args;
while (is_list(tmp)) {
if (arity < MAX_REG) {
tmp = CDR(list_val(tmp));
arity++;
} else {
c_p->freason = SYSTEM_LIMIT;
goto error2;
}
}
if (is_not_nil(tmp)) { /* Must be well-formed list */
goto error;
}
void erts_hibernate(Process *c_p, Eterm *regs, int arity) {
const Uint max_default_arg_reg =
sizeof(c_p->def_arg_reg) / sizeof(c_p->def_arg_reg[0]);

/*
* At this point, arguments are known to be good.
*/

if (c_p->arg_reg != c_p->def_arg_reg) {
/* Save some memory */
erts_free(ERTS_ALC_T_ARG_REG, c_p->arg_reg);
c_p->arg_reg = c_p->def_arg_reg;
c_p->max_arg_reg = sizeof(c_p->def_arg_reg)/sizeof(c_p->def_arg_reg[0]);
/* Save some memory if possible. */
if (arity <= max_default_arg_reg && c_p->arg_reg != c_p->def_arg_reg) {
erts_free(ERTS_ALC_T_ARG_REG, c_p->arg_reg);
c_p->max_arg_reg = max_default_arg_reg;
c_p->arg_reg = c_p->def_arg_reg;
}

#ifdef USE_VM_PROBES
if (DTRACE_ENABLED(process_hibernate)) {
ErtsCodeMFA cmfa = { module, function, arity};
DTRACE_CHARBUF(process_name, DTRACE_TERM_BUF_SIZE);
DTRACE_CHARBUF(mfa_buf, DTRACE_TERM_BUF_SIZE);
dtrace_fun_decode(c_p, &cmfa, process_name, mfa_buf);
DTRACE2(process_hibernate, process_name, mfa_buf);
}
#endif
/*
* Arrange for the process to be resumed at the given MFA with
* the stack cleared.
*/
c_p->arity = 3;
c_p->arg_reg[0] = module;
c_p->arg_reg[1] = function;
c_p->arg_reg[2] = args;
c_p->stop = c_p->hend - CP_SIZE; /* Keep first continuation pointer */

switch(erts_frame_layout) {
case ERTS_FRAME_LAYOUT_RA:
ASSERT(c_p->stop[0] == make_cp(beam_normal_exit));
break;
case ERTS_FRAME_LAYOUT_FP_RA:
FRAME_POINTER(c_p) = &c_p->stop[0];
ASSERT(c_p->stop[0] == make_cp(NULL));
ASSERT(c_p->stop[1] == make_cp(beam_normal_exit));
break;
}

c_p->catches = 0;
c_p->return_trace_frames = 0;
c_p->i = beam_run_process;
sys_memcpy(c_p->arg_reg, regs, arity * sizeof(Eterm));
c_p->arity = arity;

/*
* If there are no waiting messages, garbage collect and
Expand All @@ -1712,10 +1643,9 @@ erts_hibernate(Process* c_p, Eterm* reg)
erts_atomic32_read_band_relb(&c_p->state, ~ERTS_PSFLG_ACTIVE);
ASSERT(!ERTS_PROC_IS_EXITING(c_p));
}

erts_proc_unlock(c_p, ERTS_PROC_LOCK_MSGQ|ERTS_PROC_LOCK_STATUS);
c_p->current = &BIF_TRAP_EXPORT(BIF_hibernate_3)->info.mfa;
c_p->flags |= F_HIBERNATE_SCHED; /* Needed also when woken! */
return 1;
}

ErtsCodePtr
Expand Down
73 changes: 57 additions & 16 deletions erts/emulator/beam/bif.c
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,7 @@
#include "jit/beam_asm.h"
#include "erl_global_literals.h"
#include "beam_load.h"
#include "beam_common.h"

Export *erts_await_result;
static Export await_exit_trap;
Expand Down Expand Up @@ -1189,26 +1190,66 @@ BIF_RETTYPE unlink_1(BIF_ALIST_1)

BIF_RETTYPE hibernate_3(BIF_ALIST_3)
{
/*
* hibernate/3 is usually translated to an instruction; therefore
* this function is only called when the call could not be translated.
*/
Eterm reg[3];
Eterm module = BIF_ARG_1, function = BIF_ARG_2, args = BIF_ARG_3;
Uint arity = 0;

/* Check for obvious errors as a courtesy to the user; while apply/3 will
* fail later on if there's anything wrong with the arguments (e.g. the
* callee does not exist), we have more helpful context now than after
* discarding the stack. */
if (is_not_atom(module) || is_not_atom(function)) {
BIF_ERROR(BIF_P, BADARG);
}

while (is_list(args) && arity <= MAX_ARG) {
args = CDR(list_val(args));
arity++;
}

reg[0] = BIF_ARG_1;
reg[1] = BIF_ARG_2;
reg[2] = BIF_ARG_3;
if (is_not_nil(args)) {
if (arity > MAX_ARG) {
BIF_ERROR(BIF_P, SYSTEM_LIMIT);
}

if (erts_hibernate(BIF_P, reg)) {
/*
* If hibernate succeeded, TRAP. The process will be wait in a
* hibernated state if its state is inactive (!ERTS_PSFLG_ACTIVE);
* otherwise, continue executing (if any message was in the queue).
*/
BIF_TRAP_CODE_PTR(BIF_P, BIF_P->i, 3);
BIF_ERROR(BIF_P, BADARG);
}

return THE_NON_VALUE;
#ifdef USE_VM_PROBES
if (DTRACE_ENABLED(process_hibernate)) {
ErtsCodeMFA cmfa = { module, function, arity };
DTRACE_CHARBUF(process_name, DTRACE_TERM_BUF_SIZE);
DTRACE_CHARBUF(mfa_buf, DTRACE_TERM_BUF_SIZE);
dtrace_fun_decode(BIF_P, &cmfa, process_name, mfa_buf);
DTRACE2(process_hibernate, process_name, mfa_buf);
}
#endif

/* Discard our execution state and prepare to resume with apply/3 after
* waking up from hibernation.
*
* Note that BIF_P->current has already been set to hibernate/3 as this is
* a heavy BIF. */
BIF_P->stop = BIF_P->hend - CP_SIZE;
BIF_P->return_trace_frames = 0;
BIF_P->catches = 0;

switch(erts_frame_layout) {
case ERTS_FRAME_LAYOUT_RA:
ASSERT(BIF_P->stop[0] == make_cp(beam_normal_exit));
break;
case ERTS_FRAME_LAYOUT_FP_RA:
FRAME_POINTER(BIF_P) = &BIF_P->stop[0];
ASSERT(BIF_P->stop[0] == make_cp(NULL));
ASSERT(BIF_P->stop[1] == make_cp(beam_normal_exit));
break;
}

/* Normally, the X register array is filled when trapping out. We do NOT do
* this here as there is special magic involved when trapping out after
* hibernation; `erts_hibernate` populates the process' argument registers
* and then the BIF epilogue jumps straight into do_schedule. */
erts_hibernate(BIF_P, BIF__ARGS, 3);
BIF_TRAP_CODE_PTR(BIF_P, beam_run_process, 3);
}

/**********************************************************************/
Expand Down
11 changes: 6 additions & 5 deletions erts/emulator/beam/emu/ops.tab
Original file line number Diff line number Diff line change
Expand Up @@ -879,12 +879,13 @@ call_ext u==0 u$func:erlang:yield/0 => i_yield
call_ext_last u==0 u$func:erlang:yield/0 D => i_yield | deallocate_return D
call_ext_only u==0 u$func:erlang:yield/0 => i_yield | return


# The hibernate/0 BIF is an instruction
#
# The hibernate/3 BIF is an instruction.
#
call_ext u==3 u$func:erlang:hibernate/3 => i_hibernate
call_ext_last u==3 u$func:erlang:hibernate/3 _D => i_hibernate
call_ext_only u==3 u$func:erlang:hibernate/3 => i_hibernate

call_ext u==0 u$func:erlang:hibernate/0 => i_hibernate
call_ext_last u==0 u$func:erlang:hibernate/0 D => i_hibernate | deallocate_return D
call_ext_only u==0 u$func:erlang:hibernate/0 => i_hibernate | return

call_ext u==0 u$func:os:perf_counter/0 =>
i_perf_counter
Expand Down
19 changes: 9 additions & 10 deletions erts/emulator/beam/emu/trace_instrs.tab
Original file line number Diff line number Diff line change
Expand Up @@ -120,16 +120,15 @@ i_yield() {

i_hibernate() {
HEAVY_SWAPOUT;
if (erts_hibernate(c_p, reg)) {
FCALLS = c_p->fcalls;
c_p->flags &= ~F_HIBERNATE_SCHED;
goto do_schedule;
} else {
HEAVY_SWAPIN;
I = handle_error(c_p, I, reg, &BIF_TRAP_EXPORT(BIF_hibernate_3)->info.mfa);
goto post_error_handling;
}
//| -no_next

erts_hibernate(c_p, reg, 0);

c_p->arg_reg[0] = am_ok;
c_p->arity = 1;

$SET_CP_I_ABS($NEXT_INSTRUCTION);
c_p->current = NULL;
goto do_schedule;
}

// This is optimised as an instruction because
Expand Down
Loading

0 comments on commit 2c47049

Please sign in to comment.