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 Sep 4, 2024
1 parent 98e7aea commit c484148
Show file tree
Hide file tree
Showing 3 changed files with 115 additions and 25 deletions.
57 changes: 36 additions & 21 deletions erts/doc/guides/match_spec.md
Original file line number Diff line number Diff line change
Expand Up @@ -204,50 +204,65 @@ The functions allowed only for tracing work as follows:
process as a binary. Takes no arguments and is only allowed in the `MatchBody`
part when tracing.

- **`enable_trace`** - With one parameter this function turns on tracing like
the Erlang call `erlang:trace(self(), true, [P2])`, where `P2` is the
parameter to `enable_trace`.
- **`enable_trace`** - Enable a trace flag for a process.

With one parameter this function turns on tracing like
the Erlang call [`trace:process(S, self(), true, [P2])`](`trace:process/4`),
where `S` is the current trace session and `P2` is the parameter to
`enable_trace`.

With two parameters, the first parameter is to be either a process identifier
or the registered name of a process. In this case tracing is turned on for the
designated process in the same way as in the Erlang call
`erlang:trace(P1, true, [P2])`, where `P1` is the first and `P2` is the second
argument. The process `P1` gets its trace messages sent to the same tracer as
the process executing the statement uses. `P1` _cannot_ be one of the atoms
[`trace:process(S, P1, true, [P2])`](`trace:process/4`), where `P1` is the
first and `P2` is the second argument. `P1` _cannot_ be one of the atoms
`all`, `new` or `existing` (unless they are registered names). `P2` _cannot_
be `cpu_timestamp` or `tracer`.

Returns `true` and can only be used in the `MatchBody` part when tracing.

- **`disable_trace`** - With one parameter this function disables tracing like
the Erlang call `erlang:trace(self(), false, [P2])`, where `P2` is the
parameter to `disable_trace`.
If used by the legacy function `erlang:trace_pattern/3`, the process `P1` gets
its trace messages sent to the same tracer as the process executing the
statement uses.

- **`disable_trace`** - Disable a trace flag for a process.

With one parameter this function disables tracing like
the Erlang call [`trace:process(S, self(), false, [P2])`](`trace:process/4`),
where `S` is the current trace session and `P2` is the parameter to
`disable_trace`.

With two parameters this function works as the Erlang call
`erlang:trace(P1, false, [P2])`, where `P1` can be either a process identifier
or a registered name and is specified as the first argument to the match
specification function. `P2` _cannot_ be `cpu_timestamp` or `tracer`.
[`trace:process(S, P1, false, [P2])`](`trace:process/4`), where `P1` can be
either a process identifier or a registered name and is specified as the first
argument to the match specification function. `P2` _cannot_ be `cpu_timestamp`
or `tracer`.

Returns `true` and can only be used in the `MatchBody` part when tracing.

- **`trace`** - With two parameters this function takes a list of trace flags to
- **`trace`** - Enable and/or disable trace flags for a process.

With two parameters this function takes a list of trace flags to
disable as first parameter and a list of trace flags to enable as second
parameter. Logically, the disable list is applied first, but effectively all
changes are applied atomically. The trace flags are the same as for
`erlang:trace/3`, not including `cpu_timestamp`, but including `tracer`.
`trace:process/4`, not including `cpu_timestamp`.

If a tracer is specified in both lists, the tracer in the enable list takes
precedence. If no tracer is specified, the same tracer as the process
With three parameters to this function, the first is either a process
identifier or the registered name of a process to set trace flags on, the
second is the disable list, and the third is the enable list.

When used via the new `m:trace` API, trace flag `tracer` is not allowed and the
receiving tracer is always the tracer of the current session.

When used via the legacy function `erlang:trace_pattern/3`, trace flag `tracer`
is allowed. If no tracer is specified, the same tracer as the process
executing the match specification is used (not the meta tracer). If that
process doesn't have tracer either, then trace flags are ignored.
process doesn't have a tracer either, then trace flags are ignored.

When using a [tracer module](`m:erl_tracer`), the module must be loaded before
the match specification is executed. If it is not loaded, the match fails.

With three parameters to this function, the first is either a process
identifier or the registered name of a process to set trace flags on, the
second is the disable list, and the third is the enable list.

Returns `true` if any trace property was changed for the trace target process,
otherwise `false`. Can only be used in the `MatchBody` part when tracing.

Expand Down
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 c484148

Please sign in to comment.