Skip to content

Commit

Permalink
[pause_proc_timer][1/n] Introduce ErtsPausedProcTimer type and operat…
Browse files Browse the repository at this point in the history
…ions

We want a way to "pause" a proc timer when suspending a process, and
"resume" it later. We will do this as follows.

  * Pausing a proc timer means:
    1. Cancelling the current timer in `common.timer`, if any.
    2. Storing in `common.timer` instead how much time was left in the
       timer. To compute the time left, we need to inspect the current
       timer.
    3. Flagging in the `Process` struct that the timer is paused. This is
       so that we know later that we need to resume the timer when resuming
       the process.
  * Resuming a proc timer then amounts to:
    1. Creating a new proc timer based on the time left that was stored
       in `common.timer`.
    2. Clear all the flags in the `Process` struct
  * When cancelling a proc timer, we now need to check if it is paused
    (in which case, it can just be ignored)

So here we introduce a `ErtsPausedProcTimer` type, that will contain the
time remaining on a paused timer, and a header that is shared with all
other timer types (so that we can safely insert it in `common.timer`).

We also introduce the functions to pause a proc timer and resume it.
At this point nothing calls these functions, this happens in the next
commits.
  • Loading branch information
jcpetruzza committed Nov 28, 2024
1 parent 187a6be commit 825ddd3
Show file tree
Hide file tree
Showing 3 changed files with 116 additions and 0 deletions.
1 change: 1 addition & 0 deletions erts/emulator/beam/erl_alloc.types
Original file line number Diff line number Diff line change
Expand Up @@ -135,6 +135,7 @@ type TIMER_SERVICE LONG_LIVED SYSTEM timer_service
type LL_PTIMER FIXED_SIZE PROCESSES ll_ptimer
type HL_PTIMER FIXED_SIZE PROCESSES hl_ptimer
type BIF_TIMER FIXED_SIZE PROCESSES bif_timer
type PAUSED_TIMER STANDARD PROCESSES paused_timer
type TIMER_REQUEST SHORT_LIVED PROCESSES timer_request
type BTM_YIELD_STATE SHORT_LIVED PROCESSES btm_yield_state
type REG_TABLE STANDARD SYSTEM reg_tab
Expand Down
113 changes: 113 additions & 0 deletions erts/emulator/beam/erl_hl_timer.c
Original file line number Diff line number Diff line change
Expand Up @@ -100,6 +100,7 @@ typedef enum {
#define ERTS_TMR_ROFLG_PROC (((Uint32) 1) << 15)
#define ERTS_TMR_ROFLG_PORT (((Uint32) 1) << 16)
#define ERTS_TMR_ROFLG_CALLBACK (((Uint32) 1) << 17)
#define ERTS_TMR_ROFLG_PAUSED (((Uint32) 1) << 18)

#define ERTS_TMR_ROFLG_SID_MASK \
(ERTS_TMR_ROFLG_HLT - (Uint32) 1)
Expand Down Expand Up @@ -205,6 +206,12 @@ typedef union {
ErtsBifTimer btm;
} ErtsTimer;

typedef struct {
ErtsTmrHead head; /* NEED to be first! */
Sint64 time_left_in_msec;
int count;
} ErtsPausedProcTimer;

typedef ErtsTimer *(*ErtsCreateTimerFunc)(ErtsSchedulerData *esdp,
ErtsMonotonicTime timeout_pos,
int short_time, ErtsTmrType type,
Expand Down Expand Up @@ -950,6 +957,54 @@ create_tw_timer(ErtsSchedulerData *esdp,
return (ErtsTimer *) tmr;
}

/*
* Paused proc timers
*/
static ERTS_INLINE ErtsPausedProcTimer *
create_paused_proc_timer(Process *c_p)
{
ErtsPausedProcTimer *result = NULL;
erts_aint_t itmr = erts_atomic_read_nob(&c_p->common.timer);

if (itmr != ERTS_PTMR_NONE && itmr != ERTS_PTMR_TIMEDOUT) {
ErtsSchedulerData *esdp = erts_proc_sched_data(c_p);
ErtsTimer *tmr = (ErtsTimer *)itmr;

if (tmr->head.roflgs & ERTS_TMR_ROFLG_PAUSED) {
// The process timer was already paused, reuse the paused timer
ErtsPausedProcTimer *pptmr = (ErtsPausedProcTimer*) tmr;
pptmr->count++;
} else {
int is_hlt = !!(tmr->head.roflgs & ERTS_TMR_ROFLG_HLT);
ErtsMonotonicTime timeout_pos;

ASSERT(tmr->head.roflgs & ERTS_TMR_ROFLG_PROC);

result = erts_alloc(ERTS_ALC_T_PAUSED_TIMER,
sizeof(ErtsPausedProcTimer));
result->head.roflgs = tmr->head.roflgs | ERTS_TMR_ROFLG_PAUSED;
erts_atomic32_init_nob(&result->head.refc, 1);
result->head.receiver.proc = tmr->head.receiver.proc;

timeout_pos = (is_hlt
? tmr->hlt.timeout
: erts_tweel_read_timeout(&tmr->twt.u.tw_tmr));
result->time_left_in_msec = get_time_left(esdp, timeout_pos);
result->count = 1;
}
}

return result;
}

static ERTS_INLINE void
paused_proc_timer_dec_refc(ErtsPausedProcTimer *pptmr)
{
if (erts_atomic32_dec_read_relb(&pptmr->head.refc) == 0) {
erts_free(ERTS_ALC_T_PAUSED_TIMER, (void *) pptmr);
}
}

/*
* Basic high level timer stuff
*/
Expand Down Expand Up @@ -1665,6 +1720,11 @@ continue_cancel_ptimer(ErtsSchedulerData *esdp, ErtsTimer *tmr)
{
Uint32 sid = (tmr->head.roflgs & ERTS_TMR_ROFLG_SID_MASK);

if (tmr->head.roflgs & ERTS_TMR_ROFLG_PAUSED) {
paused_proc_timer_dec_refc((ErtsPausedProcTimer*) tmr);
return;
}

if (esdp->no != sid)
queue_canceled_timer(esdp, sid, tmr);
else
Expand Down Expand Up @@ -2714,6 +2774,59 @@ erts_cancel_proc_timer(Process *c_p)
(ErtsTimer *) tval);
}

void
erts_pause_proc_timer(Process *c_p)
{
ErtsPausedProcTimer *pptmr;

ERTS_LC_ASSERT((ERTS_PROC_LOCK_MAIN | ERTS_PROC_LOCK_STATUS)
& erts_proc_lc_my_proc_locks(c_p));

pptmr = create_paused_proc_timer(c_p);
if (!pptmr) {
return;
}

CANCEL_TIMER(c_p);

erts_atomic_set_nob(&c_p->common.timer, (erts_aint_t) pptmr);
}

int
erts_resume_paused_proc_timer(Process *c_p)
{
erts_aint_t timer;
int resumed_timer = 0;

ERTS_LC_ASSERT((ERTS_PROC_LOCK_MAIN | ERTS_PROC_LOCK_STATUS)
& erts_proc_lc_my_proc_locks(c_p));

timer = erts_atomic_xchg_nob(&c_p->common.timer, ERTS_PTMR_NONE);

ASSERT(timer != ERTS_PTMR_TIMEDOUT);

if (timer != ERTS_PTMR_NONE) {
UWord tmo = 0;
ErtsPausedProcTimer *pptmr = (ErtsPausedProcTimer *)timer;

ASSERT(pptmr->head.roflgs & ERTS_TMR_ROFLG_PAUSED);

pptmr->count -= 1;
if (pptmr->count == 0) {
if (pptmr->time_left_in_msec > 0) {
ASSERT((pptmr->time_left_in_msec >> 32) == 0);
tmo = (UWord) pptmr->time_left_in_msec;
}

erts_set_proc_timer_uword(c_p, tmo);
paused_proc_timer_dec_refc(pptmr);
resumed_timer = 1;
}
}

return resumed_timer;
}

void
erts_set_port_timer(Port *c_prt, Sint64 tmo)
{
Expand Down
2 changes: 2 additions & 0 deletions erts/emulator/beam/erl_hl_timer.h
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,8 @@ size_t erts_timer_type_size(ErtsAlcType_t type);
int erts_set_proc_timer_term(Process *, Eterm);
void erts_set_proc_timer_uword(Process *, UWord);
void erts_cancel_proc_timer(Process *);
void erts_pause_proc_timer(Process *);
int erts_resume_paused_proc_timer(Process *);
void erts_set_port_timer(Port *, Sint64);
void erts_cancel_port_timer(Port *);
Sint64 erts_read_port_timer(Port *);
Expand Down

0 comments on commit 825ddd3

Please sign in to comment.