File 1234-Add-tests-for-start_epmd-and-epmd_module-options.patch of Package erlang

From 8ff06daa90c7c3c599c9e8cbc93fe98c2ed5ebfa Mon Sep 17 00:00:00 2001
From: Magnus Henoch <magnus@erlang-solutions.com>
Date: Wed, 25 May 2016 17:35:11 +0100
Subject: [PATCH 3/3] Add tests for -start_epmd and -epmd_module options

For -start_epmd, check that the node starts properly and that we can
ping it.

For -epmd_module, start two nodes that can communicate only because we
supply the correct port number through a command line argument.
---
 erts/emulator/test/distribution_SUITE.erl | 69 ++++++++++++++++++++++++++++++-
 1 file changed, 67 insertions(+), 2 deletions(-)

diff --git a/erts/emulator/test/distribution_SUITE.erl b/erts/emulator/test/distribution_SUITE.erl
index d0096fb..26780f6 100644
--- a/erts/emulator/test/distribution_SUITE.erl
+++ b/erts/emulator/test/distribution_SUITE.erl
@@ -56,7 +56,8 @@
 	 bad_dist_ext_receive/1,
 	 bad_dist_ext_process_info/1,
 	 bad_dist_ext_control/1,
-	 bad_dist_ext_connection_id/1]).
+	 bad_dist_ext_connection_id/1,
+	 start_epmd_false/1, epmd_module/1]).
 
 -export([init_per_testcase/2, end_per_testcase/2]).
 
@@ -67,6 +67,9 @@
 	 dist_evil_parallel_receiver/0,
          sendersender/4, sendersender2/4]).
 
+%% epmd_module exports
+-export([start_link/0, register_node/2, port_please/2]).
+
 suite() -> [{ct_hooks,[ts_install_cth]}].
 
 all() -> 
@@ -76,7 +80,8 @@ all() ->
      {group, trap_bif}, {group, dist_auto_connect},
      dist_parallel_send, atom_roundtrip, unicode_atom_roundtrip, atom_roundtrip_r15b,
      contended_atom_cache_entry, contended_unicode_atom_cache_entry,
-     bad_dist_structure, {group, bad_dist_ext}].
+     bad_dist_structure, {group, bad_dist_ext},
+     start_epmd_false, epmd_module].
 
 groups() -> 
     [{bulk_send, [], [bulk_send_small, bulk_send_big, bulk_send_bigbig]},
@@ -1881,6 +1886,66 @@ dmsg_ext(Term) ->
 dmsg_bad_atom_cache_ref() ->
     [$R, 137].
 
+start_epmd_false(Config) when is_list(Config) ->
+    %% Start a node with the option -start_epmd false.
+    {ok, OtherNode} = start_node(start_epmd_false, "-start_epmd false"),
+    %% We should be able to ping it, as epmd was started by us:
+    pong = net_adm:ping(OtherNode),
+    stop_node(OtherNode),
+
+    ok.
+
+epmd_module(Config) when is_list(Config) ->
+    %% We need a relay node to test this, since the test node uses the
+    %% standard epmd module.
+    Sock1 = start_relay_node(epmd_module_node1, "-epmd_module " ++ ?MODULE_STRING),
+    Node1 = inet_rpc_nodename(Sock1),
+    %% Ask what port it's listening on - it won't have registered with
+    %% epmd.
+    {ok, {ok, Port1}} = do_inet_rpc(Sock1, application, get_env, [kernel, dist_listen_port]),
+
+    %% Start a second node, passing the port number as a secret
+    %% argument.
+    Sock2 = start_relay_node(epmd_module_node2, "-epmd_module " ++ ?MODULE_STRING
+			     ++ " -other_node_port " ++ integer_to_list(Port1)),
+    Node2 = inet_rpc_nodename(Sock2),
+    %% Node 1 can't ping node 2
+    {ok, pang} = do_inet_rpc(Sock1, net_adm, ping, [Node2]),
+    {ok, []} = do_inet_rpc(Sock1, erlang, nodes, []),
+    {ok, []} = do_inet_rpc(Sock2, erlang, nodes, []),
+    %% But node 2 can ping node 1
+    {ok, pong} = do_inet_rpc(Sock2, net_adm, ping, [Node1]),
+    {ok, [Node2]} = do_inet_rpc(Sock1, erlang, nodes, []),
+    {ok, [Node1]} = do_inet_rpc(Sock2, erlang, nodes, []),
+
+    stop_relay_node(Sock2),
+    stop_relay_node(Sock1).
+
+%% epmd_module functions:
+
+start_link() ->
+    ignore.
+
+register_node(_Name, Port) ->
+    %% Save the port number we're listening on.
+    application:set_env(kernel, dist_listen_port, Port),
+    Creation = rand:uniform(3),
+    {ok, Creation}.
+
+port_please(_Name, _Ip) ->
+    case init:get_argument(other_node_port) of
+	error ->
+	    %% None specified.  Default to 42.
+	    Port = 42,
+	    Version = 5,
+	    {port, Port, Version};
+	{ok, [[PortS]]} ->
+	    %% Port number given on command line.
+	    Port = list_to_integer(PortS),
+	    Version = 5,
+	    {port, Port, Version}
+    end.
+
 %%% Utilities
 
 timestamp() ->
-- 
2.1.4

openSUSE Build Service is sponsored by