Skip to content

Commit 7298f55

Browse files
committed
Add erlang:system_info(bif_timer_count)
This is helpful to detect when a process is accidentally generating an excessive number of bif timers. We only count bif timers and not proc timers, because the latter are bounded by the number of processes.
1 parent 6ff969d commit 7298f55

File tree

10 files changed

+96
-13
lines changed

10 files changed

+96
-13
lines changed

erts/doc/src/erlang_system_info.md

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ order to make it easier to navigate.
5555
[`port_limit`](`m:erlang#system_info_port_limit`),
5656
[`process_count`](`m:erlang#system_info_process_count`),
5757
[`process_limit`](`m:erlang#system_info_process_limit`)
58+
[`bif_timer_count`](`m:erlang#system_info_bif_timer_count`),
5859

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

401+
- `bif_timer_count`{: #system_info_bif_timer_count } - Returns the number of bif
402+
timers currently existing at the local node. Bif timers are those created by `erlang:send_after`
403+
and `erlang:start_timer`, but not those implicitly created by receive statements with timeouts.
404+
The value is given as an integer.
405+
406+
Since OTP 29.0
407+
400408
## System Time
401409

402410
Returns information about the current system (emulator) time as specified by `Item`:

erts/emulator/beam/atom.names

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -733,6 +733,7 @@ atom threads
733733
atom time_offset
734734
atom timeout
735735
atom timeout_value
736+
atom bif_timer_count
736737
atom Times='*'
737738
atom timestamp
738739
atom total

erts/emulator/beam/erl_bif_info.c

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2937,6 +2937,8 @@ BIF_RETTYPE system_info_1(BIF_ALIST_1)
29372937
hp = HAlloc(BIF_P, 3);
29382938
res = TUPLE2(hp, am_min_bin_vheap_size,make_small(BIN_VH_MIN_SIZE));
29392939
BIF_RET(res);
2940+
} else if (BIF_ARG_1 == am_bif_timer_count) {
2941+
BIF_RET(make_small(erts_bif_timer_count()));
29402942
} else if (BIF_ARG_1 == am_process_count) {
29412943
BIF_RET(make_small(erts_ptab_count(&erts_proc)));
29422944
} else if (BIF_ARG_1 == am_process_limit) {

erts/emulator/beam/erl_hl_timer.c

Lines changed: 29 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -302,6 +302,7 @@ struct ErtsHLTimerService_ {
302302
ErtsHLTimer *next_timeout;
303303
ErtsYieldingTimeoutState yield;
304304
ErtsTWheelTimer service_timer;
305+
Uint btm_count;
305306
};
306307

307308
static ERTS_INLINE int
@@ -635,6 +636,7 @@ erts_create_timer_service(void)
635636
srv->btm_tree = NULL;
636637
srv->next_timeout = NULL;
637638
srv->yield = init_yield;
639+
srv->btm_count = 0;
638640
erts_twheel_init_timer(&srv->service_timer);
639641

640642
init_canceled_queue(&srv->canceled_queue);
@@ -707,6 +709,21 @@ port_timeout_common(Port *port, void *tmr)
707709
return 0;
708710
}
709711

712+
static ERTS_INLINE void
713+
insert_btm(ErtsBifTimer *tmr, ErtsHLTimerService *srv)
714+
{
715+
btm_rbt_insert(&srv->btm_tree, tmr);
716+
++ srv->btm_count;
717+
}
718+
719+
static ERTS_INLINE void
720+
remove_btm(ErtsBifTimer *tmr, ErtsHLTimerService *srv)
721+
{
722+
btm_rbt_delete(&srv->btm_tree, tmr);
723+
-- srv->btm_count;
724+
tmr->btm.tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
725+
}
726+
710727
static ERTS_INLINE erts_aint_t
711728
init_btm_specifics(ErtsSchedulerData *esdp,
712729
ErtsBifTimer *tmr, Eterm msg,
@@ -732,7 +749,7 @@ init_btm_specifics(ErtsSchedulerData *esdp,
732749

733750
tmr->btm.proc_tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
734751

735-
btm_rbt_insert(&esdp->timer_service->btm_tree, tmr);
752+
insert_btm(tmr, esdp->timer_service);
736753

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

11441161
if (tmr->btm.tree.parent != ERTS_HLT_PFIELD_NOT_IN_TABLE) {
1145-
btm_rbt_delete(&srv->btm_tree, tmr);
1146-
tmr->btm.tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
1162+
remove_btm(tmr, srv);
11471163
}
11481164

11491165
}
@@ -1470,8 +1486,7 @@ cleanup_sched_local_canceled_timer(ErtsSchedulerData *esdp,
14701486
if (roflgs & ERTS_TMR_ROFLG_BIF_TMR) {
14711487
ErtsBifTimer *btm = (ErtsBifTimer *) tmr;
14721488
if (btm->btm.tree.parent != ERTS_HLT_PFIELD_NOT_IN_TABLE) {
1473-
btm_rbt_delete(&esdp->timer_service->btm_tree, btm);
1474-
btm->btm.tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
1489+
remove_btm(btm, esdp->timer_service);
14751490
}
14761491
}
14771492

@@ -1779,8 +1794,7 @@ setup_bif_timer(Process *c_p, int twheel, ErtsMonotonicTime timeout_pos,
17791794
ERTS_P2P_FLG_INC_REFC);
17801795
if (!proc) {
17811796
if (tmr->btm.tree.parent != ERTS_HLT_PFIELD_NOT_IN_TABLE) {
1782-
btm_rbt_delete(&esdp->timer_service->btm_tree, tmr);
1783-
tmr->btm.tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
1797+
remove_btm(tmr, esdp->timer_service);
17841798
}
17851799
if (tmr->btm.bp)
17861800
free_message_buffer(tmr->btm.bp);
@@ -1884,8 +1898,7 @@ access_btm(ErtsBifTimer *tmr, Uint32 sid, ErtsSchedulerData *esdp, int cancel)
18841898
}
18851899
else {
18861900
if (tmr->btm.tree.parent != ERTS_HLT_PFIELD_NOT_IN_TABLE) {
1887-
btm_rbt_delete(&esdp->timer_service->btm_tree, tmr);
1888-
tmr->btm.tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
1901+
remove_btm(tmr, esdp->timer_service);
18891902
}
18901903
if (is_hlt) {
18911904
if (cncl_res > 0)
@@ -2361,8 +2374,7 @@ exit_cancel_bif_timer(ErtsBifTimer *tmr, void *vesdp, Sint reds)
23612374
}
23622375

23632376
if (tmr->btm.tree.parent != ERTS_HLT_PFIELD_NOT_IN_TABLE) {
2364-
btm_rbt_delete(&esdp->timer_service->btm_tree, tmr);
2365-
tmr->btm.tree.parent = ERTS_HLT_PFIELD_NOT_IN_TABLE;
2377+
remove_btm(tmr, esdp->timer_service);
23662378
}
23672379
if (is_hlt)
23682380
hlt_delete_timer(esdp, &tmr->type.hlt);
@@ -2898,6 +2910,12 @@ erts_read_port_timer(Port *c_prt)
28982910
return get_time_left(NULL, timeout_pos);
28992911
}
29002912

2913+
Uint
2914+
erts_bif_timer_count_in_timer_service(ErtsHLTimerService *service)
2915+
{
2916+
return service->btm_count;
2917+
}
2918+
29012919
/*
29022920
* Debug stuff...
29032921
*/

erts/emulator/beam/erl_hl_timer.h

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -87,4 +87,6 @@ erts_debug_callback_timer_foreach(void (*tclbk)(void *),
8787
ErtsMonotonicTime,
8888
void *),
8989
void *arg);
90+
91+
Uint erts_bif_timer_count_in_timer_service(ErtsHLTimerService *service);
9092
#endif /* ERL_HL_TIMER_H__ */

erts/emulator/beam/erl_process.c

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15248,6 +15248,16 @@ void erts_halt(int code, ErtsMonotonicTime htmo)
1524815248
}
1524915249
}
1525015250

15251+
Uint erts_bif_timer_count()
15252+
{
15253+
Uint result = 0;
15254+
ERTS_FOREACH_RUNQ(rq,
15255+
ErtsHLTimerService *srv = rq->scheduler->timer_service;
15256+
result += erts_bif_timer_count_in_timer_service(srv);
15257+
);
15258+
return result;
15259+
}
15260+
1525115261
#if defined(ERTS_ENABLE_LOCK_CHECK)
1525215262
int
1525315263
erts_dbg_check_halloc_lock(Process *p)

erts/emulator/beam/erl_process.h

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -759,6 +759,7 @@ extern ErtsAlignedSchedulerData * ERTS_WRITE_UNLIKELY(erts_aligned_scheduler_dat
759759
extern ErtsAlignedSchedulerData * ERTS_WRITE_UNLIKELY(erts_aligned_dirty_cpu_scheduler_data);
760760
extern ErtsAlignedSchedulerData * ERTS_WRITE_UNLIKELY(erts_aligned_dirty_io_scheduler_data);
761761

762+
Uint erts_bif_timer_count(void);
762763

763764
#if defined(ERTS_ENABLE_LOCK_CHECK)
764765
int erts_lc_runq_is_locked(ErtsRunQueue *);

erts/emulator/test/system_info_SUITE.erl

Lines changed: 40 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@
3939

4040
-export([process_count/1, system_version/1, misc_smoke_tests/1,
4141
heap_size/1, wordsize/1, memory/1, ets_limit/1, atom_limit/1,
42-
procs_bug/1,
42+
procs_bug/1, bif_timer_count/1,
4343
ets_count/1, atom_count/1, system_logger/1]).
4444

4545
-export([init/1, handle_event/2, handle_call/2]).
@@ -53,7 +53,7 @@ suite() ->
5353
all() ->
5454
[process_count, system_version, misc_smoke_tests,
5555
ets_count, heap_size, wordsize, memory, ets_limit, atom_limit, atom_count,
56-
procs_bug,
56+
procs_bug, bif_timer_count,
5757
system_logger].
5858

5959

@@ -519,6 +519,44 @@ ets_count_do(Opts) ->
519519
ets:delete(T),
520520
Before = erlang:system_info(ets_count).
521521

522+
bif_timer_count(Config) when is_list(Config) ->
523+
NumTmrs = 1000, ShortTimeout = 1_000, LongTimeout = 1_000_000_000,
524+
bif_timer_count_single_threaded(NumTmrs, ShortTimeout),
525+
bif_timer_count_single_threaded(NumTmrs, LongTimeout),
526+
bif_timer_count_multi_threaded(NumTmrs, ShortTimeout),
527+
bif_timer_count_multi_threaded(NumTmrs, LongTimeout),
528+
ok.
529+
530+
bif_timer_count_do(NumTmrs, Fun) ->
531+
Before = erlang:system_info(bif_timer_count),
532+
Tmrs = Fun(),
533+
After = erlang:system_info(bif_timer_count),
534+
MaxJitter = 10,
535+
ActualJitter = abs(After - Before - NumTmrs),
536+
true = ActualJitter < MaxJitter,
537+
Tmrs.
538+
539+
bif_timer_count_single_threaded(NumTmrs, Timeout) ->
540+
Tmrs = bif_timer_count_do(NumTmrs, fun () ->
541+
[erlang:start_timer(Timeout, self(), bif_timer_count_test) || _ <- lists:seq(1, NumTmrs)] end),
542+
lists:foreach(fun (Tmr) -> erlang:cancel_timer(Tmr) end, Tmrs).
543+
544+
bif_timer_count_multi_threaded(NumTmrs, Timeout) ->
545+
SpawnerPid = self(),
546+
_ = bif_timer_count_do(NumTmrs, fun () ->
547+
[erlang:spawn_link(fun () ->
548+
Tmr = erlang:start_timer(Timeout, SpawnerPid, bif_timer_count_test),
549+
SpawnerPid ! {timer_initialized, Tmr},
550+
% We're cancelling the timers in the spawned processes, because cancelling timers across schedulers is done lazily,
551+
% and we want to make sure that the timers are cancelled before we start the next test (otherwise the second multithreaded test fails).
552+
% 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)
553+
receive after 2_000 -> ok end,
554+
erlang:cancel_timer(Tmr),
555+
SpawnerPid ! timer_cancelled
556+
end) || _ <- lists:seq(1, NumTmrs)],
557+
[receive {timer_initialized, Tmr} -> Tmr end || _ <- lists:seq(1, NumTmrs)]
558+
end),
559+
[receive timer_cancelled -> ok end || _ <- lists:seq(1, NumTmrs)].
522560

523561
%% Verify system_info(ets_limit) reflects max ETS table settings.
524562
ets_limit(Config0) when is_list(Config0) ->

erts/preloaded/src/erlang.erl

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10251,6 +10251,7 @@ the `CpuTopology` type to change.
1025110251
Alloc :: atom();
1025210252
(atom_count) -> pos_integer();
1025310253
(atom_limit) -> pos_integer();
10254+
(bif_timer_count) -> non_neg_integer();
1025410255
(build_type) -> opt | debug |
1025510256
gcov | valgrind | gprof | lcnt | frmptr;
1025610257
(c_compiler_used) -> {atom(), term()};

lib/dialyzer/src/erl_bif_types.erl

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -957,6 +957,8 @@ type(erlang, system_info, 1, Xs) ->
957957
t_non_neg_fixnum();
958958
['trace_control_word'] ->
959959
t_integer();
960+
['bif_timer_count'] ->
961+
t_non_neg_fixnum();
960962
['version'] ->
961963
t_string();
962964
['wordsize'] ->

0 commit comments

Comments
 (0)