Skip to content

Commit

Permalink
Merge 'sverker/26/erts/trace-bp-hash-reset-bug/GH-8835/OTP-19269'
Browse files Browse the repository at this point in the history
into sverker/27/erts/trace-bp-hash-reset-bug/GH-8835/OTP-19269
  • Loading branch information
sverker committed Oct 3, 2024
2 parents 9ae2ef5 + ef72dc8 commit 212d454
Show file tree
Hide file tree
Showing 3 changed files with 96 additions and 21 deletions.
41 changes: 22 additions & 19 deletions erts/emulator/beam/beam_bp.c
Original file line number Diff line number Diff line change
Expand Up @@ -141,6 +141,7 @@ static GenericBpData* check_break(ErtsTraceSession *session,

static void bp_meta_unref(BpMetaTracer *bmt);
static void bp_count_unref(BpCount *bcp);
static BpDataCallTrace* bp_calltrace_alloc(void);
static void bp_calltrace_unref(BpDataCallTrace *bdt);
static void consolidate_bp_data(struct erl_module_instance *mi,
ErtsCodeInfo *ci, int local);
Expand Down Expand Up @@ -489,12 +490,10 @@ consolidate_bp_data_session(GenericBp* g)
if (flags & ERTS_BPF_TIME_TRACE) {
dst->time = src->time;
erts_refc_inc(&dst->time->refc, 1);
ASSERT(dst->time->hash);
}
if (flags & ERTS_BPF_MEM_TRACE) {
dst->memory = src->memory;
erts_refc_inc(&dst->memory->refc, 1);
ASSERT(dst->memory->hash);
}
}

Expand Down Expand Up @@ -1620,12 +1619,9 @@ static void bp_hash_delete(bp_trace_hash_t *hash) {
hash->item = NULL;
}

static void bp_hash_reset(BpDataCallTrace* bdt) {
Uint i;
for (i = 0; i < bdt->n; i++) {
bp_hash_delete(&(bdt->hash[i]));
bp_hash_init(&(bdt->hash[i]), 32);
}
static void bp_hash_reset(BpDataCallTrace** bdt_p) {
bp_calltrace_unref(*bdt_p);
*bdt_p = bp_calltrace_alloc();
}

void erts_schedule_time_break(Process *p, Uint schedule) {
Expand Down Expand Up @@ -1860,7 +1856,7 @@ set_function_break(ErtsCodeInfo *ci,
bp->flags &= ~ERTS_BPF_TIME_TRACE_ACTIVE;
} else {
bp->flags |= ERTS_BPF_TIME_TRACE_ACTIVE;
bp_hash_reset(bp->time);
bp_hash_reset(&bp->time);
}
ASSERT((bp->flags & ~ERTS_BPF_ALL) == 0);
return;
Expand All @@ -1869,7 +1865,7 @@ set_function_break(ErtsCodeInfo *ci,
bp->flags &= ~ERTS_BPF_MEM_TRACE_ACTIVE;
} else {
bp->flags |= ERTS_BPF_MEM_TRACE_ACTIVE;
bp_hash_reset(bp->memory);
bp_hash_reset(&bp->memory);
}
ASSERT((bp->flags & ~ERTS_BPF_ALL) == 0);
return;
Expand Down Expand Up @@ -1902,17 +1898,12 @@ set_function_break(ErtsCodeInfo *ci,
bp->count = bcp;
} else if (break_flags & (ERTS_BPF_TIME_TRACE | ERTS_BPF_MEM_TRACE)) {
BpDataCallTrace* bdt;
Uint i;

ASSERT((break_flags & bp->flags & ERTS_BPF_TIME_TRACE) == 0);
ASSERT((break_flags & bp->flags & ERTS_BPF_MEM_TRACE) == 0);
bdt = Alloc(sizeof(BpDataCallTrace));
erts_refc_init(&bdt->refc, 1);
bdt->n = erts_no_schedulers + 1;
bdt->hash = Alloc(sizeof(bp_trace_hash_t)*(bdt->n));
for (i = 0; i < bdt->n; i++) {
bp_hash_init(&(bdt->hash[i]), 32);
}

bdt = bp_calltrace_alloc();

if (break_flags & ERTS_BPF_TIME_TRACE)
bp->time = bdt;
else
Expand Down Expand Up @@ -2011,6 +2002,19 @@ bp_count_unref(BpCount* bcp)
}
}

static BpDataCallTrace* bp_calltrace_alloc(void)
{
const Uint n = erts_no_schedulers + 1;
BpDataCallTrace *bdt = Alloc(offsetof(BpDataCallTrace,hash) +
sizeof(bp_trace_hash_t)*n);
bdt->n = n;
erts_refc_init(&bdt->refc, 1);
for (Uint i = 0; i < n; i++) {
bp_hash_init(&(bdt->hash[i]), 32);
}
return bdt;
}

static void
bp_calltrace_unref(BpDataCallTrace* bdt)
{
Expand All @@ -2020,7 +2024,6 @@ bp_calltrace_unref(BpDataCallTrace* bdt)
for (i = 0; i < bdt->n; ++i) {
bp_hash_delete(&(bdt->hash[i]));
}
Free(bdt->hash);
Free(bdt);
}
}
Expand Down
2 changes: 1 addition & 1 deletion erts/emulator/beam/beam_bp.h
Original file line number Diff line number Diff line change
Expand Up @@ -47,8 +47,8 @@ typedef struct {

typedef struct bp_data_time { /* Call time, Memory trace */
Uint n;
bp_trace_hash_t *hash;
erts_refc_t refc;
bp_trace_hash_t hash[1];
} BpDataCallTrace;

typedef struct process_breakpoint_trace_t {
Expand Down
74 changes: 73 additions & 1 deletion erts/emulator/test/trace_call_time_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@

-export([seq/3, seq_r/3]).
-export([loaded/1, a_function/1, a_called_function/1, dec/1, nif_dec/1, dead_tracer/1,
return_stop/1,catch_crash/1]).
return_stop/1,reset/1,catch_crash/1]).

-define(US_ERROR, 10000).
-define(R_ERROR, 0.8).
Expand Down Expand Up @@ -88,6 +88,7 @@ testcases() ->
disable_ongoing,
apply_bif_bug,
combo, bif, nif, called_function, dead_tracer, return_stop,
reset,
catch_crash].

init_per_suite(Config) ->
Expand Down Expand Up @@ -685,6 +686,77 @@ spinner(N) ->
quicky() ->
done.

%% OTP-19269: Verify call_time is reset correctly
%% while traced functions are called.
reset(_Config) ->
erlang:trace_pattern({'_','_','_'}, false, [call_time]),

CallTimeReader = fun({P,Cnt,_,_}) -> {P,Cnt} end,
reset_do(call_time, true, CallTimeReader),
reset_do(call_time, restart, CallTimeReader),

CallMemoryReader = fun({P,Cnt,_}) -> {P,Cnt} end,
reset_do(call_memory, true, CallMemoryReader),
reset_do(call_memory, restart, CallMemoryReader),
ok.

reset_do(TraceType, ResetArg, InfoReader) ->
%%
1 = erlang:trace_pattern({?MODULE,aaa, 0}, true, [TraceType]),
1 = erlang:trace_pattern({?MODULE,bbb, 0}, true, [TraceType]),

Np = erlang:system_info(schedulers_online),
Tester = self(),
Pids = [begin
Pid = spawn_opt(fun() ->
receive go -> ok end,
aaa(),
bbb(),
Tester ! {running, self()},
loop_aaa_bbb()
end,
[link, {scheduler,I}]),
erlang:trace(Pid, true, [call]),
Pid ! go,
Pid
end
|| I <- lists:seq(1,Np)],

%% Wait for all to make at least one traced call
[receive {running, P} -> ok end || P <- Pids],

{TraceType, AAA1} = erlang:trace_info({?MODULE,aaa,0}, TraceType),

io:format("Reset trace counters for aaa.\n", []),
1 = erlang:trace_pattern({?MODULE,aaa, 0}, ResetArg, [TraceType]),

{TraceType, AAA2} = erlang:trace_info({?MODULE,aaa,0}, TraceType),
{TraceType, BBB} = erlang:trace_info({?MODULE,bbb,0}, TraceType),

%% Verify counters are sane
lists:zipwith3(fun({P, ACnt1}=A1,
{P, ACnt2}=A2,
{P, BCnt}=B) ->
io:format("A1=~p A2=~p B=~p\n", [A1,A2,B]),
true = (ACnt1+ACnt2 =< BCnt)
end,
lists:sort(lists:map(InfoReader, AAA1)),
lists:sort(lists:map(InfoReader, AAA2)),
lists:sort(lists:map(InfoReader, BBB))),

[P ! die || P <- Pids],
1 = erlang:trace_pattern({?MODULE,aaa, 0}, false, [TraceType]),
1 = erlang:trace_pattern({?MODULE,bbb, 0}, false, [TraceType]),
ok.

loop_aaa_bbb() ->
aaa = aaa(),
bbb = bbb(),
receive die -> ok
after 0 -> loop_aaa_bbb()
end.


%% OTP-16994: next_catch returned a bogus stack pointer when call_time tracing
%% was enabled, crashing the emulator.
catch_crash(_Config) ->
Expand Down

0 comments on commit 212d454

Please sign in to comment.