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
5 changes: 1 addition & 4 deletions erts/emulator/beam/beam_bif_load.c
Original file line number Diff line number Diff line change
Expand Up @@ -2237,10 +2237,7 @@ delete_code(Module* modp)
}
}

if (ep->bif_number != -1 && ep->is_bif_traced) {
/* Code unloading kills both global and local call tracing. */
ep->is_bif_traced = 0;
}
ASSERT(!ep->is_bif_traced);

ep->trampoline.common.op = BeamOpCodeAddr(op_call_error_handler);
ep->trampoline.not_loaded.deferred = 0;
Expand Down
56 changes: 51 additions & 5 deletions erts/emulator/beam/beam_bp.c
Original file line number Diff line number Diff line change
Expand Up @@ -299,8 +299,36 @@ erts_bp_free_matched_functions(BpFunctions* f)
else ASSERT(f->matched == 0);
}

void
erts_consolidate_export_bp_data(BpFunctions* f)
/*
* Set Export.is_bif_traced for BIFs
* to true if breakpoint exist in either export trampoline or code
* to false otherwise.
*/
static void set_export_is_bif_traced(Export *ep)
{
ErtsCodePtr code;
const ErtsCodeInfo *ci;

if (ep->bif_number < 0) {
ASSERT(!ep->is_bif_traced);
return;
}

if (ep->info.gen_bp && ep->is_bif_traced) {
return;
}

code = ep->dispatch.addresses[erts_active_code_ix()];
ci = erts_code_to_codeinfo(code);
ASSERT(ci->mfa.module == ep->info.mfa.module);
ASSERT(ci->mfa.function == ep->info.mfa.function);
ASSERT(ci->mfa.arity == ep->info.mfa.arity);

ep->is_bif_traced = (ep->info.gen_bp || ci->gen_bp);
}

static void
consolidate_export_bp_data(BpFunctions* f)
{
BpFunction* fs = f->matching;
Uint i, n;
Expand All @@ -324,6 +352,8 @@ erts_consolidate_export_bp_data(BpFunctions* f)
mi->code_length));

consolidate_bp_data(mi, ci_rw, 0);

set_export_is_bif_traced(ErtsContainerStruct(ci_rw, Export, info));
}
}

Expand Down Expand Up @@ -365,6 +395,19 @@ erts_consolidate_local_bp_data(BpFunctions* f)
}
}

void
erts_consolidate_all_bp_data(BpFunctions* f, BpFunctions* e)
{
erts_consolidate_local_bp_data(f);
/*
* Must do export entries *after* module code
* so breakpoints in code have been cleared and
* Export.is_bif_traced can be updated accordingly.
*/
consolidate_export_bp_data(e);
}


void
erts_free_breakpoints(void)
{
Expand All @@ -387,7 +430,7 @@ consolidate_bp_data(struct erl_module_instance *mi,

g = ci_rw->gen_bp;
if (!g) {
return;
return;
}

prev_p = &ci_rw->gen_bp;
Expand Down Expand Up @@ -710,9 +753,12 @@ erts_set_mtrace_break(BpFunctions* f, Binary *match_spec, ErtsTracer tracer)
}

void
erts_set_export_trace(ErtsCodeInfo *ci, Binary *match_spec)
erts_set_export_trace(Export* ep, Binary *match_spec)
{
set_function_break(ci, match_spec, ERTS_BPF_GLOBAL_TRACE, 0, erts_tracer_nil);
set_function_break(&ep->info, match_spec, ERTS_BPF_GLOBAL_TRACE, 0,
erts_tracer_nil);

set_export_is_bif_traced(ep);
}

void
Expand Down
4 changes: 2 additions & 2 deletions erts/emulator/beam/beam_bp.h
Original file line number Diff line number Diff line change
Expand Up @@ -142,13 +142,13 @@ Uint erts_sum_all_session_flags(ErtsCodeInfo *ci_rw);
void erts_uninstall_breakpoints(BpFunctions* f);

void erts_consolidate_local_bp_data(BpFunctions* f);
void erts_consolidate_export_bp_data(BpFunctions* f);
void erts_consolidate_all_bp_data(BpFunctions* f, BpFunctions* e);
void erts_free_breakpoints(void);

void erts_set_trace_break(BpFunctions *f, Binary *match_spec);
void erts_clear_trace_break(BpFunctions *f);

void erts_set_export_trace(ErtsCodeInfo *ci, Binary *match_spec);
void erts_set_export_trace(Export *ep, Binary *match_spec);
void erts_clear_export_trace(ErtsCodeInfo *ci);

void erts_set_mtrace_break(BpFunctions *f, Binary *match_spec, ErtsTracer tracer);
Expand Down
98 changes: 46 additions & 52 deletions erts/emulator/beam/erl_bif_trace.c
Original file line number Diff line number Diff line change
Expand Up @@ -2387,54 +2387,13 @@ erts_set_trace_pattern(ErtsCodeMFA *mfa, int specified,
ErtsTracer meta_tracer, int is_blocking)
{
const ErtsCodeIndex code_ix = erts_active_code_ix();
Uint i, n, matches;
Uint i, n;
Uint matches = 0;
BpFunction* fp;

erts_bp_match_export(&finish_bp.e, mfa, specified);

fp = finish_bp.e.matching;
n = finish_bp.e.matched;
matches = 0;

for (i = 0; i < n; i++) {
ErtsCodeInfo *ci_rw;
Export* ep;

/* Export entries are always writable, discard const. */
ci_rw = (ErtsCodeInfo *)fp[i].code_info;
ep = ErtsContainerStruct(ci_rw, Export, info);

if (ep->bif_number != -1) {
ep->is_bif_traced = !!on;
}

if (on && !flags.breakpoint) {
/* Turn on global call tracing */
if (!erts_is_export_trampoline_active(ep, code_ix)) {
fp[i].mod->curr.num_traced_exports++;
#if defined(DEBUG) && !defined(BEAMASM)
ep->info.u.op = BeamOpCodeAddr(op_i_func_info_IaaI);
#endif
ep->trampoline.breakpoint.op = BeamOpCodeAddr(op_i_generic_breakpoint);
ep->trampoline.breakpoint.address =
(BeamInstr) ep->dispatch.addresses[code_ix];
}
erts_set_export_trace(ci_rw, match_prog_set);

} else if (!on && flags.breakpoint) {
/* Turn off breakpoint tracing -- nothing to do here. */
} else {
/*
* Turn off global tracing, either explicitly or implicitly
* before turning on breakpoint tracing.
*/
erts_clear_export_trace(ci_rw);
}
}

/*
** So, now for code breakpoint tracing
*/
* First do "local" code breakpoint tracing
*/
erts_bp_match_functions(&finish_bp.f, mfa, specified);

if (on) {
Expand Down Expand Up @@ -2476,6 +2435,47 @@ erts_set_trace_pattern(ErtsCodeMFA *mfa, int specified,
}
}

/*
* Do export entries after module code so breakpoints have been set
* and Export.is_bif_traced can be updated accordingly.
*/
erts_bp_match_export(&finish_bp.e, mfa, specified);

fp = finish_bp.e.matching;
n = finish_bp.e.matched;

for (i = 0; i < n; i++) {
ErtsCodeInfo *ci_rw;
Export* ep;

/* Export entries are always writable, discard const. */
ci_rw = (ErtsCodeInfo *)fp[i].code_info;
ep = ErtsContainerStruct(ci_rw, Export, info);

if (on && !flags.breakpoint) {
/* Turn on global call tracing */
if (!erts_is_export_trampoline_active(ep, code_ix)) {
fp[i].mod->curr.num_traced_exports++;
#if defined(DEBUG) && !defined(BEAMASM)
ep->info.u.op = BeamOpCodeAddr(op_i_func_info_IaaI);
#endif
ep->trampoline.breakpoint.op = BeamOpCodeAddr(op_i_generic_breakpoint);
ep->trampoline.breakpoint.address =
(BeamInstr) ep->dispatch.addresses[code_ix];
}
erts_set_export_trace(ep, match_prog_set);

} else if (!on && flags.breakpoint) {
/* Turn off breakpoint tracing -- nothing to do here. */
} else {
/*
* Turn off global tracing, either explicitly or implicitly
* before turning on breakpoint tracing.
*/
erts_clear_export_trace(ci_rw);
}
}

finish_bp.current = 0;
finish_bp.install = on;
finish_bp.local = flags.breakpoint;
Expand Down Expand Up @@ -2515,15 +2515,10 @@ prepare_clear_all_trace_pattern(ErtsTraceSession* session)

for (i = 0; i < n; i++) {
ErtsCodeInfo *ci_rw;
Export* ep;

/* Export entries are always writable, discard const. */
ci_rw = (ErtsCodeInfo *)fp[i].code_info;
ep = ErtsContainerStruct(ci_rw, Export, info);

if (ep->bif_number != -1) {
ep->is_bif_traced = 0; // ToDo: multi sessions?
}
erts_clear_export_trace(ci_rw);
}

Expand Down Expand Up @@ -2686,8 +2681,7 @@ erts_finish_breakpointing(void)
* deallocate the GenericBp structs for them.
*/
clean_export_entries(&finish_bp.e);
erts_consolidate_export_bp_data(&finish_bp.e);
erts_consolidate_local_bp_data(&finish_bp.f);
erts_consolidate_all_bp_data(&finish_bp.f, &finish_bp.e);
erts_bp_free_matched_functions(&finish_bp.e);
erts_bp_free_matched_functions(&finish_bp.f);
consolidate_event_tracing(erts_staging_trace_session->send_tracing);
Expand Down
76 changes: 76 additions & 0 deletions erts/emulator/test/trace_session_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,8 @@
destroy/1,
negative/1,
error_info/1,
is_bif_traced/1,

end_of_list/1]).

-include_lib("common_test/include/ct.hrl").
Expand Down Expand Up @@ -72,6 +74,8 @@ all() ->
destroy,
negative,
error_info,
is_bif_traced,

end_of_list].

init_per_suite(Config) ->
Expand Down Expand Up @@ -1634,6 +1638,78 @@ tracer_loop(Name, Tester) ->
tracer_loop(Name, Tester).


%% OTP-19840: Verify setting/clearing of 'is_bif_traced' in export entry
%% works correctly for multiple sessions.
is_bif_traced(_Config) ->
CallTypes = [global, local],
[is_bif_traced_do(CT1, CT2, CT3)
|| CT1 <- CallTypes, CT2 <- CallTypes, CT3 <- CallTypes],
ok.

is_bif_traced_do(CT1, CT2, CT3) ->
Tester = self(),
TracerFun = fun F() -> receive M -> Tester ! {self(), M} end, F() end,
T1 = spawn_link(TracerFun),
S1 = trace:session_create(one, T1, []),
trace:function(S1, {erlang,display,1}, true, [CT1]),
trace:process(S1, self(), true, [call]),

erlang:display("S1"),
{T1, {trace,Tester,call,{erlang,display,["S1"]}}} = receive_any(),

T2 = spawn_link(TracerFun),
S2 = trace:session_create(two, T2, []),
trace:function(S2, {erlang,display,1}, true, [CT2]),
trace:process(S2, self(), true, [call]),

erlang:display("S1 & S2"),
receive_parallel_list(
[[{T1, {trace,Tester,call,{erlang,display,["S1 & S2"]}}}],
[{T2, {trace,Tester,call,{erlang,display,["S1 & S2"]}}}]]),

T3 = spawn_link(TracerFun),
S3 = trace:session_create(three, T3, []),
trace:function(S3, {erlang,display,1}, true, [CT3]),
trace:process(S3, self(), true, [call]),

erlang:display("S1 & S2 & S3"),
receive_parallel_list(
[[{T1, {trace,Tester,call,{erlang,display,["S1 & S2 & S3"]}}}],
[{T2, {trace,Tester,call,{erlang,display,["S1 & S2 & S3"]}}}],
[{T3, {trace,Tester,call,{erlang,display,["S1 & S2 & S3"]}}}]]),

%% Remove not last BIF trace nicely
trace:function(S1, {erlang,display,1}, false, [CT1]),
erlang:display("S2 & S3"),
receive_parallel_list(
[[{T2, {trace,Tester,call,{erlang,display,["S2 & S3"]}}}],
[{T3, {trace,Tester,call,{erlang,display,["S2 & S3"]}}}]]),

%% Remove not last BIF trace by session destruction
trace:session_destroy(S2),
erlang:display("S3"),
receive_parallel_list(
[[{T3, {trace,Tester,call,{erlang,display,["S3"]}}}]]),

%% Remove last BIF trace nicely
trace:function(S3, {erlang,display,1}, false, [CT3]),
erlang:display("no trace"),
timeout = receive_any(),

trace:function(S1, {erlang,display,1}, true, [CT1]),
erlang:display("S1"),
receive_parallel_list(
[[{T1, {trace,Tester,call,{erlang,display,["S1"]}}}]]),

%% Remove last BIF trace by session destruction
trace:session_destroy(S1),
erlang:display("no trace"),
timeout = receive_any(),

trace:session_destroy(S3),
ok.


receive_any() ->
receive_any(1000).

Expand Down
Loading