Skip to content

Commit 69f7884

Browse files
committed
erts: Add BIFs processes_iterator/0 and processes_next/1
This PR adds 2 BIFs to the `erlang` module. `processes_iterator/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. The process identifier of a process that is alive before `processes_iterator/0` is called and continues to be alive until `processes_next/1` returns `none` is guaranteed to be part of the result returned from one of the calls to `processes_next/1`.
1 parent 6c20557 commit 69f7884

File tree

12 files changed

+207
-3
lines changed

12 files changed

+207
-3
lines changed

erts/emulator/beam/bif.c

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3825,6 +3825,24 @@ BIF_RETTYPE processes_0(BIF_ALIST_0)
38253825
return erts_ptab_list(BIF_P, &erts_proc);
38263826
}
38273827

3828+
/**********************************************************************/
3829+
/*
3830+
* The erts_internal:processes_next/1 BIF.
3831+
*/
3832+
3833+
BIF_RETTYPE erts_internal_processes_next_1(BIF_ALIST_1)
3834+
{
3835+
Eterm res;
3836+
if (is_not_small(BIF_ARG_1)) {
3837+
BIF_ERROR(BIF_P, BADARG);
3838+
}
3839+
res = erts_ptab_processes_next(BIF_P, &erts_proc, unsigned_val(BIF_ARG_1));
3840+
if (is_non_value(res)) {
3841+
BIF_ERROR(BIF_P, BADARG);
3842+
}
3843+
BIF_RET(res);
3844+
}
3845+
38283846
/**********************************************************************/
38293847
/*
38303848
* The erlang:ports/0 BIF.

erts/emulator/beam/bif.tab

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -807,3 +807,4 @@ bif erts_trace_cleaner:send_trace_clean_signal/1
807807
#
808808
bif erts_internal:system_monitor/1
809809
bif erts_internal:system_monitor/3
810+
bif erts_internal:processes_next/1

erts/emulator/beam/erl_ptab.c

Lines changed: 66 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1465,6 +1465,72 @@ ptab_pix2el(ErtsPTab *ptab, int ix)
14651465
return ptab_el;
14661466
}
14671467

1468+
#define ERTS_PTAB_REDS_MULTIPLIER 25
1469+
1470+
Eterm
1471+
erts_ptab_processes_next(Process *c_p, ErtsPTab *ptab, Uint first)
1472+
{
1473+
Uint i;
1474+
int scanned;
1475+
Sint limit;
1476+
Uint need;
1477+
Eterm res;
1478+
Eterm* hp;
1479+
Eterm *hp_end;
1480+
1481+
int max_pids = MAX(ERTS_BIF_REDS_LEFT(c_p), 1);
1482+
int num_pids = 0;
1483+
int n = max_pids * ERTS_PTAB_REDS_MULTIPLIER;
1484+
limit = MIN(ptab->r.o.max, first+n);
1485+
1486+
if (first == 0) {
1487+
/*
1488+
* Ensure no reorder of memory operations made before the first read in
1489+
* the table with reads in the table.
1490+
*/
1491+
ETHR_MEMBAR(ETHR_LoadLoad|ETHR_StoreLoad);
1492+
} else if (first == limit) {
1493+
/*
1494+
* Ensure no reorder of memory operations made after the last read in
1495+
* the table with reads in the table.
1496+
*/
1497+
ETHR_MEMBAR(ETHR_LoadLoad|ETHR_LoadStore);
1498+
return am_none;
1499+
} else if (first > limit) {
1500+
return THE_NON_VALUE;
1501+
}
1502+
1503+
need = n * 2;
1504+
hp = HAlloc(c_p, need); /* we need two heap words for each id */
1505+
hp_end = hp + need;
1506+
res = make_list(hp);
1507+
1508+
for (i = first; i < limit && num_pids < max_pids; i++) {
1509+
ErtsPTabElementCommon *el = ptab_pix2el(ptab, i);
1510+
if (el) {
1511+
hp[0] = el->id;
1512+
hp[1] = make_list(hp+2);
1513+
hp += 2;
1514+
num_pids++;
1515+
}
1516+
}
1517+
1518+
if (num_pids == 0) {
1519+
res = NIL;
1520+
} else {
1521+
hp[-1] = NIL;
1522+
}
1523+
1524+
scanned = (i - first) / ERTS_PTAB_REDS_MULTIPLIER + 1;
1525+
1526+
res = TUPLE2(hp, make_small(i), res);
1527+
HRelease(c_p, hp_end, hp);
1528+
1529+
BUMP_REDS(c_p, scanned);
1530+
1531+
return res;
1532+
}
1533+
14681534
Eterm
14691535
erts_debug_ptab_list(Process *c_p, ErtsPTab *ptab)
14701536
{

erts/emulator/beam/erl_ptab.h

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -474,6 +474,9 @@ ERTS_GLB_INLINE int erts_lc_ptab_is_rwlocked(ErtsPTab *ptab)
474474

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

477+
BIF_RETTYPE erts_ptab_processes_next(struct process *c_p, ErtsPTab *ptab,
478+
Uint first);
479+
477480
#endif
478481

479482
#if defined(ERTS_PTAB_WANT_DEBUG_FUNCS__) && !defined(ERTS_PTAB_DEBUG_FUNCS__)

erts/emulator/test/exception_SUITE.erl

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1108,6 +1108,10 @@ error_info(_Config) ->
11081108
{process_display, [ExternalPid, whatever]},
11091109
{process_display, [DeadProcess, backtrace]},
11101110

1111+
{processes_next, [{a, []}]},
1112+
{processes_next, [{-1, []}]},
1113+
{processes_next, [a]},
1114+
11111115
{process_flag, [trap_exit, some_value]},
11121116
{process_flag, [bad_flag, some_value]},
11131117

erts/emulator/test/process_SUITE.erl

Lines changed: 37 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -103,7 +103,8 @@
103103
demonitor_aliasmonitor/1,
104104
down_aliasmonitor/1,
105105
monitor_tag/1,
106-
no_pid_wrap/1]).
106+
no_pid_wrap/1,
107+
processes_iter/1]).
107108

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

@@ -163,7 +164,8 @@ groups() ->
163164
processes_small_tab, processes_this_tab,
164165
processes_last_call_trap, processes_apply_trap,
165166
processes_gc_trap, processes_term_proc_list,
166-
processes_send_infant]},
167+
processes_send_infant,
168+
processes_iter]},
167169
{process_info_bif, [],
168170
[t_process_info, process_info_messages,
169171
process_info_other, process_info_other_msg,
@@ -2513,7 +2515,14 @@ processes_bif_test() ->
25132515
processes()
25142516
end,
25152517

2518+
IterProcesses =
2519+
fun () ->
2520+
erts_debug:set_internal_state(reds_left, WantReds),
2521+
iter_all_processes()
2522+
end,
2523+
25162524
ok = do_processes_bif_test(WantReds, WillTrap, Processes),
2525+
ok = do_processes_bif_test(WantReds, false, IterProcesses()),
25172526

25182527
case WillTrap of
25192528
false ->
@@ -2550,7 +2559,19 @@ processes_bif_test() ->
25502559
undefined -> ok;
25512560
Comment -> {comment, Comment}
25522561
end.
2553-
2562+
2563+
iter_all_processes() ->
2564+
Iter = erlang:processes_iterator(),
2565+
iter_all_processes(Iter).
2566+
2567+
iter_all_processes(Iter0) ->
2568+
case erlang:processes_next(Iter0) of
2569+
{Pid, Iter} ->
2570+
[Pid|iter_all_processes(Iter)];
2571+
none ->
2572+
none
2573+
end.
2574+
25542575
do_processes_bif_test(WantReds, DieTest, Processes) ->
25552576
Tester = self(),
25562577
SpawnProcesses = fun (Prio) ->
@@ -4199,6 +4220,19 @@ processes_term_proc_list(Config) when is_list(Config) ->
41994220

42004221
ok.
42014222

4223+
processes_iter(Config) when is_list(Config) ->
4224+
ProcessLimit = erlang:system_info(process_limit),
4225+
{'EXIT',{badarg,_}} = catch erts_internal:processes_next(ProcessLimit + 1),
4226+
{'EXIT',{badarg,_}} = catch erts_internal:processes_next(-1),
4227+
{'EXIT',{badarg,_}} = catch erts_internal:processes_next(1 bsl 32),
4228+
{'EXIT',{badarg,_}} = catch erts_internal:processes_next(1 bsl 64),
4229+
{'EXIT',{badarg,_}} = catch erts_internal:processes_next(abc),
4230+
4231+
none = erts_internal:processes_next(ProcessLimit),
4232+
4233+
ok.
4234+
4235+
42024236
%% OTP-18322: Send msg to spawning process pid returned from processes/0
42034237
processes_send_infant(_Config) ->
42044238
case erlang:system_info(schedulers_online) of

erts/preloaded/ebin/erlang.beam

348 Bytes
Binary file not shown.
52 Bytes
Binary file not shown.

erts/preloaded/src/erlang.erl

Lines changed: 68 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -265,6 +265,7 @@ A timeout value that can be passed to a
265265
-export_type([message_queue_data/0]).
266266
-export_type([monitor_option/0]).
267267
-export_type([stacktrace/0]).
268+
-export_type([processes_iter_ref/0]).
268269

269270
-type stacktrace_extrainfo() ::
270271
{line, pos_integer()} |
@@ -465,6 +466,7 @@ A list of binaries. This datatype is useful to use together with
465466
-export([time_offset/0, time_offset/1, timestamp/0]).
466467
-export([process_display/2]).
467468
-export([process_flag/3, process_info/1, processes/0, purge_module/1]).
469+
-export([processes_iterator/0, processes_next/1]).
468470
-export([put/2, raise/3, read_timer/1, read_timer/2, ref_to_list/1, register/2]).
469471
-export([send_after/3, send_after/4, start_timer/3, start_timer/4]).
470472
-export([registered/0, resume_process/1, round/1, self/0]).
@@ -5219,6 +5221,72 @@ Example:
52195221
processes() ->
52205222
erlang:nif_error(undefined).
52215223

5224+
%% The process iterator is a 2-tuple, consisting of an index to the process
5225+
%% table and a list of process identifiers that existed when the last scan of
5226+
%% the process table took place. The index is the starting place for the next
5227+
%% scan of the process table.
5228+
-opaque processes_iter_ref() :: {integer(), [pid()]}.
5229+
5230+
%% processes_iterator/0
5231+
-doc """
5232+
Returns a processes iterator that can be used in
5233+
[`processes_next/1`](`processes_next/1`).
5234+
""".
5235+
-doc #{ group => processes, since => <<"OTP @OTP-19369@">> }.
5236+
-spec processes_iterator() -> processes_iter_ref().
5237+
processes_iterator() ->
5238+
{0, []}.
5239+
5240+
%% processes_next/1
5241+
-doc """
5242+
Returns a 2-tuple, consisting of one process identifier and a new processes
5243+
iterator. If the process iterator has run out of processes in the process table,
5244+
`none` will be returned.
5245+
5246+
The two major benefits of using the `processes_iterator/0`/`processes_next/1`
5247+
BIFs instead of using the `processes/0` BIF are that they scale better since
5248+
no locking is needed, and you do not risk getting a huge list allocated on the
5249+
heap if there are a huge amount of processes alive in the system.
5250+
5251+
Example:
5252+
5253+
```erlang
5254+
> I0 = erlang:processes_iterator(), ok.
5255+
ok
5256+
> {Pid1, I1} = erlang:processes_next(I0), Pid1.
5257+
<0.0.0>,
5258+
> {Pid2, I2} = erlang:processes_next(I1), Pid2.
5259+
<0.1.0>
5260+
```
5261+
5262+
> #### Note {: .info }
5263+
>
5264+
> This BIF has less consistency guarantee than [`processes/0`](`processes/0`).
5265+
> Process identifiers returned from consecutive calls of this BIF may not be a
5266+
> consistent snapshot of all elements existing in the table during any of the
5267+
> calls. The process identifier of a process that is alive before
5268+
> `processes_iterator/0` is called and continues to be alive until
5269+
> `processes_next/1` returns `none` is guaranteed to be part of the result
5270+
> returned from one of the calls to `processes_next/1`.
5271+
""".
5272+
-doc #{ group => processes, since => <<"OTP @OTP-19369@">> }.
5273+
-spec processes_next(Iter) -> {Pid, NewIter} | 'none' when
5274+
Iter :: processes_iter_ref(),
5275+
NewIter :: processes_iter_ref(),
5276+
Pid :: pid().
5277+
processes_next({IterRef, [Pid|Pids]}) ->
5278+
{Pid, {IterRef, Pids}};
5279+
processes_next({IterRef0, []}=Arg) ->
5280+
try erts_internal:processes_next(IterRef0) of
5281+
none -> none;
5282+
{IterRef, [Pid|Pids]} -> {Pid, {IterRef, Pids}};
5283+
{IterRef, []} -> processes_next({IterRef, []})
5284+
catch error:badarg ->
5285+
badarg_with_info([Arg])
5286+
end;
5287+
processes_next(Arg) ->
5288+
badarg_with_info([Arg]).
5289+
52225290
%% purge_module/1
52235291
-doc """
52245292
Removes old code for `Module`. Before this BIF is used, `check_process_code/2`

erts/preloaded/src/erts_internal.erl

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -129,6 +129,8 @@
129129

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

132+
-export([processes_next/1]).
133+
132134
%%
133135
%% Await result of send to port
134136
%%
@@ -1166,3 +1168,7 @@ system_monitor(_Session) ->
11661168
Return :: undefined | ok | {pid(), Options}.
11671169
system_monitor(_Session, _MonitorPid, _Options) ->
11681170
erlang:nif_error(undefined).
1171+
1172+
-spec processes_next(integer()) -> {integer(), [pid()]} | 'none'.
1173+
processes_next(_IterRef) ->
1174+
erlang:nif_error(undefined).

0 commit comments

Comments
 (0)