Skip to content

Commit 449a07d

Browse files
committed
erts: Fix handling of Export.is_bif_traced for multi sessions
Problem: Export.is_bif_traced was prematurely cleared when the first GenericBp breakpoint was unlinked which caused tracing of the BIF for remaining sessions to be ignored. Solution: Set 'is_bif_traced' if we have at least one GenericBp. Clear 'is_bif_traced' when the last GenericBp disappears.
1 parent c388a2d commit 449a07d

File tree

5 files changed

+185
-65
lines changed

5 files changed

+185
-65
lines changed

erts/emulator/beam/beam_bif_load.c

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2237,10 +2237,7 @@ delete_code(Module* modp)
22372237
}
22382238
}
22392239

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

22452242
ep->trampoline.common.op = BeamOpCodeAddr(op_call_error_handler);
22462243
ep->trampoline.not_loaded.deferred = 0;

erts/emulator/beam/beam_bp.c

Lines changed: 48 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -299,8 +299,34 @@ erts_bp_free_matched_functions(BpFunctions* f)
299299
else ASSERT(f->matched == 0);
300300
}
301301

302-
void
303-
erts_consolidate_export_bp_data(BpFunctions* f)
302+
/*
303+
* Set Export.is_bif_traced for BIFs
304+
* to true if breakpoint exist in either export trampoline or code
305+
* to false otherwise.
306+
*/
307+
void erts_update_export_is_bif_traced(Export *ep)
308+
{
309+
if (ep->bif_number < 0) {
310+
ASSERT(!ep->is_bif_traced);
311+
return;
312+
}
313+
314+
if (ep->info.gen_bp) {
315+
ep->is_bif_traced = 1;
316+
}
317+
else {
318+
ErtsCodePtr code = ep->dispatch.addresses[erts_active_code_ix()];
319+
const ErtsCodeInfo *ci = erts_code_to_codeinfo(code);
320+
ASSERT(ci->mfa.module == ep->info.mfa.module);
321+
ASSERT(ci->mfa.function == ep->info.mfa.function);
322+
ASSERT(ci->mfa.arity == ep->info.mfa.arity);
323+
324+
ep->is_bif_traced = (ci->gen_bp != NULL);
325+
}
326+
}
327+
328+
static void
329+
consolidate_export_bp_data(BpFunctions* f)
304330
{
305331
BpFunction* fs = f->matching;
306332
Uint i, n;
@@ -365,6 +391,19 @@ erts_consolidate_local_bp_data(BpFunctions* f)
365391
}
366392
}
367393

394+
void
395+
erts_consolidate_all_bp_data(BpFunctions* f, BpFunctions* e)
396+
{
397+
erts_consolidate_local_bp_data(f);
398+
/*
399+
* Must do export entries *after* module code
400+
* so breakpoints in code have been cleared and
401+
* Export.is_bif_traced can be updated accordingly.
402+
*/
403+
consolidate_export_bp_data(e);
404+
}
405+
406+
368407
void
369408
erts_free_breakpoints(void)
370409
{
@@ -387,7 +426,7 @@ consolidate_bp_data(struct erl_module_instance *mi,
387426

388427
g = ci_rw->gen_bp;
389428
if (!g) {
390-
return;
429+
return;
391430
}
392431

393432
prev_p = &ci_rw->gen_bp;
@@ -423,7 +462,9 @@ consolidate_bp_data(struct erl_module_instance *mi,
423462
}
424463
#endif
425464
}
426-
465+
if (!local) {
466+
erts_update_export_is_bif_traced(ErtsContainerStruct(ci_rw, Export, info));
467+
}
427468
}
428469

429470

@@ -710,9 +751,10 @@ erts_set_mtrace_break(BpFunctions* f, Binary *match_spec, ErtsTracer tracer)
710751
}
711752

712753
void
713-
erts_set_export_trace(ErtsCodeInfo *ci, Binary *match_spec)
754+
erts_set_export_trace(Export* ep, Binary *match_spec)
714755
{
715-
set_function_break(ci, match_spec, ERTS_BPF_GLOBAL_TRACE, 0, erts_tracer_nil);
756+
set_function_break(&ep->info, match_spec, ERTS_BPF_GLOBAL_TRACE, 0,
757+
erts_tracer_nil);
716758
}
717759

718760
void

erts/emulator/beam/beam_bp.h

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -142,14 +142,15 @@ Uint erts_sum_all_session_flags(ErtsCodeInfo *ci_rw);
142142
void erts_uninstall_breakpoints(BpFunctions* f);
143143

144144
void erts_consolidate_local_bp_data(BpFunctions* f);
145-
void erts_consolidate_export_bp_data(BpFunctions* f);
145+
void erts_consolidate_all_bp_data(BpFunctions* f, BpFunctions* e);
146146
void erts_free_breakpoints(void);
147147

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

151-
void erts_set_export_trace(ErtsCodeInfo *ci, Binary *match_spec);
151+
void erts_set_export_trace(Export *ep, Binary *match_spec);
152152
void erts_clear_export_trace(ErtsCodeInfo *ci);
153+
void erts_update_export_is_bif_traced(Export*);
153154

154155
void erts_set_mtrace_break(BpFunctions *f, Binary *match_spec, ErtsTracer tracer);
155156
void erts_clear_mtrace_break(BpFunctions *f);

erts/emulator/beam/erl_bif_trace.c

Lines changed: 48 additions & 52 deletions
Original file line numberDiff line numberDiff line change
@@ -2387,54 +2387,13 @@ erts_set_trace_pattern(ErtsCodeMFA *mfa, int specified,
23872387
ErtsTracer meta_tracer, int is_blocking)
23882388
{
23892389
const ErtsCodeIndex code_ix = erts_active_code_ix();
2390-
Uint i, n, matches;
2390+
Uint i, n;
2391+
Uint matches = 0;
23912392
BpFunction* fp;
23922393

2393-
erts_bp_match_export(&finish_bp.e, mfa, specified);
2394-
2395-
fp = finish_bp.e.matching;
2396-
n = finish_bp.e.matched;
2397-
matches = 0;
2398-
2399-
for (i = 0; i < n; i++) {
2400-
ErtsCodeInfo *ci_rw;
2401-
Export* ep;
2402-
2403-
/* Export entries are always writable, discard const. */
2404-
ci_rw = (ErtsCodeInfo *)fp[i].code_info;
2405-
ep = ErtsContainerStruct(ci_rw, Export, info);
2406-
2407-
if (ep->bif_number != -1) {
2408-
ep->is_bif_traced = !!on;
2409-
}
2410-
2411-
if (on && !flags.breakpoint) {
2412-
/* Turn on global call tracing */
2413-
if (!erts_is_export_trampoline_active(ep, code_ix)) {
2414-
fp[i].mod->curr.num_traced_exports++;
2415-
#if defined(DEBUG) && !defined(BEAMASM)
2416-
ep->info.u.op = BeamOpCodeAddr(op_i_func_info_IaaI);
2417-
#endif
2418-
ep->trampoline.breakpoint.op = BeamOpCodeAddr(op_i_generic_breakpoint);
2419-
ep->trampoline.breakpoint.address =
2420-
(BeamInstr) ep->dispatch.addresses[code_ix];
2421-
}
2422-
erts_set_export_trace(ci_rw, match_prog_set);
2423-
2424-
} else if (!on && flags.breakpoint) {
2425-
/* Turn off breakpoint tracing -- nothing to do here. */
2426-
} else {
2427-
/*
2428-
* Turn off global tracing, either explicitly or implicitly
2429-
* before turning on breakpoint tracing.
2430-
*/
2431-
erts_clear_export_trace(ci_rw);
2432-
}
2433-
}
2434-
24352394
/*
2436-
** So, now for code breakpoint tracing
2437-
*/
2395+
* First do "local" code breakpoint tracing
2396+
*/
24382397
erts_bp_match_functions(&finish_bp.f, mfa, specified);
24392398

24402399
if (on) {
@@ -2476,6 +2435,49 @@ erts_set_trace_pattern(ErtsCodeMFA *mfa, int specified,
24762435
}
24772436
}
24782437

2438+
/*
2439+
* Do export entries *after* module code, when breakpoints have been set
2440+
* and Export.is_bif_traced can be updated accordingly.
2441+
*/
2442+
erts_bp_match_export(&finish_bp.e, mfa, specified);
2443+
2444+
fp = finish_bp.e.matching;
2445+
n = finish_bp.e.matched;
2446+
2447+
for (i = 0; i < n; i++) {
2448+
ErtsCodeInfo *ci_rw;
2449+
Export* ep;
2450+
2451+
/* Export entries are always writable, discard const. */
2452+
ci_rw = (ErtsCodeInfo *)fp[i].code_info;
2453+
ep = ErtsContainerStruct(ci_rw, Export, info);
2454+
2455+
if (on && !flags.breakpoint) {
2456+
/* Turn on global call tracing */
2457+
if (!erts_is_export_trampoline_active(ep, code_ix)) {
2458+
fp[i].mod->curr.num_traced_exports++;
2459+
#if defined(DEBUG) && !defined(BEAMASM)
2460+
ep->info.u.op = BeamOpCodeAddr(op_i_func_info_IaaI);
2461+
#endif
2462+
ep->trampoline.breakpoint.op = BeamOpCodeAddr(op_i_generic_breakpoint);
2463+
ep->trampoline.breakpoint.address =
2464+
(BeamInstr) ep->dispatch.addresses[code_ix];
2465+
}
2466+
erts_set_export_trace(ep, match_prog_set);
2467+
2468+
} else if (!on && flags.breakpoint) {
2469+
/* Turn off breakpoint tracing -- nothing to do here. */
2470+
} else {
2471+
/*
2472+
* Turn off global tracing, either explicitly or implicitly
2473+
* before turning on breakpoint tracing.
2474+
*/
2475+
erts_clear_export_trace(ci_rw);
2476+
}
2477+
2478+
erts_update_export_is_bif_traced(ep);
2479+
}
2480+
24792481
finish_bp.current = 0;
24802482
finish_bp.install = on;
24812483
finish_bp.local = flags.breakpoint;
@@ -2515,15 +2517,10 @@ prepare_clear_all_trace_pattern(ErtsTraceSession* session)
25152517

25162518
for (i = 0; i < n; i++) {
25172519
ErtsCodeInfo *ci_rw;
2518-
Export* ep;
25192520

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

2524-
if (ep->bif_number != -1) {
2525-
ep->is_bif_traced = 0; // ToDo: multi sessions?
2526-
}
25272524
erts_clear_export_trace(ci_rw);
25282525
}
25292526

@@ -2686,8 +2683,7 @@ erts_finish_breakpointing(void)
26862683
* deallocate the GenericBp structs for them.
26872684
*/
26882685
clean_export_entries(&finish_bp.e);
2689-
erts_consolidate_export_bp_data(&finish_bp.e);
2690-
erts_consolidate_local_bp_data(&finish_bp.f);
2686+
erts_consolidate_all_bp_data(&finish_bp.f, &finish_bp.e);
26912687
erts_bp_free_matched_functions(&finish_bp.e);
26922688
erts_bp_free_matched_functions(&finish_bp.f);
26932689
consolidate_event_tracing(erts_staging_trace_session->send_tracing);

erts/emulator/test/trace_session_SUITE.erl

Lines changed: 85 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,8 @@
3737
destroy/1,
3838
negative/1,
3939
error_info/1,
40+
is_bif_traced/1,
41+
4042
end_of_list/1]).
4143

4244
-include_lib("common_test/include/ct.hrl").
@@ -72,6 +74,8 @@ all() ->
7274
destroy,
7375
negative,
7476
error_info,
77+
is_bif_traced,
78+
7579
end_of_list].
7680

7781
init_per_suite(Config) ->
@@ -1634,6 +1638,86 @@ tracer_loop(Name, Tester) ->
16341638
tracer_loop(Name, Tester).
16351639

16361640

1641+
%% OTP-19840: Verify setting/clearing of 'is_bif_traced' in export entry
1642+
%% works correctly for multiple sessions.
1643+
is_bif_traced(_Config) ->
1644+
CallTypes = [global, local],
1645+
[is_bif_traced_do(CT1, CT2, CT3)
1646+
|| CT1 <- CallTypes, CT2 <- CallTypes, CT3 <- CallTypes],
1647+
ok.
1648+
1649+
is_bif_traced_do(CT1, CT2, CT3) ->
1650+
io:format("CT1=~w, CT2=~w, CT3=~w\n", [CT1, CT2, CT3]),
1651+
1652+
Tester = self(),
1653+
TracerFun = fun F() -> receive M -> Tester ! {self(), M} end, F() end,
1654+
T1 = spawn_link(TracerFun),
1655+
S1 = trace:session_create(one, T1, []),
1656+
1657+
%% A benign BIF call that does not get optimized away
1658+
BIF = {erlang,phash2,1},
1659+
{M,F,A} = BIF,
1660+
true = erlang:is_builtin(M,F,A),
1661+
1662+
trace:function(S1, BIF, true, [CT1]),
1663+
trace:process(S1, self(), true, [call]),
1664+
1665+
M:F("S1"),
1666+
{T1, {trace,Tester,call,{M,F,["S1"]}}} = receive_any(),
1667+
1668+
T2 = spawn_link(TracerFun),
1669+
S2 = trace:session_create(two, T2, []),
1670+
trace:function(S2, BIF, true, [CT2]),
1671+
trace:process(S2, self(), true, [call]),
1672+
1673+
M:F("S1 & S2"),
1674+
receive_parallel_list(
1675+
[[{T1, {trace,Tester,call,{M,F,["S1 & S2"]}}}],
1676+
[{T2, {trace,Tester,call,{M,F,["S1 & S2"]}}}]]),
1677+
1678+
T3 = spawn_link(TracerFun),
1679+
S3 = trace:session_create(three, T3, []),
1680+
trace:function(S3, BIF, true, [CT3]),
1681+
trace:process(S3, self(), true, [call]),
1682+
1683+
M:F("S1 & S2 & S3"),
1684+
receive_parallel_list(
1685+
[[{T1, {trace,Tester,call,{M,F,["S1 & S2 & S3"]}}}],
1686+
[{T2, {trace,Tester,call,{M,F,["S1 & S2 & S3"]}}}],
1687+
[{T3, {trace,Tester,call,{M,F,["S1 & S2 & S3"]}}}]]),
1688+
1689+
%% Remove not last BIF trace nicely
1690+
trace:function(S1, BIF, false, [CT1]),
1691+
M:F("S2 & S3"),
1692+
receive_parallel_list(
1693+
[[{T2, {trace,Tester,call,{M,F,["S2 & S3"]}}}],
1694+
[{T3, {trace,Tester,call,{M,F,["S2 & S3"]}}}]]),
1695+
1696+
%% Remove not last BIF trace by session destruction
1697+
trace:session_destroy(S2),
1698+
M:F("S3"),
1699+
receive_parallel_list(
1700+
[[{T3, {trace,Tester,call,{M,F,["S3"]}}}]]),
1701+
1702+
%% Remove last BIF trace nicely
1703+
trace:function(S3, BIF, false, [CT3]),
1704+
M:F("no trace"),
1705+
receive_nothing(),
1706+
1707+
trace:function(S1, BIF, true, [CT1]),
1708+
M:F("S1"),
1709+
receive_parallel_list(
1710+
[[{T1, {trace,Tester,call,{M,F,["S1"]}}}]]),
1711+
1712+
%% Remove last BIF trace by session destruction
1713+
trace:session_destroy(S1),
1714+
M:F("no trace"),
1715+
receive_nothing(),
1716+
1717+
trace:session_destroy(S3),
1718+
ok.
1719+
1720+
16371721
receive_any() ->
16381722
receive_any(1000).
16391723

@@ -1643,7 +1727,7 @@ receive_any(Timeout) ->
16431727
end.
16441728

16451729
receive_nothing() ->
1646-
receive_any(10).
1730+
timeout = receive_any(10).
16471731

16481732
%% Argument is a tuple of lists with expected messages to receive.
16491733
%% Each list is internally ordered according to expected reception.

0 commit comments

Comments
 (0)