Skip to content

Commit

Permalink
Update on_load handling during boot
Browse files Browse the repository at this point in the history
Introduce a transient worker that is started by kernel:init
and that only calls init:run_on_load_handlers(), which will
run all so far postponed (after code load) on_load handlers.
The worker exits immediately after that.

This on_load worker is run after code_server and standard_error,
which should provide enough fundamentals for the on_load handlers
themselves.

The need for explicitly calling on_load handlers from e.g user_drv
and the SSL distribution inet_tls_dist should vanish.

Therefore init:run_on_load_handlers/1 should be removed, but
to avoid bootstrap problems that can wait to a later commit.
  • Loading branch information
RaimoNiskanen committed Feb 7, 2023
1 parent 1c1cc59 commit 4a28031
Show file tree
Hide file tree
Showing 3 changed files with 51 additions and 26 deletions.
54 changes: 35 additions & 19 deletions lib/kernel/src/kernel.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1996-2022. All Rights Reserved.
%% Copyright Ericsson AB 1996-2023. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
Expand Down Expand Up @@ -58,14 +58,19 @@ config_change(Changed, New, Removed) ->
%%% | kernel_sup (A)|
%%% ---------------
%%% |
%%% -------------------------------
%%% | | |
%%% <std services> ------------- -------------
%%% (file,code, | erl_dist (A)| | safe_sup (1)|
%%% rpc, ...) ------------- -------------
%%% | |
%%% (net_kernel, (disk_log, pg,
%%% auth, ...) ...)
%%% ------------------------------------------
%%% | | | | |
%%% <std services> | ------------- | -------------
%%% (code, [stderr], | | erl_dist (A)| | | safe_sup (1)|
%%% ...) | ------------- | -------------
%%% | | | |
%%% <on_load> ([net_sup], | (disk_log, pg,
%%% (transient) rpc, global, | ...)
%%% ...) |
%%% |
%%% <more services>
%%% (file, peer, [user],
%%% [logger], ...)
%%%
%%% The rectangular boxes are supervisors. All supervisors except
%%% for kernel_safe_sup terminates the entire erlang node if any of
Expand Down Expand Up @@ -118,6 +123,15 @@ init([]) ->
type => supervisor,
modules => [standard_error]},

OnLoad = #{id => on_load,
start =>
{proc_lib, start_link,
[?MODULE, ?FUNCTION_NAME, [on_load]]},
restart => transient,
shutdown => 2000,
type => worker,
modules => [?MODULE]},

User = #{id => user,
start => {user_sup, start, []},
restart => temporary,
Expand Down Expand Up @@ -148,7 +162,8 @@ init([]) ->
case init:get_argument(mode) of
{ok, [["minimal"]|_]} ->
{ok, {SupFlags,
[Code, File, StdError] ++ Peer ++
[Code, StdError, OnLoad] ++
[File | Peer] ++
[User, LoggerSup, Config, RefC, SafeSup]}};
_ ->
DistChildren =
Expand All @@ -175,11 +190,18 @@ init([]) ->
CompileServer = start_compile_server(),

{ok, {SupFlags,
[Code, InetDb | DistChildren] ++
[File, SigSrv, StdError] ++ Peer ++
[User, Config, RefC, SafeSup, LoggerSup] ++
[Code, StdError, OnLoad, InetDb | DistChildren] ++
[File, SigSrv | Peer] ++
[User, LoggerSup, Config, RefC, SafeSup] ++
Timer ++ CompileServer}}
end;
init(on_load) ->
%% Run the on_load handlers for all modules that have been
%% loaded so far. Running them at this point means that
%% on_load handlers can safely call some essential kernel processes,
%% in particular call code:priv_dir/1 or code:lib_dir/1.
init:run_on_load_handlers(),
proc_lib:init_ack({ok, self()});
init(safe) ->
SupFlags = #{strategy => one_for_one,
intensity => 4,
Expand All @@ -189,12 +211,6 @@ init(safe) ->
DiskLog = start_disk_log(),
Pg = start_pg(),

%% Run the on_load handlers for all modules that have been
%% loaded so far. Running them at this point means that
%% on_load handlers can safely call kernel processes
%% (and in particular call code:priv_dir/1 or code:lib_dir/1).
init:run_on_load_handlers(),

{ok, {SupFlags, Boot ++ DiskLog ++ Pg}}.

start_distribution() ->
Expand Down
5 changes: 1 addition & 4 deletions lib/kernel/src/user_drv.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1996-2021. All Rights Reserved.
%% Copyright Ericsson AB 1996-2023. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
Expand Down Expand Up @@ -139,9 +139,6 @@ callback_mode() -> state_functions.
-spec init(arguments()) -> gen_statem:init_result(init).
init(Args) ->
process_flag(trap_exit, true),
%% When running in embedded mode we need to call prim_tty:on_load manually here
%% as the automatic call happens after user is started.
ok = init:run_on_load_handlers([prim_tty]),

IsTTY = prim_tty:isatty(stdin) =:= true andalso prim_tty:isatty(stdout) =:= true,
StartShell = maps:get(initial_shell, Args, undefined) =/= noshell,
Expand Down
18 changes: 15 additions & 3 deletions lib/ssl/test/ssl_dist_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2007-2022. All Rights Reserved.
%% Copyright Ericsson AB 2007-2023. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
Expand Down Expand Up @@ -1102,6 +1102,7 @@ add_ssl_opts_config(Config) ->
{ok, _} = file:read_file_info(KrnlDir),
SSL_VSN = get_app_vsn(ssl),
VSN_CRYPTO = get_app_vsn(crypto),
VSN_ASN1 = get_app_vsn(asn1),
VSN_PKEY = get_app_vsn(public_key),

SslDir = filename:join([LibDir, "ssl-" ++ SSL_VSN]),
Expand All @@ -1116,6 +1117,7 @@ add_ssl_opts_config(Config) ->
" [{kernel, \"~s\"},~n"
" {stdlib, \"~s\"},~n"
" {crypto, \"~s\"},~n"
" {asn1, \"~s\"},~n"
" {public_key, \"~s\"},~n"
" {ssl, \"~s\"}]}.~n",
[case catch erlang:system_info(otp_release) of
Expand All @@ -1126,13 +1128,23 @@ add_ssl_opts_config(Config) ->
KRNL_VSN,
STDL_VSN,
VSN_CRYPTO,
VSN_ASN1,
VSN_PKEY,
SSL_VSN]),
ok = file:close(RelFile),
ok = systools:make_script(Script, []),
ct:log("Bootscript: ~p", [Script]),
case systools:make_script(Script, []) of
ok ->
ok;
NotOk ->
ct:log("Bootscript problem: ~p", [NotOk]),
erlang:error(NotOk)
end,
[{app_opts, "-boot " ++ Script} | Config]
catch
_:_ ->
Class : Reason : Stacktrace ->
ct:log("Exception while generating bootscript:~n~p",
[{Class, Reason, Stacktrace}]),
[{app_opts, "-pa \"" ++ filename:dirname(code:which(ssl))++"\""}
| add_comment_config(
"Bootscript wasn't used since the test wasn't run on an "
Expand Down

0 comments on commit 4a28031

Please sign in to comment.