Skip to content

Commit

Permalink
Extend net_kernel:start/2 options
Browse files Browse the repository at this point in the history
Introduced the 'dist_listen' and 'hidden' options.
  • Loading branch information
rickard-green committed May 25, 2022
1 parent 500e63b commit 4984ae4
Show file tree
Hide file tree
Showing 7 changed files with 164 additions and 66 deletions.
7 changes: 7 additions & 0 deletions erts/doc/src/erl_cmd.xml
Original file line number Diff line number Diff line change
Expand Up @@ -313,6 +313,13 @@ $ <input>erl \
used to disable all non permanent features.
</p>
</item>
<tag><marker id="dist_listen"/><c>-dist_listen true|false</c></tag>
<item><p>
Specifies whether this node should be listening for incoming
distribution connections or not. By default a node will listen for
incoming connections. Setting this option to <c>false</c>
implies <seecom marker="#hidden"><c>-hidden</c></seecom>.
</p></item>
<tag><c><![CDATA[-emu_args]]></c></tag>
<item>
<p>Useful for debugging. Prints the arguments sent to the emulator.</p>
Expand Down
6 changes: 0 additions & 6 deletions lib/kernel/doc/src/kernel_app.xml
Original file line number Diff line number Diff line change
Expand Up @@ -176,12 +176,6 @@
<seeerl marker="net_kernel"><c>net_kernel(3)</c></seeerl>.</p></item>
</taglist>
</item>
<tag><marker id="dist_listen"/><c>dist_listen = boolean()</c></tag>
<item>
<p>Specifies whether this node should be listening for incoming
distribution connections. Using this option implies that the node
also is <seecom marker="erts:erl#hidden"><c>-hidden</c></seecom>.</p>
</item>
<tag><marker id="permissions"/><c>permissions = [Perm]</c></tag>
<item>
<p>Specifies the default permission for applications when they
Expand Down
35 changes: 31 additions & 4 deletions lib/kernel/doc/src/net_kernel.xml
Original file line number Diff line number Diff line change
Expand Up @@ -550,10 +550,13 @@ ok
</p>

<p>
If <c>Name</c> is set to <em><c>undefined</c></em> the distribution
will be started to request a dynamic node name from the first node it
connects to. See <seeguide marker="system/reference_manual:distributed#dyn_node_name">
Dynamic Node Name</seeguide>.
If <c><anno>Name</anno></c> is set to <em><c>undefined</c></em> the
distribution will be started to request a dynamic node name from the
first node it connects to. See
<seeguide marker="system/reference_manual:distributed#dyn_node_name">
Dynamic Node Name</seeguide>. Setting <c><anno>Name</anno></c> to
<c>undefined</c> implies options <c>dist_listen => false</c> and
<c>hidden => true</c>.
</p>

<p>Currently supported options:</p>
Expand Down Expand Up @@ -588,6 +591,30 @@ ok
<c><anno>NetTickIntensity</anno></c> value is passed as option value
to this function, the call will fail.
</p></item>
<tag><c>dist_listen => boolean()</c></tag>
<item><p>
Enable or disable listening for incoming connections. Defaults to
the value of the
<seecom marker="erts:erl#dist_listen"><c>-dist_listen</c></seecom>
<c>erl</c> command line argument. Note that
<c>dist_listen => false</c> implies <c>hidden => true</c>.
</p>
<p>
If <c>undefined</c> has been passed as <c><anno>Name</anno></c>,
the <c>dist_listen</c> option will be overridden with
<c>dist_listen => false</c>.
</p></item>
<tag><c>hidden => boolean()</c></tag>
<item><p>
Enable or disable hidden node. Defaults to <c>true</c> if the
<seecom marker="erts:erl#hidden"><c>-hidden</c></seecom> <c>erl</c>
command line argument has been passed; otherwise <c>false</c>.
</p>
<p>
If <c>undefined</c> has been passed as <c><anno>Name</anno></c>,
or the option <c>dist_listen</c> equals <c>false</c>, the
<c>hidden</c> option will be overridden with <c>hidden => true</c>.
</p></item>
</taglist>
</desc>
</func>
Expand Down
1 change: 0 additions & 1 deletion lib/kernel/src/dist_util.erl
Original file line number Diff line number Diff line change
Expand Up @@ -430,7 +430,6 @@ handshake_we_started(#hs_data{request_type=ReqType,
case node() of
nonode@nohost ->
{node, "undefined", Host} = split_node(MyNode),
false = net_kernel:dist_listen(),
{?DFLAG_NAME_ME, Host};

_ ->
Expand Down
129 changes: 82 additions & 47 deletions lib/kernel/src/net_kernel.erl
Original file line number Diff line number Diff line change
Expand Up @@ -71,8 +71,7 @@
nodename/0,
protocol_childspecs/0,
epmd_module/0,
get_state/0,
dist_listen/0]).
get_state/0]).

-export([disconnect/1, async_disconnect/1, passive_cnct/1]).
-export([hidden_connect_node/1]).
Expand Down Expand Up @@ -414,7 +413,9 @@ retry_request_maybe(Req) ->
-spec start(Name, Options) -> {ok, pid()} | {error, Reason} when
Options :: #{name_domain => NameDomain,
net_ticktime => NetTickTime,
net_tickintensity => NetTickIntensity},
net_tickintensity => NetTickIntensity,
dist_listen => boolean(),
hidden => boolean()},
Name :: atom(),
NameDomain :: shortnames | longnames,
NetTickTime :: pos_integer(),
Expand All @@ -433,6 +434,10 @@ start(Name, Options) when is_atom(Name), is_map(Options) ->
4 =< Val,
Val =< 1000 ->
ok;
(dist_listen, Val) when is_boolean(Val) ->
ok;
(hidden, Val) when is_boolean(Val) ->
ok;
(Opt, Val) ->
error({invalid_option, Opt, Val})
end, Options)
Expand Down Expand Up @@ -519,28 +524,66 @@ make_init_opts(Opts) ->
NTT = if NTT1 rem NTI =:= 0 -> NTT1;
true -> ((NTT1 div NTI) + 1) * NTI
end,

ND = case maps:find(name_domain, Opts) of
{ok, ND0} ->
ND0;
error ->
longnames
end,

Opts#{net_ticktime => NTT, net_tickintensity => NTI, name_domain => ND}.
DL = case split_node(maps:get(name, Opts)) of
{"undefined", _} ->
%% dynamic node name implies dist_listen=false
false;
_ ->
case maps:find(dist_listen, Opts) of
error ->
dist_listen_argument();
{ok, false} ->
false;
_ ->
true
end
end,

H = case DL of
false ->
%% dist_listen=false implies hidden=true
true;
true ->
case maps:find(hidden, Opts) of
error ->
hidden_argument();
{ok, true} ->
true;
_ ->
false
end
end,

Opts#{net_ticktime => NTT,
net_tickintensity => NTI,
name_domain => ND,
dist_listen => DL,
hidden => H}.

init(#{name := Name,
name_domain := NameDomain,
net_ticktime := NetTicktime,
net_tickintensity := NetTickIntensity,
clean_halt := CleanHalt,
supervisor := Supervisor}) ->
supervisor := Supervisor,
dist_listen := DistListen,
hidden := Hidden}) ->
process_flag(trap_exit,true),
case init_node(Name, NameDomain, CleanHalt) of
persistent_term:put({?MODULE, publish_type},
if Hidden -> hidden;
true -> normal
end),
case init_node(Name, NameDomain, CleanHalt, DistListen) of
{ok, Node, Listeners} ->
process_flag(priority, max),
persistent_term:put({?MODULE, publish_type},
publish_type()),
TickInterval = NetTicktime div NetTickIntensity,
Ticker = spawn_link(net_kernel, ticker, [self(), TickInterval]),
{ok, #state{node = Node,
Expand Down Expand Up @@ -1807,10 +1850,10 @@ get_proto_mod(_Family, _Protocol, []) ->

%% -------- Initialisation functions ------------------------

init_node(Name, LongOrShortNames, CleanHalt) ->
init_node(Name, LongOrShortNames, CleanHalt, Listen) ->
case create_name(Name, LongOrShortNames, 1) of
{ok,Node} ->
case start_protos(Node, CleanHalt) of
case start_protos(Node, CleanHalt, Listen) of
{ok, Ls} ->
{ok, Node, Ls};
Error ->
Expand Down Expand Up @@ -1925,65 +1968,57 @@ protocol_childspecs([H|T]) ->
end.

%%
%% epmd_module() -> module_name of erl_epmd or similar gen_server_module.
%% epmd_module argument -> module_name of erl_epmd or similar gen_server_module.
%%

epmd_module() ->
case init:get_argument(epmd_module) of
{ok,[[Module]]} ->
{ok,[[Module | _] | _]} ->
list_to_atom(Module);
_ ->
erl_epmd
end.

%%%
%%% publish type
%%%
publish_type() ->
case dist_listen() of
false ->
hidden;
true ->
case init:get_argument(hidden) of
{ok,[[] | _]} ->
hidden;
{ok,[["true" | _] | _]} ->
hidden;
_ ->
normal
end
end.

%%
%% dist_listen() -> whether the erlang distribution should listen for connections
%% -dist_listen argument -> whether the erlang distribution should listen for connections
%%
dist_listen() ->
case persistent_term:get(net_kernel, undefined) of
dynamic_node_name ->

dist_listen_argument() ->
case init:get_argument(dist_listen) of
{ok,[["false" | _] | _]} ->
false;
_ ->
case init:get_argument(dist_listen) of
{ok,[[DoListen]]} ->
list_to_atom(DoListen) =/= false;
_ ->
true
end
true
end.

%%%
%%% -hidden command line argument
%%%

hidden_argument() ->
case init:get_argument(hidden) of
{ok,[[] | _]} ->
true;
{ok,[["true" | _] | _]} ->
true;
_ ->
false
end.

%%
%% Start all protocols
%%

start_protos(Node, CleanHalt) ->
start_protos(Node, CleanHalt, Listen) ->
case init:get_argument(proto_dist) of
{ok, [Protos]} ->
start_protos(Node, Protos, CleanHalt);
start_protos(Node, Protos, CleanHalt, Listen);
_ ->
start_protos(Node, ["inet_tcp"], CleanHalt)
start_protos(Node, ["inet_tcp"], CleanHalt, Listen)
end.

start_protos(Node, Ps, CleanHalt) ->
Listeners = case dist_listen() of
start_protos(Node, Ps, CleanHalt, Listen) ->
Listeners = case Listen of
false -> start_protos_no_listen(Node, Ps, [], CleanHalt);
_ -> start_protos_listen(Node, Ps, CleanHalt)
end,
Expand Down Expand Up @@ -2046,7 +2081,7 @@ wrap_creation(Cr) ->
start_protos_listen(Node, Ps, CleanHalt) ->
case split_node(Node) of
{"undefined", _} ->
start_protos_no_listen(Node, Ps, [], CleanHalt);
error({internal_error, "Dynamic node name and dist listen both enabled"});
{Name, "@"++Host} ->
start_protos_listen(list_to_atom(Name), Host, Node, Ps, [], CleanHalt)
end.
Expand Down
Loading

0 comments on commit 4984ae4

Please sign in to comment.