Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
* maint:
  Add `process_info(Pid, label)` for retrieving the process label
  • Loading branch information
bjorng committed Nov 26, 2024
2 parents a83f774 + 9650953 commit c59539f
Show file tree
Hide file tree
Showing 5 changed files with 51 additions and 1 deletion.
2 changes: 2 additions & 0 deletions erts/emulator/beam/atom.names
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
20 changes: 20 additions & 0 deletions erts/emulator/beam/erl_bif_info.c
Original file line number Diff line number Diff line change
Expand Up @@ -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_UNRESERVE(RS, SZ) \
(ASSERT((RS) >= (SZ)), (RS) -= (SZ))
Expand Down Expand Up @@ -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])))
Expand Down Expand Up @@ -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);
Expand Down Expand Up @@ -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 */

Expand Down
23 changes: 22 additions & 1 deletion erts/emulator/test/process_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down Expand Up @@ -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]},
Expand Down Expand Up @@ -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},
Expand Down
Binary file modified erts/preloaded/ebin/erlang.beam
Binary file not shown.
7 changes: 7 additions & 0 deletions erts/preloaded/src/erlang.erl
Original file line number Diff line number Diff line change
Expand Up @@ -7663,6 +7663,7 @@ process_flag(_Flag, _Value) ->
heap_size |
initial_call |
links |
label |
last_calls |
memory |
message_queue_len |
Expand Down Expand Up @@ -7707,6 +7708,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()} |
Expand Down Expand Up @@ -7842,6 +7844,11 @@ Valid `InfoTuple`s with corresponding `Item`s:
- **`{links, PidsAndPorts}`** - `PidsAndPorts` is a list of process identifiers
and port identifiers, with processes or ports to which the process has a link.
- **`{label, Label}`** -
`Label` is the label for the process. See `proc_lib:get_label/1`.
Since: OTP 27.2
- **`{last_calls, false|Calls}`** - The value is `false` if call saving is not
active for the process (see `process_flag/3`). If call saving is active, a
list is returned, in which the last element is the most recent called.
Expand Down

0 comments on commit c59539f

Please sign in to comment.