File 1097-erts-Fix-bug-when-resetting-call_time-memory-while-t.patch of Package erlang
From 9e1fa96c2850ae360969331a20f1b7dbcda2fff8 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Wed, 2 Oct 2024 17:21:04 +0200
Subject: [PATCH] erts: Fix bug when resetting call_time/memory while tracing
Clearing the BpDataCallTrace hashes under the feet of executing
processes could cause crash.
Instead allocate a new cleared BpDataCallTrace
for the staged breakpoint.
---
erts/emulator/beam/beam_bp.c | 42 ++++++------
erts/emulator/beam/beam_bp.h | 2 +-
erts/emulator/test/trace_call_time_SUITE.erl | 70 +++++++++++++++++++-
3 files changed, 92 insertions(+), 22 deletions(-)
diff --git a/erts/emulator/beam/beam_bp.c b/erts/emulator/beam/beam_bp.c
index 7f105ce7c4..50c8c6eb90 100644
--- a/erts/emulator/beam/beam_bp.c
+++ b/erts/emulator/beam/beam_bp.c
@@ -121,6 +121,7 @@ static GenericBpData* check_break(const ErtsCodeInfo *ci, Uint break_flags);
static void bp_meta_unref(BpMetaTracer *bmt);
static void bp_count_unref(BpCount *bcp);
+static BpDataTime* bp_time_alloc(void);
static void bp_time_unref(BpDataTime *bdt);
static void consolidate_bp_data(Module *modp, ErtsCodeInfo *ci, int local);
static void uninstall_breakpoint(ErtsCodeInfo *ci);
@@ -380,7 +381,6 @@ consolidate_bp_data(Module* modp, ErtsCodeInfo *ci_rw, int local)
if (flags & ERTS_BPF_TIME_TRACE) {
dst->time = src->time;
erts_refc_inc(&dst->time->refc, 1);
- ASSERT(dst->time->hash);
}
}
@@ -1308,6 +1308,11 @@ static void bp_hash_delete(bp_time_hash_t *hash) {
hash->item = NULL;
}
+static void bp_hash_reset(BpDataTime** bdt_p) {
+ bp_time_unref(*bdt_p);
+ *bdt_p = bp_time_alloc();
+}
+
void erts_schedule_time_break(Process *p, Uint schedule) {
process_breakpoint_time_t *pbt = NULL;
bp_data_time_item_t sitem, *item = NULL;
@@ -1388,6 +1393,7 @@ set_break(BpFunctions* f, Binary *match_spec, Uint break_flags,
}
}
+
static void
set_function_break(ErtsCodeInfo *ci, Binary *match_spec, Uint break_flags,
enum erts_break_op count_op, ErtsTracer tracer)
@@ -1450,17 +1456,11 @@ set_function_break(ErtsCodeInfo *ci, Binary *match_spec, Uint break_flags,
ASSERT((bp->flags & ~ERTS_BPF_ALL) == 0);
return;
} else if (common & ERTS_BPF_TIME_TRACE) {
- BpDataTime* bdt = bp->time;
- Uint i = 0;
-
if (count_op == ERTS_BREAK_PAUSE) {
bp->flags &= ~ERTS_BPF_TIME_TRACE_ACTIVE;
} else {
bp->flags |= ERTS_BPF_TIME_TRACE_ACTIVE;
- for (i = 0; i < bdt->n; i++) {
- bp_hash_delete(&(bdt->hash[i]));
- bp_hash_init(&(bdt->hash[i]), 32);
- }
+ bp_hash_reset(&bp->time);
}
ASSERT((bp->flags & ~ERTS_BPF_ALL) == 0);
return;
@@ -1492,18 +1492,8 @@ set_function_break(ErtsCodeInfo *ci, Binary *match_spec, Uint break_flags,
erts_atomic_init_nob(&bcp->acount, 0);
bp->count = bcp;
} else if (break_flags & ERTS_BPF_TIME_TRACE) {
- BpDataTime* bdt;
- Uint i;
-
ASSERT((bp->flags & ERTS_BPF_TIME_TRACE) == 0);
- bdt = Alloc(sizeof(BpDataTime));
- erts_refc_init(&bdt->refc, 1);
- bdt->n = erts_no_schedulers + 1;
- bdt->hash = Alloc(sizeof(bp_time_hash_t)*(bdt->n));
- for (i = 0; i < bdt->n; i++) {
- bp_hash_init(&(bdt->hash[i]), 32);
- }
- bp->time = bdt;
+ bp->time = bp_time_alloc();
}
bp->flags |= break_flags;
@@ -1578,6 +1568,19 @@ bp_count_unref(BpCount* bcp)
}
}
+static BpDataTime* bp_time_alloc(void)
+{
+ const Uint n = erts_no_schedulers + 1;
+ BpDataTime *bdt = Alloc(offsetof(BpDataTime,hash) +
+ sizeof(bp_time_hash_t)*n);
+ bdt->n = n;
+ erts_refc_init(&bdt->refc, 1);
+ for (Uint i = 0; i < n; i++) {
+ bp_hash_init(&(bdt->hash[i]), 32);
+ }
+ return bdt;
+}
+
static void
bp_time_unref(BpDataTime* bdt)
{
@@ -1587,7 +1590,6 @@ bp_time_unref(BpDataTime* bdt)
for (i = 0; i < bdt->n; ++i) {
bp_hash_delete(&(bdt->hash[i]));
}
- Free(bdt->hash);
Free(bdt);
}
}
diff --git a/erts/emulator/beam/beam_bp.h b/erts/emulator/beam/beam_bp.h
index 3688f08332..d9b786dd1f 100644
--- a/erts/emulator/beam/beam_bp.h
+++ b/erts/emulator/beam/beam_bp.h
@@ -40,8 +40,8 @@ typedef struct {
typedef struct bp_data_time { /* Call time */
Uint n;
- bp_time_hash_t *hash;
erts_refc_t refc;
+ bp_time_hash_t hash[1];
} BpDataTime;
typedef struct {
diff --git a/erts/emulator/test/trace_call_time_SUITE.erl b/erts/emulator/test/trace_call_time_SUITE.erl
index 2da660c881..df22e3d0f1 100644
--- a/erts/emulator/test/trace_call_time_SUITE.erl
+++ b/erts/emulator/test/trace_call_time_SUITE.erl
@@ -35,7 +35,7 @@
-export([seq/3, seq_r/3]).
-export([loaded/1, a_function/1, a_called_function/1, dec/1, nif_dec/1, dead_tracer/1,
- return_stop/1,catch_crash/1]).
+ return_stop/1,reset/1,catch_crash/1]).
-define(US_ERROR, 10000).
-define(R_ERROR, 0.8).
@@ -91,6 +91,7 @@ all() ->
disable_ongoing,
apply_bif_bug,
combo, bif, nif, called_function, dead_tracer, return_stop,
+ reset,
catch_crash].
%% Tests basic call time trace
@@ -633,6 +634,73 @@ spinner(N) ->
quicky() ->
done.
+%% OTP-19269: Verify call_time is reset correctly
+%% while traced functions are called.
+reset(_Config) ->
+ erlang:trace_pattern({'_','_','_'}, false, [call_time]),
+
+ CallTimeReader = fun({P,Cnt,_,_}) -> {P,Cnt} end,
+ reset_do(call_time, true, CallTimeReader),
+ reset_do(call_time, restart, CallTimeReader),
+ ok.
+
+reset_do(TraceType, ResetArg, InfoReader) ->
+ %%
+ 1 = erlang:trace_pattern({?MODULE,aaa, 0}, true, [TraceType]),
+ 1 = erlang:trace_pattern({?MODULE,bbb, 0}, true, [TraceType]),
+
+ Np = erlang:system_info(schedulers_online),
+ Tester = self(),
+ Pids = [begin
+ Pid = spawn_opt(fun() ->
+ receive go -> ok end,
+ aaa(),
+ bbb(),
+ Tester ! {running, self()},
+ loop_aaa_bbb()
+ end,
+ [link, {scheduler,I}]),
+ erlang:trace(Pid, true, [call]),
+ Pid ! go,
+ Pid
+ end
+ || I <- lists:seq(1,Np)],
+
+ %% Wait for all to make at least one traced call
+ [receive {running, P} -> ok end || P <- Pids],
+
+ {TraceType, AAA1} = erlang:trace_info({?MODULE,aaa,0}, TraceType),
+
+ io:format("Reset trace counters for aaa.\n", []),
+ 1 = erlang:trace_pattern({?MODULE,aaa, 0}, ResetArg, [TraceType]),
+
+ {TraceType, AAA2} = erlang:trace_info({?MODULE,aaa,0}, TraceType),
+ {TraceType, BBB} = erlang:trace_info({?MODULE,bbb,0}, TraceType),
+
+ %% Verify counters are sane
+ lists:zipwith3(fun({P, ACnt1}=A1,
+ {P, ACnt2}=A2,
+ {P, BCnt}=B) ->
+ io:format("A1=~p A2=~p B=~p\n", [A1,A2,B]),
+ true = (ACnt1+ACnt2 =< BCnt)
+ end,
+ lists:sort(lists:map(InfoReader, AAA1)),
+ lists:sort(lists:map(InfoReader, AAA2)),
+ lists:sort(lists:map(InfoReader, BBB))),
+
+ [P ! die || P <- Pids],
+ 1 = erlang:trace_pattern({?MODULE,aaa, 0}, false, [TraceType]),
+ 1 = erlang:trace_pattern({?MODULE,bbb, 0}, false, [TraceType]),
+ ok.
+
+loop_aaa_bbb() ->
+ aaa = aaa(),
+ bbb = bbb(),
+ receive die -> ok
+ after 0 -> loop_aaa_bbb()
+ end.
+
+
%% OTP-16994: next_catch returned a bogus stack pointer when call_time tracing
%% was enabled, crashing the emulator.
catch_crash(_Config) ->
--
2.43.0