File 3761-Add-process_info-Pid-label-for-retrieving-the-proces.patch of Package erlang

From 2a8c77b210307db2110c4f3c3cdc59ddaed6bd2d Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 25 Nov 2024 12:43:30 +0100
Subject: [PATCH] Add `process_info(Pid, label)` for retrieving the process
 label

The only documented way to retrieve the label for a process was
by calling `proc_lib:get_label/1`.

This commit teaches `process_info/2` the option `label` for retrieving
the process label. This is especially useful when one needs to
retrieve other process info items at the same time. For example:

    process_info(Pid, [label,registered_name])
---
 erts/emulator/beam/atom.names        |   2 ++
 erts/emulator/beam/erl_bif_info.c    |  20 ++++++++++++++++++++
 erts/emulator/test/process_SUITE.erl |  23 ++++++++++++++++++++++-
 erts/preloaded/ebin/erlang.beam      | Bin 39168 -> 39168 bytes
 erts/preloaded/src/erlang.erl        |   7 +++++++
 5 files changed, 51 insertions(+), 1 deletion(-)

diff --git a/erts/emulator/beam/atom.names b/erts/emulator/beam/atom.names
index 758c84d1c1..0b328a6d9a 100644
--- a/erts/emulator/beam/atom.names
+++ b/erts/emulator/beam/atom.names
@@ -578,6 +578,8 @@ atom processes
 atom processes_used
 atom process_count
 atom process_display
+atom DollarProcessLabel='$process_label'
+atom process_limit
 atom process_limit
 atom process_dump
 atom procs
diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c
index c2bd395ad3..b421071579 100644
--- a/erts/emulator/beam/erl_bif_info.c
+++ b/erts/emulator/beam/erl_bif_info.c
@@ -782,6 +782,7 @@ collect_one_suspend_monitor(ErtsMonitor *mon, void *vsmicp, Sint reds)
 #define ERTS_PI_IX_PARENT                               36
 #define ERTS_PI_IX_ASYNC_DIST                           37
 #define ERTS_PI_IX_DICTIONARY_LOOKUP                    38
+#define ERTS_PI_IX_LABEL                                39
 
 #define ERTS_PI_FLAG_SINGELTON                          (1 << 0)
 #define ERTS_PI_FLAG_ALWAYS_WRAP                        (1 << 1)
@@ -834,6 +835,7 @@ static ErtsProcessInfoArgs pi_args[] = {
     {am_parent, 0, 0, ERTS_PROC_LOCK_MAIN},
     {am_async_dist, 0, 0, ERTS_PROC_LOCK_MAIN},
     {am_dictionary, 3, ERTS_PI_FLAG_FORCE_SIG_SEND|ERTS_PI_FLAG_KEY_TUPLE2, ERTS_PROC_LOCK_MAIN},
+    {am_label, 0, ERTS_PI_FLAG_FORCE_SIG_SEND, ERTS_PROC_LOCK_MAIN},
 };
 
 #define ERTS_PI_ARGS ((int) (sizeof(pi_args)/sizeof(pi_args[0])))
@@ -966,6 +968,8 @@ pi_arg2ix(Eterm arg, Eterm *extrap)
         return ERTS_PI_IX_PARENT;
     case am_async_dist:
         return ERTS_PI_IX_ASYNC_DIST;
+    case am_label:
+        return ERTS_PI_IX_LABEL;
     default:
         if (is_tuple_arity(arg, 2)) {
             Eterm *tpl = tuple_val(arg);
@@ -2279,6 +2283,22 @@ process_info_aux(Process *c_p,
         break;
     }
 
+    case ERTS_PI_IX_LABEL: {
+        Uint sz;
+
+        res = erts_pd_hash_get(rp, am_DollarProcessLabel);
+        sz = (!(flags & ERTS_PI_FLAG_REQUEST_FOR_OTHER) || is_immed(res)
+              ? 0
+              : size_object(res));
+
+        hp = erts_produce_heap(hfact, sz, reserve_size);
+
+        if (sz)
+            res = copy_struct(res, sz, &hp, hfact->off_heap);
+
+        break;
+    }
+
     default:
 	return THE_NON_VALUE; /* will produce badarg */
 
diff --git a/erts/emulator/test/process_SUITE.erl b/erts/emulator/test/process_SUITE.erl
index c8b86e4e74..9680eb5836 100644
--- a/erts/emulator/test/process_SUITE.erl
+++ b/erts/emulator/test/process_SUITE.erl
@@ -55,6 +55,7 @@
          process_info_self_msgq_len_more/1,
          process_info_msgq_len_no_very_long_delay/1,
          process_info_dict_lookup/1,
+         process_info_label/1,
 	 bump_reductions/1, low_prio/1, binary_owner/1, yield/1, yield2/1,
 	 otp_4725/1, dist_unlink_ack_exit_leak/1, bad_register/1,
          garbage_collect/1, otp_6237/1,
@@ -182,7 +183,8 @@ groups() ->
        process_info_self_msgq_len_messages,
        process_info_self_msgq_len_more,
        process_info_msgq_len_no_very_long_delay,
-       process_info_dict_lookup]},
+       process_info_dict_lookup,
+       process_info_label]},
      {otp_7738, [],
       [otp_7738_waiting, otp_7738_suspended,
        otp_7738_resume]},
@@ -1728,6 +1730,25 @@ process_info_dict_lookup(Config) when is_list(Config) ->
     false = is_process_alive(Pid),
     ok.
 
+process_info_label(Config) when is_list(Config) ->
+    Pid = spawn_link(fun proc_dict_helper/0),
+    LabelKey = '$process_label',
+    Ref = make_ref(),
+    Tuple = {make_ref(), erlang:monotonic_time()},
+
+    undefined = pdh(Pid, put, [LabelKey, Tuple]),
+    erlang:garbage_collect(Pid),
+
+    {label,Tuple} = process_info(Pid, label),
+    Self = self(),
+    [{label,Tuple},{registered_name,[]},{links,[Self]}] =
+        process_info(Pid, [label,registered_name,links]),
+
+    put(LabelKey, Ref),
+    {label,Ref} = process_info(self(), label),
+
+    ok.
+
 pdh(Pid, AsyncOp, Args) when AsyncOp == put_async;
                              AsyncOp == erase_async ->
     Pid ! {AsyncOp, Args},
diff --git a/erts/preloaded/src/erlang.erl b/erts/preloaded/src/erlang.erl
index 061f55cd43..df90b942ea 100644
--- a/erts/preloaded/src/erlang.erl
+++ b/erts/preloaded/src/erlang.erl
@@ -7724,6 +7724,7 @@ process_flag(_Flag, _Value) ->
       heap_size |
       initial_call |
       links |
+      label |
       last_calls |
       memory |
       message_queue_len |
@@ -7768,6 +7769,7 @@ process_flag(_Flag, _Value) ->
       {heap_size, Size :: non_neg_integer()} |
       {initial_call, mfa()} |
       {links, PidsAndPorts :: [pid() | port()]} |
+      {label, term()} |
       {last_calls, false | (Calls :: [mfa()])} |
       {memory, Size :: non_neg_integer()} |
       {message_queue_len, MessageQueueLen :: non_neg_integer()} |
diff --git a/erts/doc/src/erlang.xml b/erts/doc/src/erlang.xml
index 061f55cd43..df90b942ea 100644
--- a/erts/doc/src/erlang.xml
+++ b/erts/doc/src/erlang.xml
@@ -7005,6 +7005,11 @@ receive_replies(ReqId, N, Acc) ->
               and port identifiers, with processes or ports to which the process
               has a link.</p>
           </item>
+          <tag><c>{label, Label}</c></tag>
+          <item>
+            <p>Label is the label for the process. See
+              <seemfa marker="stdlib:proc_lib#get_label/1">proc_lib:get_label/1</seemfa>.</p>
+          </item>
           <tag><c>{last_calls, false|Calls}</c></tag>
           <item>
             <p>The value is <c>false</c> if call saving is not active
-- 
2.43.0

openSUSE Build Service is sponsored by