File 6032-erts-Refactor-StackTrace-to-include-max_depth.patch of Package erlang

From c2e3978c343e93e852e7535d11b67bcc96269b11 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Wed, 23 Oct 2024 19:35:08 +0200
Subject: [PATCH 2/3] erts: Refactor StackTrace to include max_depth

Just to simplify.
On 64-bit sizeof(StackTrace) is unchanged due to struct padding.
---
 erts/emulator/beam/beam_common.c  | 30 +++++++++++++-----------------
 erts/emulator/beam/bif.c          |  1 +
 erts/emulator/beam/erl_bif_info.c | 15 ++++++---------
 erts/emulator/beam/erl_db_util.c  | 15 ++++++++-------
 erts/emulator/beam/error.h        |  3 ++-
 erts/emulator/beam/global.h       |  2 +-
 6 files changed, 31 insertions(+), 35 deletions(-)

diff --git a/erts/emulator/beam/beam_common.c b/erts/emulator/beam/beam_common.c
index d7e12a5fc7..cdcbb6d8dd 100644
--- a/erts/emulator/beam/beam_common.c
+++ b/erts/emulator/beam/beam_common.c
@@ -770,12 +770,13 @@ expand_error_value(Process* c_p, Uint freason, Eterm Value) {
 
 
 static void
-gather_stacktrace(Process* p, struct StackTrace* s, int depth)
+gather_stacktrace(Process* p, struct StackTrace* s)
 {
     ErtsCodePtr prev;
     Eterm *ptr;
 
-    if (depth == 0) {
+    if (s->depth >= s->max_depth) {
+        ASSERT(s->depth == s->max_depth);
         return;
     }
 
@@ -791,7 +792,7 @@ gather_stacktrace(Process* p, struct StackTrace* s, int depth)
 
     ASSERT(ptr >= STACK_TOP(p) && ptr <= STACK_START(p));
 
-    while (ptr < STACK_START(p) && depth > 0) {
+    while (ptr < STACK_START(p) && s->depth < s->max_depth) {
         if (is_CP(*ptr)) {
             ErtsCodePtr return_address;
 
@@ -822,7 +823,6 @@ gather_stacktrace(Process* p, struct StackTrace* s, int depth)
 #endif
 
                     s->trace[s->depth++] = adjusted_address;
-                    depth--;
                 }
 
                 ptr += CP_SIZE;
@@ -872,22 +872,19 @@ save_stacktrace(Process* c_p, ErtsCodePtr pc, Eterm* reg,
                 const ErtsCodeMFA *bif_mfa, Eterm args) {
     struct StackTrace* s;
     int sz;
-    int depth = erts_backtrace_depth;    /* max depth (never negative) */
+    /* Max depth (never negative), -1 as there is always a current function. */
+    const int max_depth = MAX(erts_backtrace_depth - 1, 0);
     Eterm error_info = THE_NON_VALUE;
 
-    if (depth > 0) {
-	/* There will always be a current function */
-	depth --;
-    }
-
-    /* Create a container for the exception data */
-    sz = (offsetof(struct StackTrace, trace) + sizeof(ErtsCodePtr) * depth
+    /* Create a bignum container for the stack trace */
+    sz = (offsetof(struct StackTrace, trace) + sizeof(ErtsCodePtr) * max_depth
           + sizeof(Eterm) - 1) / sizeof(Eterm);
     s = (struct StackTrace *) HAlloc(c_p, sz);
     /* The following fields are inside the bignum */
     s->header = make_pos_bignum_header(sz - 1);
     s->freason = c_p->freason;
     s->depth = 0;
+    s->max_depth = max_depth;
 
     /*
      * If the failure was in a BIF other than 'error/1', 'error/2',
@@ -919,9 +916,8 @@ save_stacktrace(Process* c_p, ErtsCodePtr pc, Eterm* reg,
 	s->current = bif_mfa;
 	/* Save first stack entry */
 	ASSERT(pc);
-	if (depth > 0) {
+	if (s->depth < max_depth) {
 	    s->trace[s->depth++] = pc;
-	    depth--;
 	}
 	s->pc = NULL;
 
@@ -1047,13 +1043,13 @@ save_stacktrace(Process* c_p, ErtsCodePtr pc, Eterm* reg,
     }
 
     /* Save the actual stack trace */
-    gather_stacktrace(c_p, s, depth);
+    gather_stacktrace(c_p, s);
 }
 
 void
-erts_save_stacktrace(Process* p, struct StackTrace* s, int depth)
+erts_save_stacktrace(Process* p, struct StackTrace* s)
 {
-    gather_stacktrace(p, s, depth);
+    gather_stacktrace(p, s);
 }
 
 /*
diff --git a/erts/emulator/beam/bif.c b/erts/emulator/beam/bif.c
index 9b3f04f436..eb39ea961a 100644
--- a/erts/emulator/beam/bif.c
+++ b/erts/emulator/beam/bif.c
@@ -1440,6 +1440,7 @@ BIF_RETTYPE raise_3(BIF_ALIST_3)
     s->pc = NULL;
     s->current = NULL;
     s->depth = 0;
+    s->max_depth = 0;
     hp += sz;
     if (must_copy) {
 	int cnt;
diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c
index d239d05e2a..c2bd395ad3 100644
--- a/erts/emulator/beam/erl_bif_info.c
+++ b/erts/emulator/beam/erl_bif_info.c
@@ -2368,7 +2368,6 @@ erts_build_stacktrace(ErtsHeapFactory* hfact, Process* rp,
 {
     Uint sz;
     struct StackTrace* s;
-    int depth;
     FunctionInfo* stk;
     FunctionInfo* stkp;
     Uint heap_size;
@@ -2377,23 +2376,21 @@ erts_build_stacktrace(ErtsHeapFactory* hfact, Process* rp,
     Eterm mfa;
     Eterm res = NIL;
 
-    depth = max_depth;
-    sz = offsetof(struct StackTrace, trace) + sizeof(ErtsCodePtr) * depth;
+    sz = offsetof(struct StackTrace, trace) + sizeof(ErtsCodePtr) * max_depth;
     s = (struct StackTrace *) erts_alloc(ERTS_ALC_T_TMP, sz);
     s->depth = 0;
+    s->max_depth = max_depth;
     s->pc = NULL;
 
-    if (include_i && depth > 0 && rp->i) {
+    if (include_i && max_depth > 0 && rp->i) {
         s->trace[s->depth++] = rp->i;
-        depth--;
     }
-    erts_save_stacktrace(rp, s, depth);
+    erts_save_stacktrace(rp, s);
 
-    depth = s->depth;
     stk = stkp = (FunctionInfo *) erts_alloc(ERTS_ALC_T_TMP,
-					     depth*sizeof(FunctionInfo));
+					     s->depth * sizeof(FunctionInfo));
     heap_size = 3;
-    for (i = 0; i < depth; i++) {
+    for (i = 0; i < s->depth; i++) {
 	erts_lookup_function_info(stkp, s->trace[i], 1);
 	if (stkp->mfa) {
 	    heap_size += stkp->needed + 2;
diff --git a/erts/emulator/beam/erl_db_util.c b/erts/emulator/beam/erl_db_util.c
index 1c0fc44e22..cf5e96f221 100644
--- a/erts/emulator/beam/erl_db_util.c
+++ b/erts/emulator/beam/erl_db_util.c
@@ -2901,28 +2901,29 @@ restart:
             Eterm mfa;
             Eterm res;
             struct StackTrace *s;
-            int depth;
+            int max_depth;
             FunctionInfo* stk;
             FunctionInfo* stkp;
 
             ASSERT(c_p == self);
 
-            depth = unsigned_val(esp[-1]);
+            max_depth = unsigned_val(esp[-1]);
+            ASSERT(max_depth >= 0 && max_depth <= MAX_BACKTRACE_SIZE);
             esp--;
 
-            sz = offsetof(struct StackTrace, trace) + sizeof(ErtsCodePtr) * depth;
+            sz = offsetof(struct StackTrace, trace) + sizeof(ErtsCodePtr) * max_depth;
             s = (struct StackTrace *) erts_alloc(ERTS_ALC_T_TMP, sz);
             s->depth = 0;
+            s->max_depth = max_depth;
             s->pc = NULL;
 
-            erts_save_stacktrace(c_p, s, depth);
+            erts_save_stacktrace(c_p, s);
 
-            depth = s->depth;
             stk = stkp = (FunctionInfo *) erts_alloc(ERTS_ALC_T_TMP,
-                                                     depth*sizeof(FunctionInfo));
+                                                     s->depth * sizeof(FunctionInfo));
 
             heap_size = 0;
-            for (i = 0; i < depth; i++) {
+            for (i = 0; i < s->depth; i++) {
                 erts_lookup_function_info(stkp, s->trace[i], 1);
                 if (stkp->mfa) {
                     heap_size += stkp->needed + 2;
diff --git a/erts/emulator/beam/error.h b/erts/emulator/beam/error.h
index e307f3ed6d..14c650811d 100644
--- a/erts/emulator/beam/error.h
+++ b/erts/emulator/beam/error.h
@@ -218,7 +218,8 @@ struct StackTrace {
     Eterm freason; /* original exception reason is saved in the struct */
     ErtsCodePtr pc;
     const ErtsCodeMFA* current;
-    int depth;	/* number of saved pointers in trace[] */
+    int depth;	   /* number of saved pointers in trace[] */
+    int max_depth; /* capacity of trace[] */
     ErtsCodePtr trace[1];  /* varying size - must be last in struct */
 };
 
diff --git a/erts/emulator/beam/global.h b/erts/emulator/beam/global.h
index 218aea136a..c172ac0df5 100644
--- a/erts/emulator/beam/global.h
+++ b/erts/emulator/beam/global.h
@@ -1215,7 +1215,7 @@ void erts_prepare_bs_construct_fail_info(Process* c_p, const BeamInstr* p, Eterm
 void erts_dirty_process_main(ErtsSchedulerData *);
 Eterm build_stacktrace(Process* c_p, Eterm exc);
 Eterm expand_error_value(Process* c_p, Uint freason, Eterm Value);
-void erts_save_stacktrace(Process* p, struct StackTrace* s, int depth);
+void erts_save_stacktrace(Process* p, struct StackTrace* s);
 ErtsCodePtr erts_printable_return_address(Process* p, Eterm *E) ERTS_NOINLINE;
 
 /* erl_init.c */
-- 
2.43.0

openSUSE Build Service is sponsored by