Skip to content

Commit

Permalink
erts: Add BIFs processes_first/0 and processes_next/1
Browse files Browse the repository at this point in the history
This PR adds 2 BIFs to the `erlang` module.

`processes_first/0` returns a process iterator that can be used to
iterate through the process table.

`process_next/1` takes in a process iterator and returns a 2-tuple,
consisting of one process identifier and a new process iterator. If the
process iterator runs out of processes in the process table, `none`
will be returned.

By using these 2 BIFs instead of `processes/0`, one can avoid creating
a potentially huge list of the pids for all existing processes, at the
cost of less consistency guarantees. Process identifiers returned from
consecutive calls of `process_next/1` may not be a consistent snapshot
of all elements existing in the table during any of the calls.
  • Loading branch information
lucioleKi committed Dec 2, 2024
1 parent 641e374 commit 56cdff4
Show file tree
Hide file tree
Showing 12 changed files with 188 additions and 3 deletions.
18 changes: 18 additions & 0 deletions erts/emulator/beam/bif.c
Original file line number Diff line number Diff line change
Expand Up @@ -3825,6 +3825,24 @@ BIF_RETTYPE processes_0(BIF_ALIST_0)
return erts_ptab_list(BIF_P, &erts_proc);
}

/**********************************************************************/
/*
* The erts_internal:processes_next/1 BIF.
*/

BIF_RETTYPE erts_internal_processes_next_1(BIF_ALIST_1)
{
Eterm res;
if (is_not_small(BIF_ARG_1)) {
BIF_ERROR(BIF_P, BADARG);
}
res = erts_ptab_processes_next(BIF_P, &erts_proc, unsigned_val(BIF_ARG_1));
if (is_non_value(res)) {
BIF_ERROR(BIF_P, BADARG);
}
BIF_RET(res);
}

/**********************************************************************/
/*
* The erlang:ports/0 BIF.
Expand Down
1 change: 1 addition & 0 deletions erts/emulator/beam/bif.tab
Original file line number Diff line number Diff line change
Expand Up @@ -807,3 +807,4 @@ bif erts_trace_cleaner:send_trace_clean_signal/1
#
bif erts_internal:system_monitor/1
bif erts_internal:system_monitor/3
bif erts_internal:processes_next/1
55 changes: 55 additions & 0 deletions erts/emulator/beam/erl_ptab.c
Original file line number Diff line number Diff line change
Expand Up @@ -1465,6 +1465,61 @@ ptab_pix2el(ErtsPTab *ptab, int ix)
return ptab_el;
}

#define ERTS_PTAB_REDS_MULTIPLIER 25

Eterm
erts_ptab_processes_next(Process *c_p, ErtsPTab *ptab, Uint first)
{
Uint i;
int scanned;
Sint limit;
Uint need;
Eterm res;
Eterm* hp;
Eterm *hp_end;

int max_pids = MAX(ERTS_BIF_REDS_LEFT(c_p), 1);
int num_pids = 0;
int n = max_pids * ERTS_PTAB_REDS_MULTIPLIER;

need = n * 2;
hp = HAlloc(c_p, need); /* we need two heap words for each id */
hp_end = hp + need;
res = make_list(hp);

limit = MIN(ptab->r.o.max, first+n);
if (first == limit) {
return am_none;
} else if (first > limit) {
return THE_NON_VALUE;
}

for (i = first; i < limit && num_pids < max_pids; i++) {
ErtsPTabElementCommon *el = ptab_pix2el(ptab, i);
if (el) {
hp[0] = el->id;
hp[1] = make_list(hp+2);
hp += 2;
num_pids++;
}
}

if (num_pids == 0) {
res = NIL;
} else {
hp[-1] = NIL;
}

scanned = (i - first) / ERTS_PTAB_REDS_MULTIPLIER + 1;

res = TUPLE2(hp, make_small(i), res);
HRelease(c_p, hp_end, hp);

BUMP_REDS(c_p, scanned);

return res;
}

Eterm
erts_debug_ptab_list(Process *c_p, ErtsPTab *ptab)
{
Expand Down
3 changes: 3 additions & 0 deletions erts/emulator/beam/erl_ptab.h
Original file line number Diff line number Diff line change
Expand Up @@ -474,6 +474,9 @@ ERTS_GLB_INLINE int erts_lc_ptab_is_rwlocked(ErtsPTab *ptab)

BIF_RETTYPE erts_ptab_list(struct process *c_p, ErtsPTab *ptab);

BIF_RETTYPE erts_ptab_processes_next(struct process *c_p, ErtsPTab *ptab,
Uint first);

#endif

#if defined(ERTS_PTAB_WANT_DEBUG_FUNCS__) && !defined(ERTS_PTAB_DEBUG_FUNCS__)
Expand Down
4 changes: 4 additions & 0 deletions erts/emulator/test/exception_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1108,6 +1108,10 @@ error_info(_Config) ->
{process_display, [ExternalPid, whatever]},
{process_display, [DeadProcess, backtrace]},

{processes_next, [{a, []}]},
{processes_next, [{-1, []}]},
{processes_next, [a]},

{process_flag, [trap_exit, some_value]},
{process_flag, [bad_flag, some_value]},

Expand Down
40 changes: 37 additions & 3 deletions erts/emulator/test/process_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -103,7 +103,8 @@
demonitor_aliasmonitor/1,
down_aliasmonitor/1,
monitor_tag/1,
no_pid_wrap/1]).
no_pid_wrap/1,
processes_iter/1]).

-export([prio_server/2, prio_client/2, init/1, handle_event/2]).

Expand Down Expand Up @@ -163,7 +164,8 @@ groups() ->
processes_small_tab, processes_this_tab,
processes_last_call_trap, processes_apply_trap,
processes_gc_trap, processes_term_proc_list,
processes_send_infant]},
processes_send_infant,
processes_iter]},
{process_info_bif, [],
[t_process_info, process_info_messages,
process_info_other, process_info_other_msg,
Expand Down Expand Up @@ -2513,7 +2515,14 @@ processes_bif_test() ->
processes()
end,

IterProcesses =
fun () ->
erts_debug:set_internal_state(reds_left, WantReds),
iter_all_processes()
end,

ok = do_processes_bif_test(WantReds, WillTrap, Processes),
ok = do_processes_bif_test(WantReds, false, IterProcesses()),

case WillTrap of
false ->
Expand Down Expand Up @@ -2550,7 +2559,19 @@ processes_bif_test() ->
undefined -> ok;
Comment -> {comment, Comment}
end.


iter_all_processes() ->
Iter = erlang:processes_first(),
iter_all_processes(Iter).

iter_all_processes(Iter0) ->
case erlang:processes_next(Iter0) of
{Pid, Iter} ->
[Pid|iter_all_processes(Iter)];
none ->
none
end.

do_processes_bif_test(WantReds, DieTest, Processes) ->
Tester = self(),
SpawnProcesses = fun (Prio) ->
Expand Down Expand Up @@ -4199,6 +4220,19 @@ processes_term_proc_list(Config) when is_list(Config) ->

ok.

processes_iter(Config) when is_list(Config) ->
ProcessLimit = erlang:system_info(process_limit),
{'EXIT',{badarg,_}} = catch erts_internal:processes_next(ProcessLimit + 1),
{'EXIT',{badarg,_}} = catch erts_internal:processes_next(-1),
{'EXIT',{badarg,_}} = catch erts_internal:processes_next(1 bsl 32),
{'EXIT',{badarg,_}} = catch erts_internal:processes_next(1 bsl 64),
{'EXIT',{badarg,_}} = catch erts_internal:processes_next(abc),

none = erts_internal:processes_next(ProcessLimit),

ok.


%% OTP-18322: Send msg to spawning process pid returned from processes/0
processes_send_infant(_Config) ->
case erlang:system_info(schedulers_online) of
Expand Down
Binary file modified erts/preloaded/ebin/erlang.beam
Binary file not shown.
Binary file modified erts/preloaded/ebin/erts_internal.beam
Binary file not shown.
60 changes: 60 additions & 0 deletions erts/preloaded/src/erlang.erl
Original file line number Diff line number Diff line change
Expand Up @@ -265,6 +265,7 @@ A timeout value that can be passed to a
-export_type([message_queue_data/0]).
-export_type([monitor_option/0]).
-export_type([stacktrace/0]).
-export_type([processes_iter_ref/0]).

-type stacktrace_extrainfo() ::
{line, pos_integer()} |
Expand Down Expand Up @@ -465,6 +466,7 @@ A list of binaries. This datatype is useful to use together with
-export([time_offset/0, time_offset/1, timestamp/0]).
-export([process_display/2]).
-export([process_flag/3, process_info/1, processes/0, purge_module/1]).
-export([processes_first/0, processes_next/1]).
-export([put/2, raise/3, read_timer/1, read_timer/2, ref_to_list/1, register/2]).
-export([send_after/3, send_after/4, start_timer/3, start_timer/4]).
-export([registered/0, resume_process/1, round/1, self/0]).
Expand Down Expand Up @@ -5219,6 +5221,64 @@ Example:
processes() ->
erlang:nif_error(undefined).

%% The process iterator is a 2-tuple, consisting of an index to the process
%% table and a list of process identifiers that existed when the last scan of
%% the process table took place. The index is the starting place for the next
%% scan of the process table.
-opaque processes_iter_ref() :: {integer(), [pid()]}.

%% processes_first/0
-doc """
Returns a processes iterator that can be used in
[`processes_next/1`](`processes_next/1`).
""".
-doc #{ group => processes }.
-spec processes_first() -> processes_iter_ref().
processes_first() ->
{0, []}.

%% processes_next/1
-doc """
Returns a 2-tuple, consisting of one process identifier and a new processes
iterator. If the process iterator has run out of processes in the process table,
`none` will be returned.
Example:
```erlang
> I0 = erlang:processes_first(), ok.
ok
> {Pid1, I1} = erlang:processes_next(I0), Pid1.
<0.0.0>,
> {Pid2, I2} = erlang:processes_next(I1), Pid2.
<0.1.0>
```
> #### Note {: .info }
>
> This BIF has less consistency guarantee than [`processes/0`](`processes/0`).
> Process identifiers returned from consecutive calls of this BIF may not be a
> consistent snapshot of all elements existing in the table during any of the
> calls.
""".
-doc #{ group => processes }.
-spec processes_next(Iter) -> {Pid, NewIter} | 'none' when
Iter :: processes_iter_ref(),
NewIter :: processes_iter_ref(),
Pid :: pid().
processes_next({IterRef, [Pid|Pids]}) ->
{Pid, {IterRef, Pids}};
processes_next({IterRef0, []}=Arg) ->
try erts_internal:processes_next(IterRef0) of
none -> none;
{IterRef, [Pid|Pids]} -> {Pid, {IterRef, Pids}};
{IterRef, []} -> processes_next({IterRef, []})
catch error:badarg ->
badarg_with_info([Arg])
end;
processes_next(Arg) ->
badarg_with_info([Arg]).

%% purge_module/1
-doc """
Removes old code for `Module`. Before this BIF is used, `check_process_code/2`
Expand Down
6 changes: 6 additions & 0 deletions erts/preloaded/src/erts_internal.erl
Original file line number Diff line number Diff line change
Expand Up @@ -129,6 +129,8 @@

-export([system_monitor/1, system_monitor/3]).

-export([processes_next/1]).

%%
%% Await result of send to port
%%
Expand Down Expand Up @@ -1166,3 +1168,7 @@ system_monitor(_Session) ->
Return :: undefined | ok | {pid(), Options}.
system_monitor(_Session, _MonitorPid, _Options) ->
erlang:nif_error(undefined).

-spec processes_next(integer()) -> {integer(), [pid()]} | 'none'.
processes_next(_IterRef) ->
erlang:nif_error(undefined).
2 changes: 2 additions & 0 deletions lib/kernel/src/erl_erts_errors.erl
Original file line number Diff line number Diff line change
Expand Up @@ -733,6 +733,8 @@ format_erlang_error(process_display, [Pid,_], Cause) ->
_ ->
[must_be_local_pid(Pid, dead_process)]
end;
format_erlang_error(processes_next, [_], _Cause) ->
[~"invalid processes iterator"];
format_erlang_error(process_flag, [_,_], Cause) ->
case Cause of
badopt ->
Expand Down
2 changes: 2 additions & 0 deletions lib/tools/emacs/erlang.el
Original file line number Diff line number Diff line change
Expand Up @@ -993,6 +993,8 @@ resulting regexp is surrounded by \\_< and \\_>."
"posixtime_to_universaltime"
"prepare_loading"
"process_display"
"processes_first"
"processes_next"
"raise"
"read_timer"
"resume_process"
Expand Down

0 comments on commit 56cdff4

Please sign in to comment.