Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
8 changes: 8 additions & 0 deletions erts/doc/src/erlang_system_info.md
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,7 @@ order to make it easier to navigate.
[`port_limit`](`m:erlang#system_info_port_limit`),
[`process_count`](`m:erlang#system_info_process_count`),
[`process_limit`](`m:erlang#system_info_process_limit`)
[`bif_timer_count`](`m:erlang#system_info_bif_timer_count`),

- [`System Time`](`m:erlang#system_info/1-system-time`) -
[`end_time`](`m:erlang#system_info_end_time`),
Expand Down Expand Up @@ -397,6 +398,13 @@ Returns information about the current system (emulator) limits as specified by `
given as an integer. This limit can be configured at startup by using
command-line flag [`+P`](erl_cmd.md#+P) in `erl(1)`.

- `bif_timer_count`{: #system_info_bif_timer_count } - Returns the number of bif
timers currently existing at the local node. Bif timers are those created by `erlang:send_after`
and `erlang:start_timer`, but not those implicitly created by receive statements with timeouts.
The value is given as an integer.

Since OTP 29.0

## System Time

Returns information about the current system (emulator) time as specified by `Item`:
Expand Down
1 change: 1 addition & 0 deletions erts/emulator/beam/atom.names
Original file line number Diff line number Diff line change
Expand Up @@ -733,6 +733,7 @@ atom threads
atom time_offset
atom timeout
atom timeout_value
atom bif_timer_count
atom Times='*'
atom timestamp
atom total
Expand Down
2 changes: 2 additions & 0 deletions erts/emulator/beam/erl_bif_info.c
Original file line number Diff line number Diff line change
Expand Up @@ -2937,6 +2937,8 @@ BIF_RETTYPE system_info_1(BIF_ALIST_1)
hp = HAlloc(BIF_P, 3);
res = TUPLE2(hp, am_min_bin_vheap_size,make_small(BIN_VH_MIN_SIZE));
BIF_RET(res);
} else if (BIF_ARG_1 == am_bif_timer_count) {
BIF_RET(make_small(erts_bif_timer_count()));
} else if (BIF_ARG_1 == am_process_count) {
BIF_RET(make_small(erts_ptab_count(&erts_proc)));
} else if (BIF_ARG_1 == am_process_limit) {
Expand Down
40 changes: 29 additions & 11 deletions erts/emulator/beam/erl_hl_timer.c
Original file line number Diff line number Diff line change
Expand Up @@ -302,6 +302,7 @@ struct ErtsHLTimerService_ {
ErtsHLTimer *next_timeout;
ErtsYieldingTimeoutState yield;
ErtsTWheelTimer service_timer;
Uint btm_count;
};

static ERTS_INLINE int
Expand Down Expand Up @@ -635,6 +636,7 @@ erts_create_timer_service(void)
srv->btm_tree = NULL;
srv->next_timeout = NULL;
srv->yield = init_yield;
srv->btm_count = 0;
erts_twheel_init_timer(&srv->service_timer);

init_canceled_queue(&srv->canceled_queue);
Expand Down Expand Up @@ -707,6 +709,21 @@ port_timeout_common(Port *port, void *tmr)
return 0;
}

static ERTS_INLINE void
insert_btm(ErtsBifTimer *tmr, ErtsHLTimerService *srv)
{
btm_rbt_insert(&srv->btm_tree, tmr);
++ srv->btm_count;
}

static ERTS_INLINE void
remove_btm(ErtsBifTimer *tmr, ErtsHLTimerService *srv)
{
btm_rbt_delete(&srv->btm_tree, tmr);
-- srv->btm_count;
tmr->btm.tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
}

static ERTS_INLINE erts_aint_t
init_btm_specifics(ErtsSchedulerData *esdp,
ErtsBifTimer *tmr, Eterm msg,
Expand All @@ -732,7 +749,7 @@ init_btm_specifics(ErtsSchedulerData *esdp,

tmr->btm.proc_tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;

btm_rbt_insert(&esdp->timer_service->btm_tree, tmr);
insert_btm(tmr, esdp->timer_service);

erts_atomic32_init_nob(&tmr->btm.state, ERTS_TMR_STATE_ACTIVE);
return refc; /* refc from magic binary... */
Expand Down Expand Up @@ -1142,8 +1159,7 @@ bif_timer_timeout(ErtsHLTimerService *srv,
}

if (tmr->btm.tree.parent != ERTS_HLT_PFIELD_NOT_IN_TABLE) {
btm_rbt_delete(&srv->btm_tree, tmr);
tmr->btm.tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
remove_btm(tmr, srv);
}

}
Expand Down Expand Up @@ -1470,8 +1486,7 @@ cleanup_sched_local_canceled_timer(ErtsSchedulerData *esdp,
if (roflgs & ERTS_TMR_ROFLG_BIF_TMR) {
ErtsBifTimer *btm = (ErtsBifTimer *) tmr;
if (btm->btm.tree.parent != ERTS_HLT_PFIELD_NOT_IN_TABLE) {
btm_rbt_delete(&esdp->timer_service->btm_tree, btm);
btm->btm.tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
remove_btm(btm, esdp->timer_service);
}
}

Expand Down Expand Up @@ -1779,8 +1794,7 @@ setup_bif_timer(Process *c_p, int twheel, ErtsMonotonicTime timeout_pos,
ERTS_P2P_FLG_INC_REFC);
if (!proc) {
if (tmr->btm.tree.parent != ERTS_HLT_PFIELD_NOT_IN_TABLE) {
btm_rbt_delete(&esdp->timer_service->btm_tree, tmr);
tmr->btm.tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
remove_btm(tmr, esdp->timer_service);
}
if (tmr->btm.bp)
free_message_buffer(tmr->btm.bp);
Expand Down Expand Up @@ -1884,8 +1898,7 @@ access_btm(ErtsBifTimer *tmr, Uint32 sid, ErtsSchedulerData *esdp, int cancel)
}
else {
if (tmr->btm.tree.parent != ERTS_HLT_PFIELD_NOT_IN_TABLE) {
btm_rbt_delete(&esdp->timer_service->btm_tree, tmr);
tmr->btm.tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
remove_btm(tmr, esdp->timer_service);
}
if (is_hlt) {
if (cncl_res > 0)
Expand Down Expand Up @@ -2361,8 +2374,7 @@ exit_cancel_bif_timer(ErtsBifTimer *tmr, void *vesdp, Sint reds)
}

if (tmr->btm.tree.parent != ERTS_HLT_PFIELD_NOT_IN_TABLE) {
btm_rbt_delete(&esdp->timer_service->btm_tree, tmr);
tmr->btm.tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
remove_btm(tmr, esdp->timer_service);
}
if (is_hlt)
hlt_delete_timer(esdp, &tmr->type.hlt);
Expand Down Expand Up @@ -2898,6 +2910,12 @@ erts_read_port_timer(Port *c_prt)
return get_time_left(NULL, timeout_pos);
}

Uint
erts_bif_timer_count_in_timer_service(ErtsHLTimerService *service)
{
return service->btm_count;
}

/*
* Debug stuff...
*/
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 @@ -87,4 +87,6 @@ erts_debug_callback_timer_foreach(void (*tclbk)(void *),
ErtsMonotonicTime,
void *),
void *arg);

Uint erts_bif_timer_count_in_timer_service(ErtsHLTimerService *service);
#endif /* ERL_HL_TIMER_H__ */
10 changes: 10 additions & 0 deletions erts/emulator/beam/erl_process.c
Original file line number Diff line number Diff line change
Expand Up @@ -15248,6 +15248,16 @@ void erts_halt(int code, ErtsMonotonicTime htmo)
}
}

Uint erts_bif_timer_count()
{
Uint result = 0;
ERTS_FOREACH_RUNQ(rq,
ErtsHLTimerService *srv = rq->scheduler->timer_service;
result += erts_bif_timer_count_in_timer_service(srv);
);
return result;
}

#if defined(ERTS_ENABLE_LOCK_CHECK)
int
erts_dbg_check_halloc_lock(Process *p)
Expand Down
1 change: 1 addition & 0 deletions erts/emulator/beam/erl_process.h
Original file line number Diff line number Diff line change
Expand Up @@ -759,6 +759,7 @@ extern ErtsAlignedSchedulerData * ERTS_WRITE_UNLIKELY(erts_aligned_scheduler_dat
extern ErtsAlignedSchedulerData * ERTS_WRITE_UNLIKELY(erts_aligned_dirty_cpu_scheduler_data);
extern ErtsAlignedSchedulerData * ERTS_WRITE_UNLIKELY(erts_aligned_dirty_io_scheduler_data);

Uint erts_bif_timer_count(void);

#if defined(ERTS_ENABLE_LOCK_CHECK)
int erts_lc_runq_is_locked(ErtsRunQueue *);
Expand Down
42 changes: 40 additions & 2 deletions erts/emulator/test/system_info_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@

-export([process_count/1, system_version/1, misc_smoke_tests/1,
heap_size/1, wordsize/1, memory/1, ets_limit/1, atom_limit/1,
procs_bug/1,
procs_bug/1, bif_timer_count/1,
ets_count/1, atom_count/1, system_logger/1]).

-export([init/1, handle_event/2, handle_call/2]).
Expand All @@ -53,7 +53,7 @@ suite() ->
all() ->
[process_count, system_version, misc_smoke_tests,
ets_count, heap_size, wordsize, memory, ets_limit, atom_limit, atom_count,
procs_bug,
procs_bug, bif_timer_count,
system_logger].


Expand Down Expand Up @@ -519,6 +519,44 @@ ets_count_do(Opts) ->
ets:delete(T),
Before = erlang:system_info(ets_count).

bif_timer_count(Config) when is_list(Config) ->
NumTmrs = 1000, ShortTimeout = 1_000, LongTimeout = 1_000_000_000,
bif_timer_count_single_threaded(NumTmrs, ShortTimeout),
bif_timer_count_single_threaded(NumTmrs, LongTimeout),
bif_timer_count_multi_threaded(NumTmrs, ShortTimeout),
bif_timer_count_multi_threaded(NumTmrs, LongTimeout),
ok.

bif_timer_count_do(NumTmrs, Fun) ->
Before = erlang:system_info(bif_timer_count),
Tmrs = Fun(),
After = erlang:system_info(bif_timer_count),
MaxJitter = 10,
ActualJitter = abs(After - Before - NumTmrs),
true = ActualJitter < MaxJitter,
Tmrs.

bif_timer_count_single_threaded(NumTmrs, Timeout) ->
Tmrs = bif_timer_count_do(NumTmrs, fun () ->
[erlang:start_timer(Timeout, self(), bif_timer_count_test) || _ <- lists:seq(1, NumTmrs)] end),
lists:foreach(fun (Tmr) -> erlang:cancel_timer(Tmr) end, Tmrs).

bif_timer_count_multi_threaded(NumTmrs, Timeout) ->
SpawnerPid = self(),
_ = bif_timer_count_do(NumTmrs, fun () ->
[erlang:spawn_link(fun () ->
Tmr = erlang:start_timer(Timeout, SpawnerPid, bif_timer_count_test),
SpawnerPid ! {timer_initialized, Tmr},
% We're cancelling the timers in the spawned processes, because cancelling timers across schedulers is done lazily,
% and we want to make sure that the timers are cancelled before we start the next test (otherwise the second multithreaded test fails).
% 2s should be enough for the counting to be long finished (it takes about 1s to count 1M timers on my machine, so 2s for 1k timers is very conservative)
receive after 2_000 -> ok end,
erlang:cancel_timer(Tmr),
SpawnerPid ! timer_cancelled
end) || _ <- lists:seq(1, NumTmrs)],
[receive {timer_initialized, Tmr} -> Tmr end || _ <- lists:seq(1, NumTmrs)]
end),
[receive timer_cancelled -> ok end || _ <- lists:seq(1, NumTmrs)].

%% Verify system_info(ets_limit) reflects max ETS table settings.
ets_limit(Config0) when is_list(Config0) ->
Expand Down
1 change: 1 addition & 0 deletions erts/preloaded/src/erlang.erl
Original file line number Diff line number Diff line change
Expand Up @@ -10251,6 +10251,7 @@ the `CpuTopology` type to change.
Alloc :: atom();
(atom_count) -> pos_integer();
(atom_limit) -> pos_integer();
(bif_timer_count) -> non_neg_integer();
(build_type) -> opt | debug |
gcov | valgrind | gprof | lcnt | frmptr;
(c_compiler_used) -> {atom(), term()};
Expand Down
2 changes: 2 additions & 0 deletions lib/dialyzer/src/erl_bif_types.erl
Original file line number Diff line number Diff line change
Expand Up @@ -957,6 +957,8 @@ type(erlang, system_info, 1, Xs) ->
t_non_neg_fixnum();
['trace_control_word'] ->
t_integer();
['bif_timer_count'] ->
t_non_neg_fixnum();
['version'] ->
t_string();
['wordsize'] ->
Expand Down
Loading