Skip to content

Commit 8dc1ce8

Browse files
committed
Merge 'sverker/erts/trace-bif-session-fix/OTP-19840' into maint
2 parents 58da2c0 + d974e8c commit 8dc1ce8

File tree

6 files changed

+187
-62
lines changed

6 files changed

+187
-62
lines changed

erts/emulator/beam/beam_bif_load.c

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2372,10 +2372,8 @@ delete_code(Module* modp)
23722372
}
23732373
}
23742374

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

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

erts/emulator/beam/beam_bp.c

Lines changed: 48 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -305,8 +305,34 @@ erts_bp_free_matched_functions(BpFunctions* f)
305305
else ASSERT(f->matched == 0);
306306
}
307307

308-
void
309-
erts_consolidate_export_bp_data(BpFunctions* f)
308+
/*
309+
* Return correct value for Export.is_bif_traced.
310+
* true if BIF and breakpoint exist in either export trampoline or code,
311+
* false otherwise.
312+
*/
313+
int erts_export_is_bif_traced(const Export *ep)
314+
{
315+
if (ep->bif_number < 0) {
316+
ASSERT(!ep->is_bif_traced);
317+
return 0;
318+
}
319+
320+
if (ep->info.gen_bp) {
321+
return 1;
322+
}
323+
else {
324+
ErtsCodePtr code = ep->dispatch.addresses[erts_active_code_ix()];
325+
const ErtsCodeInfo *ci = erts_code_to_codeinfo(code);
326+
ASSERT(ci->mfa.module == ep->info.mfa.module);
327+
ASSERT(ci->mfa.function == ep->info.mfa.function);
328+
ASSERT(ci->mfa.arity == ep->info.mfa.arity);
329+
330+
return (ci->gen_bp != NULL);
331+
}
332+
}
333+
334+
static void
335+
consolidate_export_bp_data(BpFunctions* f)
310336
{
311337
BpFunction* fs = f->matching;
312338
Uint i, n;
@@ -318,6 +344,7 @@ erts_consolidate_export_bp_data(BpFunctions* f)
318344
for (i = 0; i < n; i++) {
319345
struct erl_module_instance *mi;
320346
ErtsCodeInfo *ci_rw;
347+
Export* ep;
321348

322349
mi = fs[i].mod ? &fs[i].mod->curr : NULL;
323350

@@ -330,6 +357,9 @@ erts_consolidate_export_bp_data(BpFunctions* f)
330357
mi->code_length));
331358

332359
consolidate_bp_data(mi, ci_rw, 0);
360+
361+
ep = ErtsContainerStruct(ci_rw, Export, info);
362+
ep->is_bif_traced = erts_export_is_bif_traced(ep);
333363
}
334364
}
335365

@@ -371,6 +401,19 @@ erts_consolidate_local_bp_data(BpFunctions* f)
371401
}
372402
}
373403

404+
void
405+
erts_consolidate_all_bp_data(BpFunctions* f, BpFunctions* e)
406+
{
407+
erts_consolidate_local_bp_data(f);
408+
/*
409+
* Must do export entries *after* module code
410+
* so breakpoints in code have been cleared and
411+
* Export.is_bif_traced can be updated accordingly.
412+
*/
413+
consolidate_export_bp_data(e);
414+
}
415+
416+
374417
void
375418
erts_free_breakpoints(void)
376419
{
@@ -716,9 +759,10 @@ erts_set_mtrace_break(BpFunctions* f, Binary *match_spec, ErtsTracer tracer)
716759
}
717760

718761
void
719-
erts_set_export_trace(ErtsCodeInfo *ci, Binary *match_spec)
762+
erts_set_export_trace(Export* ep, Binary *match_spec)
720763
{
721-
set_function_break(ci, match_spec, ERTS_BPF_GLOBAL_TRACE, 0, erts_tracer_nil);
764+
set_function_break(&ep->info, match_spec, ERTS_BPF_GLOBAL_TRACE, 0,
765+
erts_tracer_nil);
722766
}
723767

724768
void

erts/emulator/beam/beam_bp.h

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

148148
void erts_consolidate_local_bp_data(BpFunctions* f);
149-
void erts_consolidate_export_bp_data(BpFunctions* f);
149+
void erts_consolidate_all_bp_data(BpFunctions* f, BpFunctions* e);
150150
void erts_free_breakpoints(void);
151151

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

155-
void erts_set_export_trace(ErtsCodeInfo *ci, Binary *match_spec);
155+
void erts_set_export_trace(Export *ep, Binary *match_spec);
156156
void erts_clear_export_trace(ErtsCodeInfo *ci);
157+
int erts_export_is_bif_traced(const Export*);
157158

158159
void erts_set_mtrace_break(BpFunctions *f, Binary *match_spec, ErtsTracer tracer);
159160
void erts_clear_mtrace_break(BpFunctions *f);

erts/emulator/beam/beam_load.c

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -290,6 +290,8 @@ erts_finish_loading(Binary* magic, Process* c_p,
290290

291291
ASSERT(ep->trampoline.breakpoint.address == 0);
292292
}
293+
ASSERT(!erts_export_is_bif_traced(ep));
294+
ep->is_bif_traced = 0;
293295
}
294296
ASSERT(mod_tab_p->curr.num_breakpoints == 0);
295297
ASSERT(mod_tab_p->curr.num_traced_exports == 0);

erts/emulator/beam/erl_bif_trace.c

Lines changed: 48 additions & 52 deletions
Original file line numberDiff line numberDiff line change
@@ -2415,54 +2415,13 @@ erts_set_trace_pattern(ErtsCodeMFA *mfa, int specified,
24152415
ErtsTracer meta_tracer, int is_blocking)
24162416
{
24172417
const ErtsCodeIndex code_ix = erts_active_code_ix();
2418-
Uint i, n, matches;
2418+
Uint i, n;
2419+
Uint matches = 0;
24192420
BpFunction* fp;
24202421

2421-
erts_bp_match_export(&finish_bp.e, mfa, specified);
2422-
2423-
fp = finish_bp.e.matching;
2424-
n = finish_bp.e.matched;
2425-
matches = 0;
2426-
2427-
for (i = 0; i < n; i++) {
2428-
ErtsCodeInfo *ci_rw;
2429-
Export* ep;
2430-
2431-
/* Export entries are always writable, discard const. */
2432-
ci_rw = (ErtsCodeInfo *)fp[i].code_info;
2433-
ep = ErtsContainerStruct(ci_rw, Export, info);
2434-
2435-
if (ep->bif_number != -1) {
2436-
ep->is_bif_traced = !!on;
2437-
}
2438-
2439-
if (on && !flags.breakpoint) {
2440-
/* Turn on global call tracing */
2441-
if (!erts_is_export_trampoline_active(ep, code_ix)) {
2442-
fp[i].mod->curr.num_traced_exports++;
2443-
#if defined(DEBUG) && !defined(BEAMASM)
2444-
ep->info.u.op = BeamOpCodeAddr(op_i_func_info_IaaI);
2445-
#endif
2446-
ep->trampoline.breakpoint.op = BeamOpCodeAddr(op_i_generic_breakpoint);
2447-
ep->trampoline.breakpoint.address =
2448-
(BeamInstr) ep->dispatch.addresses[code_ix];
2449-
}
2450-
erts_set_export_trace(ci_rw, match_prog_set);
2451-
2452-
} else if (!on && flags.breakpoint) {
2453-
/* Turn off breakpoint tracing -- nothing to do here. */
2454-
} else {
2455-
/*
2456-
* Turn off global tracing, either explicitly or implicitly
2457-
* before turning on breakpoint tracing.
2458-
*/
2459-
erts_clear_export_trace(ci_rw);
2460-
}
2461-
}
2462-
24632422
/*
2464-
** So, now for code breakpoint tracing
2465-
*/
2423+
* First do "local" code breakpoint tracing
2424+
*/
24662425
erts_bp_match_functions(&finish_bp.f, mfa, specified);
24672426

24682427
if (on) {
@@ -2504,6 +2463,49 @@ erts_set_trace_pattern(ErtsCodeMFA *mfa, int specified,
25042463
}
25052464
}
25062465

2466+
/*
2467+
* Do export entries *after* module code, when breakpoints have been set
2468+
* and Export.is_bif_traced can be updated accordingly.
2469+
*/
2470+
erts_bp_match_export(&finish_bp.e, mfa, specified);
2471+
2472+
fp = finish_bp.e.matching;
2473+
n = finish_bp.e.matched;
2474+
2475+
for (i = 0; i < n; i++) {
2476+
ErtsCodeInfo *ci_rw;
2477+
Export* ep;
2478+
2479+
/* Export entries are always writable, discard const. */
2480+
ci_rw = (ErtsCodeInfo *)fp[i].code_info;
2481+
ep = ErtsContainerStruct(ci_rw, Export, info);
2482+
2483+
if (on && !flags.breakpoint) {
2484+
/* Turn on global call tracing */
2485+
if (!erts_is_export_trampoline_active(ep, code_ix)) {
2486+
fp[i].mod->curr.num_traced_exports++;
2487+
#if defined(DEBUG) && !defined(BEAMASM)
2488+
ep->info.u.op = BeamOpCodeAddr(op_i_func_info_IaaI);
2489+
#endif
2490+
ep->trampoline.breakpoint.op = BeamOpCodeAddr(op_i_generic_breakpoint);
2491+
ep->trampoline.breakpoint.address =
2492+
(BeamInstr) ep->dispatch.addresses[code_ix];
2493+
}
2494+
erts_set_export_trace(ep, match_prog_set);
2495+
2496+
} else if (!on && flags.breakpoint) {
2497+
/* Turn off breakpoint tracing -- nothing to do here. */
2498+
} else {
2499+
/*
2500+
* Turn off global tracing, either explicitly or implicitly
2501+
* before turning on breakpoint tracing.
2502+
*/
2503+
erts_clear_export_trace(ci_rw);
2504+
}
2505+
2506+
ep->is_bif_traced = erts_export_is_bif_traced(ep);
2507+
}
2508+
25072509
finish_bp.current = 0;
25082510
finish_bp.install = on;
25092511
finish_bp.local = flags.breakpoint;
@@ -2543,15 +2545,10 @@ prepare_clear_all_trace_pattern(ErtsTraceSession* session)
25432545

25442546
for (i = 0; i < n; i++) {
25452547
ErtsCodeInfo *ci_rw;
2546-
Export* ep;
25472548

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

2552-
if (ep->bif_number != -1) {
2553-
ep->is_bif_traced = 0; // ToDo: multi sessions?
2554-
}
25552552
erts_clear_export_trace(ci_rw);
25562553
}
25572554

@@ -2716,8 +2713,7 @@ erts_finish_breakpointing(void)
27162713
* deallocate the GenericBp structs for them.
27172714
*/
27182715
clean_export_entries(&finish_bp.e);
2719-
erts_consolidate_export_bp_data(&finish_bp.e);
2720-
erts_consolidate_local_bp_data(&finish_bp.f);
2716+
erts_consolidate_all_bp_data(&finish_bp.f, &finish_bp.e);
27212717
erts_bp_free_matched_functions(&finish_bp.e);
27222718
erts_bp_free_matched_functions(&finish_bp.f);
27232719
consolidate_event_tracing(erts_staging_trace_session->send_tracing);

erts/emulator/test/trace_session_SUITE.erl

Lines changed: 84 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,8 @@
4141
destroy/1,
4242
negative/1,
4343
error_info/1,
44+
is_bif_traced/1,
45+
4446
end_of_list/1]).
4547

4648
-include_lib("common_test/include/ct.hrl").
@@ -78,6 +80,8 @@ all() ->
7880
destroy,
7981
negative,
8082
error_info,
83+
is_bif_traced,
84+
8185
end_of_list].
8286

8387
init_per_suite(Config) ->
@@ -1842,6 +1846,86 @@ tracer_loop(Name, Tester) ->
18421846
tracer_loop(Name, Tester).
18431847

18441848

1849+
%% OTP-19840: Verify setting/clearing of 'is_bif_traced' in export entry
1850+
%% works correctly for multiple sessions.
1851+
is_bif_traced(_Config) ->
1852+
CallTypes = [global, local],
1853+
[is_bif_traced_do(CT1, CT2, CT3)
1854+
|| CT1 <- CallTypes, CT2 <- CallTypes, CT3 <- CallTypes],
1855+
ok.
1856+
1857+
is_bif_traced_do(CT1, CT2, CT3) ->
1858+
io:format("CT1=~w, CT2=~w, CT3=~w\n", [CT1, CT2, CT3]),
1859+
1860+
Tester = self(),
1861+
TracerFun = fun F() -> receive M -> Tester ! {self(), M} end, F() end,
1862+
T1 = spawn_link(TracerFun),
1863+
S1 = trace:session_create(one, T1, []),
1864+
1865+
%% A benign BIF call that does not get optimized away
1866+
BIF = {erlang,phash2,1},
1867+
{M,F,A} = BIF,
1868+
true = erlang:is_builtin(M,F,A),
1869+
1870+
trace:function(S1, BIF, true, [CT1]),
1871+
trace:process(S1, self(), true, [call]),
1872+
1873+
M:F("S1"),
1874+
{T1, {trace,Tester,call,{M,F,["S1"]}}} = receive_any(),
1875+
1876+
T2 = spawn_link(TracerFun),
1877+
S2 = trace:session_create(two, T2, []),
1878+
trace:function(S2, BIF, true, [CT2]),
1879+
trace:process(S2, self(), true, [call]),
1880+
1881+
M:F("S1 & S2"),
1882+
receive_parallel_list(
1883+
[[{T1, {trace,Tester,call,{M,F,["S1 & S2"]}}}],
1884+
[{T2, {trace,Tester,call,{M,F,["S1 & S2"]}}}]]),
1885+
1886+
T3 = spawn_link(TracerFun),
1887+
S3 = trace:session_create(three, T3, []),
1888+
trace:function(S3, BIF, true, [CT3]),
1889+
trace:process(S3, self(), true, [call]),
1890+
1891+
M:F("S1 & S2 & S3"),
1892+
receive_parallel_list(
1893+
[[{T1, {trace,Tester,call,{M,F,["S1 & S2 & S3"]}}}],
1894+
[{T2, {trace,Tester,call,{M,F,["S1 & S2 & S3"]}}}],
1895+
[{T3, {trace,Tester,call,{M,F,["S1 & S2 & S3"]}}}]]),
1896+
1897+
%% Remove not last BIF trace nicely
1898+
trace:function(S1, BIF, false, [CT1]),
1899+
M:F("S2 & S3"),
1900+
receive_parallel_list(
1901+
[[{T2, {trace,Tester,call,{M,F,["S2 & S3"]}}}],
1902+
[{T3, {trace,Tester,call,{M,F,["S2 & S3"]}}}]]),
1903+
1904+
%% Remove not last BIF trace by session destruction
1905+
trace:session_destroy(S2),
1906+
M:F("S3"),
1907+
receive_parallel_list(
1908+
[[{T3, {trace,Tester,call,{M,F,["S3"]}}}]]),
1909+
1910+
%% Remove last BIF trace nicely
1911+
trace:function(S3, BIF, false, [CT3]),
1912+
M:F("no trace"),
1913+
receive_nothing(),
1914+
1915+
trace:function(S1, BIF, true, [CT1]),
1916+
M:F("S1"),
1917+
receive_parallel_list(
1918+
[[{T1, {trace,Tester,call,{M,F,["S1"]}}}]]),
1919+
1920+
%% Remove last BIF trace by session destruction
1921+
trace:session_destroy(S1),
1922+
M:F("no trace"),
1923+
receive_nothing(),
1924+
1925+
trace:session_destroy(S3),
1926+
ok.
1927+
1928+
18451929
receive_any() ->
18461930
receive_any(1000).
18471931

0 commit comments

Comments
 (0)