File 2891-Improve-boot-error-messages.patch of Package erlang

From 1cb08afe092e7967844173a7d094a6c0ec8673a9 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@dashbit.co>
Date: Sat, 15 Oct 2022 11:14:53 +0200
Subject: [PATCH] Improve boot error messages

Today if there is a crash during boot or eval,
because a more recent Erlang/OTP version is
required, the user is prompted with this message:

    $ erl -noshell -s oops
    {"init terminating in do_boot",{undef,
    [{oops,start,[],[]},{init,start_em,1,[]}
    ,{init,do_boot,3,[]}]}}
    init terminating in do_boot ({undef,[{oops,
    start,[],[]},{init,start_em,1,[]},{init,
    do_boot,3,[]}]})

    Crash dump is being written to:
    erl_crash.dump...done

Unfortunately, this message gives little indication
of what is wrong besides the "undef" atom. This
particularly problematic when users are running
a system software (Rebar, Elixir, etc) against an
old system version of Erlang/OTP.

This commit improves the boot error messages
such that:

  1. It removes the double reports from
     erlang:display/1 and crash dump

  2. Validates the module given to -s
     and attempts to provide a human error
     for common cases

  3. Makes sure the -eval failure is printed
     and uses a consistent format with -s

  4. Improve error messages to not include
     internal details such as "do_boot"

  5. It suggests that, besides using an old
     version of Erlang/OTP, they may also use
     a new one

Now we get:

    $ erl -noshell -s oops
    Error! Failed to load module 'oops' because
    the module cannot be found. Make sure the
    module name is correct and its .beam is in
    the code path

    Runtime terminating during boot ({undef,
    [{init,start_it,1,[]},{init,start_em,1,[]},
    {init,do_boot,3,[]}]})

    Crash dump is being written to:
    erl_crash.dump...done

If the .beam file exists but cannot be loaded:

    $ erl -noshell -s oops
    Error! Failed to load module 'oops' because
    the module requires a more recent Erlang/OTP
    version or its .beam was corrupted (you are
    running Erlang/OTP 26)

    Runtime terminating during boot ({undef,
    [{init,start_it,1,[]},{init,start_em,1,[]},
    {init,do_boot,3,[]}]})

    Crash dump is being written to:
    erl_crash.dump...done
---
 erts/emulator/beam/beam_load.c |  2 +-
 erts/preloaded/src/init.erl    | 52 +++++++++++++++++++++++++---------
 lib/kernel/test/init_SUITE.erl | 19 +++++++++++--
 3 files changed, 57 insertions(+), 16 deletions(-)

diff --git a/erts/emulator/beam/beam_load.c b/erts/emulator/beam/beam_load.c
index 85beba57ee..c7c0a715b5 100644
--- a/erts/emulator/beam/beam_load.c
+++ b/erts/emulator/beam/beam_load.c
@@ -47,7 +47,7 @@ Uint erts_total_code_size;
 
 static int load_code(LoaderState *stp);
 
-#define PLEASE_RECOMPILE "please re-compile this module with an Erlang/OTP " ERLANG_OTP_RELEASE " compiler"
+#define PLEASE_RECOMPILE "please re-compile this module with an Erlang/OTP " ERLANG_OTP_RELEASE " compiler or update your Erlang/OTP version"
 
 /**********************************************************************/
 
diff --git a/erts/preloaded/src/init.erl b/erts/preloaded/src/init.erl
index a95df3741e..96e0ec1dd6 100644
--- a/erts/preloaded/src/init.erl
+++ b/erts/preloaded/src/init.erl
@@ -396,8 +396,8 @@ boot_loop(BootPid, State) ->
 	    loop(State#state{status = {started,PS},
 			     subscribed = []});
 	{'EXIT',BootPid,Reason} ->
-	    erlang:display({"init terminating in do_boot",Reason}),
-	    crash("init terminating in do_boot", [Reason]);
+	    % erlang:display({"init terminating in do_boot",Reason}),
+	    crash("Runtime terminating during boot", [Reason]);
 	{'EXIT',Pid,Reason} ->
 	    Kernel = State#state.kernel,
 	    terminate(Pid,Kernel,Reason), %% If Pid is a Kernel pid, halt()!
@@ -462,9 +462,9 @@ new_kernelpid({_Name,ignore},BootPid,State) ->
     BootPid ! {self(),ignore},
     State;
 new_kernelpid({Name,What},BootPid,State) ->
-    erlang:display({"could not start kernel pid",Name,What}),
+    % erlang:display({"could not start kernel pid",Name,What}),
     clear_system(false,BootPid,State),
-    crash("could not start kernel pid", [Name, What]).
+    crash("Could not start kernel pid", [Name, What]).
 
 %% Here is the main loop after the system has booted.
 
@@ -834,7 +834,7 @@ terminate(Pid,Kernel,Reason) ->
     case kernel_pid(Pid,Kernel) of
 	{ok,Name} ->
 	    sleep(500), %% Flush error printouts!
-	    erlang:display({"Kernel pid terminated",Name,Reason}),
+	    % erlang:display({"Kernel pid terminated",Name,Reason}),
 	    crash("Kernel pid terminated", [Name, Reason]);
 	_ ->
 	    false
@@ -1235,18 +1235,44 @@ start_it({eval,Bin}) ->
         {value, _Value, _Bs} = erl_eval:exprs(Expr, erl_eval:new_bindings()),
         ok
     catch E:R:ST ->
-            erlang:display_string(
-              binary_to_list(
-                iolist_to_binary(["Failed to eval: ",Bin,"\n"]))),
+            Message = [<<"Error! Failed to eval: ">>, Bin, <<"\r\n\r\n">>],
+            erlang:display_string(binary_to_list(iolist_to_binary(Message))),
             erlang:raise(E,R,ST)
     end;
-start_it([_|_]=MFA) ->
-    case MFA of
-	[M]        -> M:start();
-	[M,F]      -> M:F();
-	[M,F|Args] -> M:F(Args)	% Args is a list
+start_it([M|FA]) ->
+    case code:ensure_loaded(M) of
+        {module, M} ->
+            case FA of
+                []       -> M:start();
+                [F]      -> M:F();
+                [F|Args] -> M:F(Args)	% Args is a list
+            end;
+
+        {error, Reason} ->
+            Message = [explain_ensure_loaded_error(M, Reason), <<"\r\n\r\n">>],
+            erlang:display_string(binary_to_list(iolist_to_binary(Message))),
+            erlang:error(undef)
     end.
 
+explain_ensure_loaded_error(M, badfile) ->
+    S = [<<"it requires a more recent Erlang/OTP version "
+           "or its .beam file was corrupted.\r\n"
+           "(You are running Erlang/OTP ">>,
+         erlang:system_info(otp_release), <<".)">>],
+    explain_add_head(M, S);
+explain_ensure_loaded_error(M, nofile) ->
+    S = <<"it cannot be found. Make sure that the module name is correct and\r\n",
+          "that its .beam file is in the code path.">>,
+    explain_add_head(M, S);
+explain_ensure_loaded_error(M, Other) ->
+    [<<"Error! Failed to load module '", (atom_to_binary(M))/binary,
+       "'. Reason: ">>,
+     atom_to_binary(Other)].
+
+explain_add_head(M, S) ->
+    [<<"Error! Failed to load module '", (atom_to_binary(M))/binary,
+       "' because ">>, S].
+
 %% Load a module.
 
 do_load_module(Mod, BinCode) ->
diff --git a/lib/kernel/test/init_SUITE.erl b/lib/kernel/test/init_SUITE.erl
index bc3882b862..ea75f040f2 100644
--- a/lib/kernel/test/init_SUITE.erl
+++ b/lib/kernel/test/init_SUITE.erl
@@ -29,7 +29,7 @@
 	 many_restarts/0, many_restarts/1, restart_with_mode/1,
 	 get_plain_arguments/1,
 	 reboot/1, stop_status/1, stop/1, get_status/1, script_id/1,
-         dot_erlang/1,
+         dot_erlang/1, unknown_module/1,
 	 find_system_processes/0]).
 -export([boot1/1, boot2/1]).
 
@@ -48,7 +48,7 @@ all() ->
     [get_arguments, get_argument, boot_var,
      many_restarts, restart_with_mode,
      get_plain_arguments, restart, stop_status, get_status, script_id,
-     dot_erlang, {group, boot}].
+     dot_erlang, unknown_module, {group, boot}].
 
 groups() -> 
     [{boot, [], [boot1, boot2]}].
@@ -689,6 +689,21 @@ dot_erlang(Config) ->
 
     ok.
 
+unknown_module(Config) when is_list(Config) ->
+    Port = open_port({spawn, "erl -s unknown_module"},
+                     [exit_status, use_stdio, stderr_to_stdout]),
+    Error = "Error! Failed to load module 'unknown_module' because it cannot be found.",
+    [_ | _] = string:find(collect_until_exit_one(Port), Error),
+    ok.
+
+collect_until_exit_one(Port) ->
+    receive
+        {Port, {data, Msg}} -> Msg ++ collect_until_exit_one(Port);
+        {Port, {exit_status, 1}} -> []
+    after
+        30_000 -> ct:fail(erl_timeout)
+    end.
+
 %% ------------------------------------------------
 %% Start the slave system with -boot flag.
 %% ------------------------------------------------
-- 
2.35.3

openSUSE Build Service is sponsored by