Skip to content

Commit

Permalink
Fix processes iterator use in literal area collector
Browse files Browse the repository at this point in the history
  • Loading branch information
rickard-green committed Dec 13, 2024
1 parent 7b0c625 commit de3f1c9
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 13 deletions.
Binary file modified erts/preloaded/ebin/erts_literal_area_collector.beam
Binary file not shown.
31 changes: 18 additions & 13 deletions erts/preloaded/src/erts_literal_area_collector.erl
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@
%%
start() ->
process_flag(trap_exit, true),
msg_loop(undefined, {0, []}, 0, []).
msg_loop(undefined, {0, none}, 0, []).

%%
%% The VM will send us a 'copy_literals' message
Expand All @@ -63,16 +63,17 @@ msg_loop(Area, {Ongoing, NeedIReq} = OReqInfo, GcOutstnd, NeedGC) ->
switch_area();

%% Process (_Pid) has completed the request...
{copy_literals, {Area, _ReqType, _Pid}, ok} when Ongoing == 1,
NeedIReq == [] ->
switch_area(); %% Last process completed...
{copy_literals, {Area, init, _Pid}, ok} ->
msg_loop(Area, check_send_copy_req(Area, Ongoing-1, NeedIReq),
GcOutstnd, NeedGC);
case check_send_copy_req(Area, Ongoing-1, NeedIReq) of
{0, none} -> switch_area(); %% Last process completed...
NewOReqInfo -> msg_loop(Area, NewOReqInfo, GcOutstnd, NeedGC)
end;
{copy_literals, {Area, ReqType, _Pid}, ok} when NeedGC == [],
ReqType /= init ->
msg_loop(Area, check_send_copy_req(Area, Ongoing-1, NeedIReq),
GcOutstnd-1, []);
case check_send_copy_req(Area, Ongoing-1, NeedIReq) of
{0, none} -> switch_area(); %% Last process completed...
NewOReqInfo -> msg_loop(Area, NewOReqInfo, GcOutstnd-1, [])
end;
{copy_literals, {Area, ReqType, _Pid}, ok} when ReqType /= init ->
[{GCPid,GCWork} | NewNeedGC] = NeedGC,
send_copy_req(GCPid, Area, GCWork),
Expand Down Expand Up @@ -117,7 +118,7 @@ switch_area() ->
case Res of
false ->
%% No more areas to handle...
msg_loop(undefined, {0, []}, 0, []);
msg_loop(undefined, {0, none}, 0, []);
true ->
%% Send requests to OReqLim processes to copy
%% all live data they have referring to the
Expand All @@ -131,11 +132,12 @@ switch_area() ->
msg_loop(Area, send_copy_reqs(Iter, Area, OReqLim), 0, [])
end.

check_send_copy_req(_Area, Ongoing, []) ->
{Ongoing, []};
check_send_copy_req(_Area, Ongoing, none) ->
{Ongoing, none};
check_send_copy_req(Area, Ongoing, Iter0) ->
case erlang:processes_next(Iter0) of
none -> {Ongoing, []};
none ->
{Ongoing, none};
{Pid, Iter1} ->
send_copy_req(Pid, Area, init),
{Ongoing+1, Iter1}
Expand All @@ -144,11 +146,14 @@ check_send_copy_req(Area, Ongoing, Iter0) ->
send_copy_reqs(Iter, Area, OReqLim) ->
send_copy_reqs(Iter, Area, OReqLim, 0).

send_copy_reqs(none, _Area, _OReqLim, N) ->
{N, none};
send_copy_reqs(Iter, _Area, OReqLim, N) when N >= OReqLim ->
{N, Iter};
send_copy_reqs(Iter0, Area, OReqLim, N) ->
case erlang:processes_next(Iter0) of
none -> {N, []};
none ->
{N, none};
{Pid, Iter1} ->
send_copy_req(Pid, Area, init),
send_copy_reqs(Iter1, Area, OReqLim, N+1)
Expand Down

0 comments on commit de3f1c9

Please sign in to comment.