File 0163-Halt-node-if-inet_gethost-cannot-start.patch of Package erlang
From b1a03912cb462f142a92ea5eff93683fed8c4a05 Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Fri, 4 Mar 2022 10:38:11 +0100
Subject: [PATCH 3/3] Halt node if inet_gethost cannot start
---
lib/kernel/src/inet_gethost_native.erl | 123 ++++++++++++-------------
1 file changed, 61 insertions(+), 62 deletions(-)
diff --git a/lib/kernel/src/inet_gethost_native.erl b/lib/kernel/src/inet_gethost_native.erl
index aa34fdd2c3..090f9b9ef9 100644
--- a/lib/kernel/src/inet_gethost_native.erl
+++ b/lib/kernel/src/inet_gethost_native.erl
@@ -21,7 +21,7 @@
-behaviour(supervisor_bridge).
%% Supervisor bridge exports
--export([start_link/0, init/1, terminate/2, start_raw/0, run_once/0]).
+-export([start_link/0, init/1, terminate/2]).
%% Server export
-export([server_init/2, main_loop/1]).
@@ -131,10 +131,16 @@ init([]) -> % Called by supervisor_bridge:start_link
start_link() ->
supervisor_bridge:start_link({local, ?PROCNAME_SUP}, ?MODULE, []).
+
+-spec terminate(term(), pid()) -> 'ok'.
+
+terminate(_Reason, Pid) ->
+ (catch exit(Pid, kill)),
+ ok.
+
+%%-----------------------------------------------------------------------
%% Only used in fallback situations, no supervisor, no bridge, serve only until
%% no requests present...
-start_raw() ->
- spawn(?MODULE,run_once,[]).
run_once() ->
Port = do_open_port(get_poolsize(), get_extra_args()),
@@ -158,12 +164,6 @@ run_once() ->
Pid ! {R, {error, timeout}}
end.
--spec terminate(term(), pid()) -> 'ok'.
-
-terminate(_Reason, Pid) ->
- (catch exit(Pid, kill)),
- ok.
-
%%-----------------------------------------------------------------------
%% Server API
%%-----------------------------------------------------------------------
@@ -395,37 +395,40 @@ do_open_port(Poolsize, ExtraArgs) ->
%% open_executable/2 below assumes overlapped_io is at the head
Opts = [overlapped_io, {args, Args}, {packet,4}, eof, binary],
RootDir = code:root_dir(),
- Prog =
- filename:join(
- [RootDir,
- "erts-"++erlang:system_info(version),
- "bin",
- ?PORT_PROGRAM]),
+ Prog = filename:join([RootDir, erts(), "bin", ?PORT_PROGRAM]),
Cont =
fun () ->
- [filename:join(
- [RootDir,
- "bin",
- erlang:system_info(system_architecture),
- ?PORT_PROGRAM])]
+ [filename:join([RootDir, "bin", target(), ?PORT_PROGRAM])]
end,
- open_executable([Prog|Cont], Opts, []).
+ open_executable([Prog|Cont], Opts).
-open_executable([Prog|Tail] = Progs, Opts, Acc) ->
- Try = {Prog,Opts},
+open_executable([Prog|Tail] = Progs, Opts) ->
try open_port({spawn_executable, Prog}, Opts)
catch
error : badarg when hd(Opts) =:= overlapped_io ->
- open_executable(Progs, tl(Opts), [Try|Acc]);
+ open_executable(Progs, tl(Opts));
error : enoent ->
- open_executable(Tail, Opts, [Try|Acc]);
+ open_executable(Tail, Opts);
error : Reason ->
- error({Reason, Try})
+ erlang:halt(
+ "Can not execute "++Prog++" : "++term2string(Reason))
end;
-open_executable([], _Opts, Acc) ->
- error({not_found, lists:reverse(Acc)});
-open_executable(Cont, Opts, Acc) ->
- open_executable(Cont(), Opts, Acc).
+open_executable([], _Opts) ->
+ erlang:halt(
+ "Can not find "++?PORT_PROGRAM++" for "++erts()++"/"++target());
+open_executable(Cont, Opts) ->
+ open_executable(Cont(), Opts).
+%% We regard not being able to start the resolver helper program
+%% as a node fatal error to avoid getting weird malfunction
+%% of name lookups
+
+erts() ->
+ "erts-"++erlang:system_info(version).
+target() ->
+ erlang:system_info(system_architecture).
+term2string(Term) ->
+ unicode:characters_to_list(io_lib:format("~tw", [Term])).
+
get_extra_args() ->
@@ -532,6 +535,34 @@ getit(Req, DefaultName) ->
Res2
end.
+ensure_started() ->
+ case whereis(?MODULE) of
+ undefined ->
+ ChildSpec =
+ {?PROCNAME_SUP, {?MODULE, start_link, []}, temporary,
+ 1000, worker, [?MODULE]},
+ ensure_started([kernel_safe_sup, net_sup], ChildSpec);
+ Pid ->
+ Pid
+ end.
+
+ensure_started([Supervisor|Supervisors], ChildSpec) ->
+ case whereis(Supervisor) of
+ undefined ->
+ ensure_started(Supervisors, ChildSpec);
+ _ ->
+ do_start(Supervisor, ChildSpec),
+ case whereis(?MODULE) of
+ undefined ->
+ exit({could_not_start_server, ?MODULE});
+ Pid ->
+ Pid
+ end
+ end;
+ensure_started([], _ChildSpec) ->
+ %% Icky fallback, run once without supervisor
+ spawn(fun run_once/0).
+
do_start(Sup, C) ->
{Child,_,_,_,_,_} = C,
case supervisor:start_child(Sup,C) of
@@ -546,38 +577,6 @@ do_start(Sup, C) ->
do_start(Sup, C)
end.
-ensure_started() ->
- case whereis(?MODULE) of
- undefined ->
- C = {?PROCNAME_SUP, {?MODULE, start_link, []}, temporary,
- 1000, worker, [?MODULE]},
- case whereis(kernel_safe_sup) of
- undefined ->
- case whereis(net_sup) of
- undefined ->
- %% Icky fallback, run once without supervisor
- start_raw();
- _ ->
- do_start(net_sup,C),
- case whereis(?MODULE) of
- undefined ->
- exit({could_not_start_server, ?MODULE});
- Pid0 ->
- Pid0
- end
- end;
- _ ->
- do_start(kernel_safe_sup,C),
- case whereis(?MODULE) of
- undefined ->
- exit({could_not_start_server, ?MODULE});
- Pid1 ->
- Pid1
- end
- end;
- Pid ->
- Pid
- end.
parse_address(BinHostent, DefaultName) ->
case catch
--
2.34.1