Skip to content

Commit

Permalink
Optimize the normal case where ErtsTracer is a local pid
Browse files Browse the repository at this point in the history
Instead of [erl_tracer | pid] just store the pid.
  • Loading branch information
sverker committed Jul 11, 2024
1 parent 6b21389 commit 84b9a73
Show file tree
Hide file tree
Showing 4 changed files with 24 additions and 10 deletions.
4 changes: 2 additions & 2 deletions erts/emulator/beam/erl_ptab.h
Original file line number Diff line number Diff line change
Expand Up @@ -49,8 +49,8 @@ typedef struct ErtsTracee_ {
ErtsTracerRef *first_ref;
} ErtsTracee;

#define ERTS_TRACER_MODULE(T) (CAR(list_val(T)))
#define ERTS_TRACER_STATE(T) (CDR(list_val(T)))
#define ERTS_TRACER_MODULE(T) (is_internal_pid(T) ? am_erl_tracer : CAR(list_val(T)))
#define ERTS_TRACER_STATE(T) (is_internal_pid(T) ? T : CDR(list_val(T)))

#define ERTS_P_LINKS(P) ((P)->common.u.alive.links)
#define ERTS_P_MONITORS(P) ((P)->common.u.alive.monitors)
Expand Down
24 changes: 18 additions & 6 deletions erts/emulator/beam/erl_trace.c
Original file line number Diff line number Diff line change
Expand Up @@ -3087,7 +3087,11 @@ erts_term_to_tracer(Eterm prefix, Eterm t)
{
ErtsTracer tracer = erts_tracer_nil;
ASSERT(is_atom(prefix) || prefix == THE_NON_VALUE);
if (!is_nil(t)) {

if (is_internal_pid(t)) {
tracer = t;
}
else if (!is_nil(t)) {
Eterm module = am_erl_tracer, state = THE_NON_VALUE;
Eterm hp[2];
if (is_tuple(t)) {
Expand Down Expand Up @@ -3440,7 +3444,7 @@ bool erts_get_tracer_pid(ErtsTracer tracer, Eterm* pid)
}

/*
* ErtsTracer is either NIL, 'true' or [Mod | State]
* ErtsTracer is either NIL, 'true', local pid or [Mod | State]
*
* - If State is immediate then the memory for
* the cons cell is just two words + sizeof(ErtsThrPrgrLaterOp) large.
Expand All @@ -3465,15 +3469,15 @@ bool erts_get_tracer_pid(ErtsTracer tracer, Eterm* pid)
* the refc when *tracer is NIL.
*/
void
erts_tracer_update_impl(ErtsTracer *tracer, const ErtsTracer new_tracer)
erts_tracer_update_impl(ErtsTracer *tracer, ErtsTracer new_tracer)
{
ErlHeapFragment *hf;

if (is_not_nil(*tracer)) {
if (is_list(*tracer)) {
Uint offs = 2;
UWord size = 2 * sizeof(Eterm) + sizeof(ErtsThrPrgrLaterOp);
ErtsThrPrgrLaterOp *lop;
ASSERT(is_list(*tracer));

if (is_not_immed(ERTS_TRACER_STATE(*tracer))) {
hf = ErtsContainerStruct_(ptr_val(*tracer), ErlHeapFragment, mem);
offs = hf->used_size;
Expand All @@ -3500,7 +3504,15 @@ erts_tracer_update_impl(ErtsTracer *tracer, const ErtsTracer new_tracer)
free_tracer, (void*)(*tracer), lop, size);
}

if (is_nil(new_tracer)) {
if (is_list(new_tracer)) {
const Eterm module = ERTS_TRACER_MODULE(new_tracer);
const Eterm state = ERTS_TRACER_STATE(new_tracer);
if (module == am_erl_tracer && is_internal_pid(state)) {
new_tracer = state;
}
}
if (is_immed(new_tracer)) {
ASSERT(is_nil(new_tracer) || is_internal_pid(new_tracer));
*tracer = new_tracer;
} else if (is_immed(ERTS_TRACER_STATE(new_tracer))) {
/* If tracer state is an immediate we only allocate a 2 Eterm heap.
Expand Down
1 change: 1 addition & 0 deletions erts/emulator/beam/erl_trace.h
Original file line number Diff line number Diff line change
Expand Up @@ -317,6 +317,7 @@ ERTS_DECLARE_DUMMY(erts_tracer_nil) = NIL;
#define IS_TRACER_VALID(tracer) \
(ERTS_TRACER_COMPARE(tracer,erts_tracer_true) \
|| ERTS_TRACER_IS_NIL(tracer) \
|| is_internal_pid(tracer) \
|| (is_list(tracer) && is_atom(CAR(list_val(tracer)))))

#define ERTS_TRACER_FROM_ETERM(termp) \
Expand Down
5 changes: 3 additions & 2 deletions erts/emulator/beam/sys.h
Original file line number Diff line number Diff line change
Expand Up @@ -704,12 +704,13 @@ typedef struct preload {
} Preload;

/*
* ErtsTracer is either NIL, 'true' or [Mod | State]
* ErtsTracer is either NIL, 'true', LocalPid or [Mod | State]
*
* If set to NIL, it means no tracer.
* If set to 'true' it means the current process' tracer.
* If set to [Mod | State], there is a tracer.
* See erts_tracer_update for more details
* LocalPid is the optimized form of the common case [erl_tracer | LocalPid].
* See erts_tracer_update_impl for more details
*/
typedef Eterm ErtsTracer;

Expand Down

0 comments on commit 84b9a73

Please sign in to comment.