Skip to content

Commit

Permalink
Speed up init:stop
Browse files Browse the repository at this point in the history
This speeds up the VM shutdown procedure by avoiding to unload code for `init:stop/1`, which is already done for `init:stop/0` - both calls are equivalent and only differ in the final result code returned by VM.
Additionally, this amends some smaller points when unloading code - using `--` instead of custom list difference implementation (which should be much faster since `--` was optimised couple releases ago), and avoiding unloading the logger module as well when shutting down.
  • Loading branch information
michalmuskala authored Jan 15, 2024
1 parent 8749ab2 commit 9165872
Showing 1 changed file with 9 additions and 12 deletions.
21 changes: 9 additions & 12 deletions erts/preloaded/src/init.erl
Original file line number Diff line number Diff line change
Expand Up @@ -591,10 +591,14 @@ stop(Reason,State) ->
BootPid = State#state.bootpid,
{_,Progress} = State#state.status,
State1 = State#state{status = {stopping, Progress}},
%% There is no need to unload code if the system is shutting down
clear_system(Reason=/=stop,BootPid,State1),
clear_system(should_unload(Reason),BootPid,State1),
do_stop(Reason,State1).

%% There is no need to unload code if the system is shutting down
should_unload(stop) -> false;
should_unload({stop, _}) -> false;
should_unload(_) -> true.

do_stop({restart,Mode},#state{start=Start, flags=Flags0, args=Args}) ->
Flags = update_flag(mode, Flags0, atom_to_binary(Mode)),
do_restart(Start,Flags,Args);
Expand All @@ -620,7 +624,7 @@ clear_system(Unload,BootPid,State) ->
shutdown_pids(Heart,Logger,BootPid,State),
Unload andalso unload(Heart),
kill_em([Logger]),
do_unload([logger_server]).
Unload andalso do_unload([logger_server]).

flush() ->
receive
Expand Down Expand Up @@ -779,9 +783,9 @@ kill_all_ports(_,_) ->
ok.

unload(false) ->
do_unload(sub([logger_server|erlang:pre_loaded()],erlang:loaded()));
do_unload(erlang:loaded() -- [logger_server|erlang:pre_loaded()]);
unload(_) ->
do_unload(sub([heart,logger_server|erlang:pre_loaded()],erlang:loaded())).
do_unload(erlang:loaded() -- [heart,logger_server|erlang:pre_loaded()]).

do_unload([M|Mods]) ->
catch erlang:purge_module(M),
Expand All @@ -791,13 +795,6 @@ do_unload([M|Mods]) ->
do_unload([]) ->
ok.

sub([H|T],L) -> sub(T,del(H,L));
sub([],L) -> L.

del(Item, [Item|T]) -> T;
del(Item, [H|T]) -> [H|del(Item, T)];
del(_Item, []) -> [].

%%% -------------------------------------------------
%%% If the terminated Pid is one of the processes
%%% added to the Kernel, take down the system brutally.
Expand Down

0 comments on commit 9165872

Please sign in to comment.