File 2741-erts-Add-current-stack-trace-to-tracing.patch of Package erlang

From 99c35190efafb3c4f5499ae4c9376b03371d44ba Mon Sep 17 00:00:00 2001
From: jdamanalo <jamanalo5@up.edu.ph>
Date: Wed, 4 Jan 2023 12:34:08 +0800
Subject: [PATCH] erts: Add current stack trace to tracing

---
 erts/doc/src/match_spec.xml             |  15 ++-
 erts/emulator/beam/erl_db_util.c        | 116 +++++++++++++++++++++++
 erts/emulator/test/match_spec_SUITE.erl | 117 +++++++++++++++++++++++-
 3 files changed, 244 insertions(+), 4 deletions(-)

diff --git a/erts/doc/src/match_spec.xml b/erts/doc/src/match_spec.xml
index 62ddefdc47..8b85c39623 100644
--- a/erts/doc/src/match_spec.xml
+++ b/erts/doc/src/match_spec.xml
@@ -142,7 +142,7 @@
         <c><![CDATA[process_dump]]></c> | <c><![CDATA[enable_trace]]></c> |
         <c><![CDATA[disable_trace]]></c> | <c><![CDATA[trace]]></c> |
         <c><![CDATA[display]]></c> | <c><![CDATA[caller]]></c> |
-        <c><![CDATA[caller_line]]></c> |
+        <c><![CDATA[caller_line]]></c> | <c><![CDATA[current_stacktrace]]></c> |
         <c><![CDATA[set_tcw]]></c> | <c><![CDATA[silent]]></c>
       </item>
     </list>
@@ -463,6 +463,19 @@
              <c><![CDATA[undefined]]></c>. The calling
              Erlang function is not available during such calls.</p>
         </item>
+        <tag><c>current_stacktrace</c></tag>
+        <item>
+          <p>Returns the current call stack back-trace
+            (<seetype marker="erts:erlang#stacktrace">stacktrace</seetype>)
+            of the calling function. The stack has the same format as in the
+            <c>catch</c> part of a <c>try</c>. See <seeguide
+            marker="system/reference_manual:errors#stacktrace">The call-stack back trace (stacktrace)</seeguide>.
+            The depth of the stacktrace is truncated according to the
+            <c>backtrace_depth</c> system flag setting.</p>
+
+          <p>Accepts a depth parameter. The depth value will be
+            <c>backtrace_depth</c> if the argument is greater.</p>
+        </item>
         <tag><c>display</c></tag>
           <item>
             <p>For debugging purposes only. Displays the single argument as an
diff --git a/erts/emulator/beam/erl_db_util.c b/erts/emulator/beam/erl_db_util.c
index e05c552c0e..8082405dd4 100644
--- a/erts/emulator/beam/erl_db_util.c
+++ b/erts/emulator/beam/erl_db_util.c
@@ -295,6 +295,7 @@ typedef enum {
     matchTrace2,
     matchTrace3,
     matchCallerLine,
+    matchCurrentStacktrace
 } MatchOps;
 
 /*
@@ -2804,6 +2805,64 @@ restart:
                }
             }
             break;
+        case matchCurrentStacktrace: {
+            Uint sz;
+            Uint heap_size;
+            Eterm mfa;
+            Eterm res;
+            struct StackTrace *s;
+            int depth;
+            FunctionInfo* stk;
+            FunctionInfo* stkp;
+
+            ASSERT(c_p == self);
+
+            depth = unsigned_val(esp[-1]);
+            esp--;
+
+            sz = offsetof(struct StackTrace, trace) + sizeof(ErtsCodePtr) * depth;
+            s = (struct StackTrace *) erts_alloc(ERTS_ALC_T_TMP, sz);
+            s->depth = 0;
+            s->pc = NULL;
+
+            erts_save_stacktrace(c_p, s, depth);
+
+            depth = s->depth;
+            stk = stkp = (FunctionInfo *) erts_alloc(ERTS_ALC_T_TMP,
+                                                     depth*sizeof(FunctionInfo));
+
+            heap_size = 0;
+            for (i = 0; i < depth; i++) {
+                erts_lookup_function_info(stkp, s->trace[i], 1);
+                if (stkp->mfa) {
+                    heap_size += stkp->needed + 2;
+                    stkp++;
+                }
+            }
+
+            res = NIL;
+
+            if (heap_size > 0) {
+                int count = stkp - stk;
+
+                ASSERT(count > 0 && count <= MAX_BACKTRACE_SIZE);
+
+                ehp = HAllocX(build_proc, heap_size, HEAP_XTRA);
+
+                for (i = count - 1; i >= 0; i--) {
+                    ehp = erts_build_mfa_item(&stk[i], ehp, am_true, &mfa, NIL);
+                    res = CONS(ehp, mfa, res);
+                    ehp += 2;
+                }
+            }
+
+            *esp++ = res;
+
+            erts_free(ERTS_ALC_T_TMP, stk);
+            erts_free(ERTS_ALC_T_TMP, s);
+
+            break;
+        }
         case matchSilent:
             ASSERT(c_p == self);
 	    --esp;
@@ -4970,6 +5029,57 @@ static DMCRet dmc_caller_line(DMCContext *context,
     return retOk;
 }
 
+static DMCRet dmc_current_stacktrace(DMCContext *context,
+                                    DMCHeap *heap,
+                                    DMC_STACK_TYPE(UWord) *text,
+                                    Eterm t,
+                                    int *constant)
+{
+    Eterm *p = tuple_val(t);
+    Uint a = arityval(*p);
+    DMCRet ret;
+    int depth;
+
+    if (!check_trace("current_stacktrace", context, constant,
+                    (DCOMP_CALL_TRACE|DCOMP_ALLOW_TRACE_OPS), 0, &ret))
+        return ret;
+
+    switch (a) {
+    case 1:
+        *constant = 0;
+        do_emit_constant(context, text, make_small(erts_backtrace_depth));
+        DMC_PUSH(*text, matchCurrentStacktrace);
+        break;
+    case 2:
+        *constant = 0;
+
+        if (!is_small(p[2])) {
+            RETURN_ERROR("Special form 'current_stacktrace' called with non "
+                         "small argument.", context, *constant);
+        }
+
+        depth = signed_val(p[2]);
+
+        if (depth < 0) {
+            RETURN_ERROR("Special form 'current_stacktrace' called with "
+                         "negative integer argument.", context, *constant);
+        }
+
+        if (depth > erts_backtrace_depth) {
+            p[2] = make_small(erts_backtrace_depth);
+        }
+
+        do_emit_constant(context, text, p[2]);
+        DMC_PUSH(*text, matchCurrentStacktrace);
+        break;
+    default:
+        RETURN_TERM_ERROR("Special form 'current_stacktrace' called with wrong "
+                          "number of arguments in %T.", t, context,
+                          *constant);
+    }
+    return retOk;
+}
+
 static DMCRet dmc_silent(DMCContext *context,
  			 DMCHeap *heap,
 			 DMC_STACK_TYPE(UWord) *text,
@@ -5058,6 +5168,8 @@ static DMCRet dmc_fun(DMCContext *context,
 	return dmc_caller(context, heap, text, t, constant);
     case am_caller_line:
 	return dmc_caller_line(context, heap, text, t, constant);
+    case am_current_stacktrace:
+	return dmc_current_stacktrace(context, heap, text, t, constant);
     case am_silent:
  	return dmc_silent(context, heap, text, t, constant);
     case am_set_tcw:
@@ -6126,6 +6238,10 @@ void db_match_dis(Binary *bp)
 	    ++t;
 	    erts_printf("CallerLine\n");
 	    break;
+	case matchCurrentStacktrace:
+	    ++t;
+	    erts_printf("CurrentStacktrace\n");
+	    break;
 	default:
 	    erts_printf("??? (0x%bpx)\n", *t);
 	    ++t;
diff --git a/erts/emulator/test/match_spec_SUITE.erl b/erts/emulator/test/match_spec_SUITE.erl
index eadddfe312..c33b26374f 100644
--- a/erts/emulator/test/match_spec_SUITE.erl
+++ b/erts/emulator/test/match_spec_SUITE.erl
@@ -23,7 +23,7 @@
 -export([all/0, suite/0]).
 -export([init_per_testcase/2, end_per_testcase/2]).
 -export([test_1/1, test_2/1, test_3/1, test_4a/1, test_4b/1, test_5a/1,
-         test_5b/1, caller_and_return_to/1, bad_match_spec_bin/1,
+         test_5b/1, test_6/1, caller_and_return_to/1, bad_match_spec_bin/1,
 	 trace_control_word/1, silent/1, silent_no_ms/1, silent_test/1,
 	 ms_trace2/1, ms_trace3/1, ms_trace_dead/1, boxed_and_small/1,
 	 destructive_in_test_bif/1, guard_exceptions/1,
@@ -33,7 +33,7 @@
 -export([otp_9422/1]).
 -export([faulty_seq_trace/1, do_faulty_seq_trace/0]).
 -export([maps/1]).
--export([runner/2, loop_runner/3]).
+-export([runner/2, loop_runner/3, fixed_runner/2]).
 -export([f1/1, f2/2, f3/2, fn/1, fn/2, fn/3]).
 -export([do_boxed_and_small/0]).
 -export([f1_test4/1, f2_test4/2, f3_test4/2]).
@@ -48,7 +48,8 @@ suite() ->
      {timetrap, {minutes, 1}}].
 
 all() ->
-    [test_1, test_2, test_3, test_4a, test_4b, test_5a, test_5b, caller_and_return_to, bad_match_spec_bin,
+    [test_1, test_2, test_3, test_4a, test_4b, test_5a, test_5b, test_6,
+     caller_and_return_to, bad_match_spec_bin,
      trace_control_word, silent, silent_no_ms, silent_test, ms_trace2,
      ms_trace3, ms_trace_dead, boxed_and_small, destructive_in_test_bif,
      guard_exceptions, unary_plus, unary_minus, fpe,
@@ -239,6 +240,86 @@ test_5b(Config) when is_list(Config) ->
                ]),
     ok.
 
+%% Test current_stacktrace/[0,1]
+test_6(Config) when is_list(Config) ->
+    %% Test non small argument
+    case catch erlang:trace_pattern({?MODULE, f2_test6, '_'},
+                                    [{'_', [], [{message, {current_stacktrace, a}}]}]) of
+        {'EXIT', {badarg, _}} -> ok;
+        Other1 -> ct:fail({noerror, Other1})
+    end,
+
+    %% Test negative
+    case catch erlang:trace_pattern({?MODULE, f2_test6, '_'},
+                                    [{'_', [], [{message, {current_stacktrace, -1}}]}]) of
+        {'EXIT', {badarg, _}} -> ok;
+        Other2 -> ct:fail({noerror, Other2})
+    end,
+
+    Fun = fun() -> f5_test6() end,
+    Pat = [{'_', [], [{message, {current_stacktrace}}]}],
+    P = spawn(?MODULE, fixed_runner, [self(), Fun]),
+    erlang:trace(P, true, [call]),
+    erlang:trace_pattern({?MODULE, f2_test6, 1}, Pat, [local]),
+    erlang:trace_pattern({?MODULE, f1_test6, 0}, Pat, [local]),
+    collect(P, [{trace, P, call, {?MODULE, f2_test6, [f1]},
+                   [
+                    {?MODULE, f3_test6, 0, [{file, "test6.erl"}, {line, 21}]},
+                    {?MODULE, f5_test6, 0, [{file, "test6.erl"}, {line, 14}]},
+                    {?MODULE, fixed_runner, 2, [{file, "test6.erl"}, {line, 7}]}
+                   ]},
+                {trace, P, call, {?MODULE, f1_test6, []},
+                   [
+                    {?MODULE, f2_test6, 1, [{file, "test6.erl"}, {line, 25}]},
+                    {?MODULE, f3_test6, 0, [{file, "test6.erl"}, {line, 21}]},
+                    {?MODULE, f5_test6, 0, [{file, "test6.erl"}, {line, 14}]},
+                    {?MODULE, fixed_runner, 2, [{file, "test6.erl"}, {line, 7}]}
+                   ]}
+               ]),
+
+    Pat2 = [{'_', [], [{message, {current_stacktrace, 3}}]}],
+    P2 = spawn(?MODULE, fixed_runner, [self(), Fun]),
+    erlang:trace(P2, true, [call]),
+    erlang:trace_pattern({?MODULE, f2_test6, 1}, Pat2, [local]),
+    erlang:trace_pattern({?MODULE, f1_test6, 0}, Pat2, [local]),
+    collect(P2, [{trace, P2, call, {?MODULE, f2_test6, [f1]},
+                   [
+                    {?MODULE, f3_test6, 0, [{file, "test6.erl"}, {line, 21}]},
+                    {?MODULE, f5_test6, 0, [{file, "test6.erl"}, {line, 14}]},
+                    {?MODULE, fixed_runner, 2, [{file, "test6.erl"}, {line, 7}]}
+                   ]},
+                {trace, P2, call, {?MODULE, f1_test6, []},
+                   [
+                    {?MODULE, f2_test6, 1, [{file, "test6.erl"}, {line, 25}]},
+                    {?MODULE, f3_test6, 0, [{file, "test6.erl"}, {line, 21}]},
+                    {?MODULE, f5_test6, 0, [{file, "test6.erl"}, {line, 14}]}
+                   ]}
+               ]),
+
+    %% Test when erts_backtrace_depth is less than depth
+    OldDepth = erlang:system_flag(backtrace_depth, 2),
+    try
+        P3 = spawn(?MODULE, fixed_runner, [self(), Fun]),
+        erlang:trace(P3, true, [call]),
+        erlang:trace_pattern({?MODULE, f2_test6, 1}, Pat2, [local]),
+        erlang:trace_pattern({?MODULE, f1_test6, 0}, Pat2, [local]),
+        collect(P3, [{trace, P3, call, {?MODULE, f2_test6, [f1]},
+                       [
+                        {?MODULE, f3_test6, 0, [{file, "test6.erl"}, {line, 21}]},
+                        {?MODULE, f5_test6, 0, [{file, "test6.erl"}, {line, 14}]}
+                       ]},
+                    {trace, P3, call, {?MODULE, f1_test6, []},
+                       [
+                        {?MODULE, f2_test6, 1, [{file, "test6.erl"}, {line, 25}]},
+                        {?MODULE, f3_test6, 0, [{file, "test6.erl"}, {line, 21}]}
+                       ]}
+                   ])
+    after
+        erlang:system_flag(backtrace_depth, OldDepth)
+    end,
+
+    ok.
+
 %% Test that caller and return to work as they should
 %% There was a bug where caller would be undefined when return_to was set
 %% for r the bif erlang:put().
@@ -1240,3 +1321,33 @@ f2_test5(X, _) ->
 
 f1_test5(X) ->
     {X}.
+
+-file("test6.erl", 1).
+fixed_runner(Collector, Fun) ->
+    receive
+        {go, Collector} ->
+            go
+    end,
+    Fun(), % Line 7 - This line number should remain stable
+    receive
+        {done, Collector} ->
+            Collector ! {gone, self()}
+    end.
+
+f5_test6() ->
+    f3_test6(), % Line 14 - This line number should remain stable
+    f4_test6().
+
+f4_test6() ->
+    f4.
+
+f3_test6() ->
+    f2_test6(f1), % Line 21 - This line number should remain stable
+    f3.
+
+f2_test6(X) ->
+    X = f1_test6(), % Line 25 - This line number should remain stable
+    f2.
+
+f1_test6() ->
+    f1.
-- 
2.35.3

openSUSE Build Service is sponsored by