Skip to content

Commit

Permalink
fixup! DEBUG: Measure latency of calls to trace:function
Browse files Browse the repository at this point in the history
  • Loading branch information
sverker committed Oct 1, 2024
1 parent e0e8000 commit 74b522f
Show file tree
Hide file tree
Showing 4 changed files with 12 additions and 65 deletions.
5 changes: 0 additions & 5 deletions erts/emulator/beam/erl_bif_info.c
Original file line number Diff line number Diff line change
Expand Up @@ -4447,11 +4447,6 @@ BIF_RETTYPE erts_debug_get_internal_state_1(BIF_ALIST_1)
Eterm* tp = tuple_val(BIF_ARG_1);
switch (arityval(tp[0])) {
case 2: {
if (tp[1] == am_session) {
Eterm get_session_thr_prog_latency(Process*, Eterm session);
return get_session_thr_prog_latency(BIF_P, tp[2]);
}
else
if (ERTS_IS_ATOM_STR("node_and_dist_references", tp[1])) {
if (tp[2] == am_blocked
&& erts_is_multi_scheduling_blocked() > 0) {
Expand Down
18 changes: 0 additions & 18 deletions erts/emulator/beam/erl_bif_trace.c
Original file line number Diff line number Diff line change
Expand Up @@ -505,7 +505,6 @@ trace_pattern(Process* p, ErtsTraceSession *session,
ASSERT(matches >= 0);
ASSERT(finish_bp.stager == NULL);
finish_bp.stager = p;
erts_staging_trace_session->bp_finish = erts_get_monotonic_time(p->scheduler_data);
erts_schedule_code_barrier(&finish_bp.barrier, smp_bp_finisher, NULL);
erts_proc_inc_refc(p);
erts_suspend(p, ERTS_PROC_LOCK_MAIN, NULL);
Expand All @@ -528,20 +527,6 @@ trace_pattern(Process* p, ErtsTraceSession *session,
}
}

Eterm get_session_thr_prog_latency(Process *p, Eterm session);

Eterm get_session_thr_prog_latency(Process *p, Eterm session)
{
ErtsTraceSession *s;
if (!term_to_session(session, &s, 0)) {
BIF_ERROR(p, BADARG);
} else {
ErtsMonotonicTime usec = ERTS_MONOTONIC_TO_USEC__(s->bp_finish);
erts_deref_trace_session(s);
return make_small(usec);
}
}

static void smp_bp_finisher(void* null)
{
if (erts_finish_breakpointing()) { /* Not done */
Expand Down Expand Up @@ -576,9 +561,6 @@ static void smp_bp_finisher(void* null)
#endif
erts_release_code_mod_permission();
if (p) {
session->bp_finish = (erts_get_monotonic_time(p->scheduler_data)
- session->bp_finish);

/*
* Operation initiated by BIF call which did refc++
* to keep session alive during entire call.
Expand Down
2 changes: 0 additions & 2 deletions erts/emulator/beam/erl_trace.h
Original file line number Diff line number Diff line change
Expand Up @@ -122,8 +122,6 @@ typedef struct ErtsTraceSession {
struct erts_system_monitor_flags_t flags;
} system_monitor;

ErtsMonotonicTime bp_finish;

#ifdef DEBUG
erts_refc_t dbg_bp_refc; /* Number of breakpoints */
erts_refc_t dbg_p_refc; /* Number of processes and ports */
Expand Down
52 changes: 12 additions & 40 deletions erts/emulator/test/trace_sessions.erl
Original file line number Diff line number Diff line change
Expand Up @@ -255,8 +255,8 @@ init_group([pre_session|Tail], Config) ->
%% Set a dummy call_count on all (local) functions.
trace:function(S, {'_','_','_'}, true, [local]),

%% Re-set a dummy global call trace on all exported functions.
set_dummy_global(S, Config),
%% Re-set a dummy global call trace on exported functions.
set_dummy_global_trace(S, Config),

%% Set a dummy send trace on all processes and ports
%% but disable send trace to not get any messages.
Expand Down Expand Up @@ -314,53 +314,25 @@ end_per_testcase(Config) ->



set_dummy_global(S, Config) ->
set_dummy_global_trace(S, Config) ->
%% Modules = [M || M <- erlang:loaded(),
%% erlang:function_exported(M, module_info, 1)],
%% Do trace_pattern on all loaded modules takes too long time
%% Calling trace_pattern on all loaded modules takes too long time
%% on some machines. Do it on a subset of modules instead.

%% Set a dummy global call trace on some exported functions.
SuiteModule = proplists:get_value(suite_module, Config),
Modules = [erlang, ets, lists, maps, SuiteModule],
io:format("~w modules to trace...\n", [length(Modules)]),

WasAvail = erts_debug:set_internal_state(available_internal_state, true),
Result = try set_dummy_global(S, Modules, 1, [])
after
erts_debug:set_internal_state(available_internal_state, WasAvail)
end,

io:format("\nModule sorted totals:\n", []),
[begin
Percent = case ModTot of
0 -> 0;
_ -> (100*ThrProgTot) div ModTot
end,
io:format("~10w ~10w ~3w%: ~w #~w", [ModTot, ThrProgTot, Percent, Module, N])
{Micros, 1} = timer:tc(fun() ->
trace:function(S, {Mod, Func, Arity},
true, [global])
end),
io:format("~10w: ~w:~w/~w", [Micros, Mod, Func, Arity])
end
|| {ModTot, ThrProgTot, Module, N} <- Result],
ok.
|| Mod <- Modules,
{Func, Arity} <- Mod:module_info(exports)],


set_dummy_global(_S, [], _N, Acc) ->
lists:sort(Acc);
set_dummy_global(S, [Module|Tail], N, Acc) ->
test_server_ctrl:print_timestamp(minor, atom_to_list(Module)),
%%io:format("\nModule #~w: ~w\n", [N, Module]),

Before = erlang:monotonic_time(microsecond),
ThrProgTot =
lists:foldl(fun({Func, Arity}, ThrProgAcc) ->
{Micros, _} = timer:tc(fun() ->
trace:function(S, {Module, Func, Arity}, true, [global])
end),
ThrProg = erts_debug:get_internal_state({session, S}),
io:format("~10w~10w: ~w:~w/~w", [Micros, ThrProg, Module, Func, Arity]),
ThrProgAcc + ThrProg
end,
0,
Module:module_info(exports)),

ModTot = erlang:monotonic_time(microsecond) - Before,
set_dummy_global(S, Tail, N+1, [{ModTot,ThrProgTot,Module,N} | Acc]).
ok.

0 comments on commit 74b522f

Please sign in to comment.