Skip to content

Commit

Permalink
erts: Use session tracer as default in match spec operations
Browse files Browse the repository at this point in the history
  • Loading branch information
sverker committed Aug 27, 2024
1 parent 98e7aea commit 37d6278
Show file tree
Hide file tree
Showing 2 changed files with 79 additions and 4 deletions.
10 changes: 6 additions & 4 deletions erts/emulator/beam/erl_db_util.c
Original file line number Diff line number Diff line change
Expand Up @@ -219,8 +219,12 @@ set_tracee_flags(Process *tracee_p, ErtsTracer tracer,
}

static ErtsTracer get_proc_tracer(Process* p, ErtsTraceSession* session) {
ErtsTracerRef *ref = get_tracer_ref(&p->common, session);
return ref ? ref->tracer : erts_tracer_nil;
if (!ERTS_TRACER_IS_NIL(session->tracer)) {
return session->tracer;
} else {
ErtsTracerRef *ref = get_tracer_ref(&p->common, session);
return ref ? ref->tracer : erts_tracer_nil;
}
}

static void
Expand Down Expand Up @@ -2788,7 +2792,6 @@ Eterm db_prog_match(Process *c_p,
esp[-1] = FAIL_TERM;
if (n) {
if ( (tmpp = get_proc(c_p, ERTS_PROC_LOCK_MAIN, esp[0], ERTS_PROC_LOCKS_ALL))) {
/* Always take over the tracer of the current process */
ErtsTracer tracer = get_proc_tracer(c_p, prog->trace_session);
set_tracee_flags(tmpp, tracer, prog->trace_session, 0, n);
if (tmpp == c_p)
Expand Down Expand Up @@ -2816,7 +2819,6 @@ Eterm db_prog_match(Process *c_p,
esp[-1] = FAIL_TERM;
if (n) {
if ( (tmpp = get_proc(c_p, ERTS_PROC_LOCK_MAIN, esp[0], ERTS_PROC_LOCKS_ALL))) {
/* Always take over the tracer of the current process */
ErtsTracer tracer = get_proc_tracer(c_p, prog->trace_session);
set_tracee_flags(tmpp, tracer, prog->trace_session, n, 0);
if (tmpp == c_p)
Expand Down
73 changes: 73 additions & 0 deletions erts/emulator/test/trace_session_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@
basic/1,
call/1,
meta/1,
ms_enable_flags/1,
return_to/1,
destroy/1,
negative/1,
Expand Down Expand Up @@ -59,6 +60,7 @@ all() ->
basic,
call,
meta,
ms_enable_flags,
on_load,
trace_info_on_load,
procs,
Expand Down Expand Up @@ -1200,6 +1202,77 @@ meta_do(S1, Tracer1, S2, Tracer2) ->

ok.

%% Test that enable trace flags with match spec on untraced process
%% uses session tracer and not tracer of current process.
ms_enable_flags(_Config) ->
Tester = self(),
Dummy = spawn_link(fun() -> receive die -> ok end end),
Tracer1 = spawn_link(fun() -> tracer("Tracer1",Tester) end),
S1 = trace:session_create(session1, Tracer1, []),

%% Test enable trace flag on current process
Fun = fun(EnableSend, DisableSend) ->
trace:function(S1, {?MODULE,foo,0},
[{'_', [], [EnableSend]}],
[meta]),

foo(),
{Tracer1, {trace_ts, Tester, call, {?MODULE,foo,[]}, {_,_,_}}}
= receive_any(),

{flags, [send]} = trace:info(S1, Tester, flags),
Dummy ! message,
{Tracer1, {trace, Tester, send, message, Dummy}} = receive_any(),

trace:function(S1, {?MODULE,foo,0},
[{'_', [], [DisableSend]}],
[meta]),
Dummy ! message,
{Tracer1, {trace, Tester, send, message, Dummy}} = receive_any(),
foo(),
{Tracer1, {trace_ts, Tester, call, {?MODULE,foo,[]}, {_,_,_}}}
= receive_any(),
{flags, []} = trace:info(S1, Tester, flags),
timeout = receive_nothing(),
ok
end,
Fun({trace, [], [send]}, {trace, [send], []}),
Fun({enable_trace, send}, {disable_trace, send}),

%% Test enable trace flag on other process
Other = spawn_link(fun() -> receive die -> ok end end),
Fun2 = fun(EnableRecv, DisableRecv) ->
trace:function(S1, {?MODULE,foo,0},
[{'_', [], [EnableRecv]}],
[meta]),

foo(),
{Tracer1, {trace_ts, Tester, call, {?MODULE,foo,[]}, {_,_,_}}}
= receive_any(),

{flags, ['receive']} = trace:info(S1, Other, flags),
Other ! message,
{Tracer1, {trace, Other, 'receive', message}} = receive_any(),

trace:function(S1, {?MODULE,foo,0},
[{'_', [], [DisableRecv]}],
[meta]),
Other ! message,
{Tracer1, {trace, Other, 'receive', message}} = receive_any(),
foo(),
{Tracer1, {trace_ts, Tester, call, {?MODULE,foo,[]}, {_,_,_}}}
= receive_any(),
{flags, []} = trace:info(S1, Other, flags),
timeout = receive_nothing(),

ok
end,
Fun2({trace, Other, [], ['receive']}, {trace, Other, ['receive'], []}),
Fun2({enable_trace, Other, 'receive'}, {disable_trace, Other, 'receive'}),

ok.


return_to(_Config) ->
%%put(display, true), %% To get some usable debug printouts

Expand Down

0 comments on commit 37d6278

Please sign in to comment.