File 3031-peer-Make-order-of-fields-in-start_options-match-doc.patch of Package erlang

From e663b307a54bd6b9868af233583ecae6b8d6c6be Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Thu, 30 Jun 2022 15:24:32 +0200
Subject: [PATCH 1/4] peer: Make order of fields in start_options match docs

---
 lib/stdlib/doc/src/peer.xml | 266 ++++++++++++++++++------------------
 lib/stdlib/src/peer.erl     |   2 +-
 2 files changed, 134 insertions(+), 134 deletions(-)

diff --git a/lib/stdlib/doc/src/peer.xml b/lib/stdlib/doc/src/peer.xml
index d8ac800605..e4a06c75fe 100644
--- a/lib/stdlib/doc/src/peer.xml
+++ b/lib/stdlib/doc/src/peer.xml
@@ -99,60 +99,60 @@
       of the same test suite running in parallel</item>
     </list>
     <code type="erl">
-      -module(my_SUITE).
-      -behaviour(ct_suite).
-      -export([all/0, groups/0]).
-      -export([basic/1, args/1, named/1, restart_node/1, multi_node/1]).
-
-      -include_lib("common_test/include/ct.hrl").
-
-      groups() ->
-          [{quick, [parallel],
-              [basic, args, named, restart_node, multi_node]}].
-
-      all() ->
-          [{group, quick}].
-
-      basic(Config) when is_list(Config) ->
-          {ok, Peer, _Node} = ?CT_PEER(),
-          peer:stop(Peer).
-
-      args(Config) when is_list(Config) ->
-          %% specify additional arguments to the new node
-          {ok, Peer, _Node} = ?CT_PEER(["-emu_flavor", "smp"]),
-          peer:stop(Peer).
-
-      named(Config) when is_list(Config) ->
-          %% pass test case name down to function starting nodes
-          Peer = start_node_impl(named_test),
-          peer:stop(Peer).
-
-      start_node_impl(ActualTestCase) ->
-          {ok, Peer, Node} = ?CT_PEER(#{name => ?CT_PEER_NAME(ActualTestCase)}),
-          %% extra setup needed for multiple test cases
-          ok = rpc:call(Node, application, set_env, [kernel, key, value]),
-          Peer.
-
-      restart_node(Config) when is_list(Config) ->
-          Name = ?CT_PEER_NAME(),
-          {ok, Peer, Node} = ?CT_PEER(#{name => Name}),
-          peer:stop(Peer),
-          %% restart the node with the same name as before
-          {ok, Peer2, Node} = ?CT_PEER(#{name => Name, args => ["+fnl"]}),
-          peer:stop(Peer2).
+-module(my_SUITE).
+-behaviour(ct_suite).
+-export([all/0, groups/0]).
+-export([basic/1, args/1, named/1, restart_node/1, multi_node/1]).
+
+-include_lib("common_test/include/ct.hrl").
+
+groups() ->
+    [{quick, [parallel],
+        [basic, args, named, restart_node, multi_node]}].
+
+all() ->
+    [{group, quick}].
+
+basic(Config) when is_list(Config) ->
+    {ok, Peer, _Node} = ?CT_PEER(),
+    peer:stop(Peer).
+
+args(Config) when is_list(Config) ->
+    %% specify additional arguments to the new node
+    {ok, Peer, _Node} = ?CT_PEER(["-emu_flavor", "smp"]),
+    peer:stop(Peer).
+
+named(Config) when is_list(Config) ->
+    %% pass test case name down to function starting nodes
+    Peer = start_node_impl(named_test),
+    peer:stop(Peer).
+
+start_node_impl(ActualTestCase) ->
+    {ok, Peer, Node} = ?CT_PEER(#{name => ?CT_PEER_NAME(ActualTestCase)}),
+    %% extra setup needed for multiple test cases
+    ok = rpc:call(Node, application, set_env, [kernel, key, value]),
+    Peer.
+
+restart_node(Config) when is_list(Config) ->
+    Name = ?CT_PEER_NAME(),
+    {ok, Peer, Node} = ?CT_PEER(#{name => Name}),
+    peer:stop(Peer),
+    %% restart the node with the same name as before
+    {ok, Peer2, Node} = ?CT_PEER(#{name => Name, args => ["+fnl"]}),
+    peer:stop(Peer2).
     </code>
 
     <p>
       The next example demonstrates how to start multiple nodes concurrently:
     </p>
     <code type="erl">
-      multi_node(Config) when is_list(Config) ->
-          Peers = [?CT_PEER(#{wait_boot => {self(), tag}})
-              || _ &lt;- lists:seq(1, 4)],
-          %% wait for all nodes to complete boot process, get their names:
-          _Nodes = [receive {tag, {started, Node, Peer}} -> Node end
-              || {ok, Peer} &lt;- Peers],
-          [peer:stop(Peer) || {ok, Peer} &lt;- Peers].
+multi_node(Config) when is_list(Config) ->
+    Peers = [?CT_PEER(#{wait_boot => {self(), tag}})
+        || _ &lt;- lists:seq(1, 4)],
+    %% wait for all nodes to complete boot process, get their names:
+    _Nodes = [receive {tag, {started, Node, Peer}} -> Node end
+        || {ok, Peer} &lt;- Peers],
+    [peer:stop(Peer) || {ok, Peer} &lt;- Peers].
     </code>
 
     <p>
@@ -161,9 +161,9 @@
       prompt.
     </p>
     <code type="erl">
-      Ssh = os:find_executable("ssh"),
-      peer:start_link(#{exec => {Ssh, ["another_host", "erl"]},
-          connection => standard_io}),
+Ssh = os:find_executable("ssh"),
+peer:start_link(#{exec => {Ssh, ["another_host", "erl"]},
+    connection => standard_io}),
     </code>
 
     <p>
@@ -172,76 +172,76 @@
       running inside containers form an Erlang cluster.
     </p>
     <code type="erl">
-      docker(Config) when is_list(Config) ->
-          Docker = os:find_executable("docker"),
-          PrivDir = proplists:get_value(priv_dir, Config),
-          build_release(PrivDir),
-          build_image(PrivDir),
-
-          %% start two Docker containers
-          {ok, Peer, Node} = peer:start_link(#{name => lambda,
-              connection => standard_io,
-              exec => {Docker, ["run", "-h", "one", "-i", "lambda"]}}),
-          {ok, Peer2, Node2} = peer:start_link(#{name => lambda,
-              connection => standard_io,
-              exec => {Docker, ["run", "-h", "two", "-i", "lambda"]}}),
-
-          %% find IP address of the second node using alternative connection RPC
-          {ok, Ips} = peer:call(Peer2, inet, getifaddrs, []),
-          {"eth0", Eth0} = lists:keyfind("eth0", 1, Ips),
-          {addr, Ip} = lists:keyfind(addr, 1, Eth0),
-
-          %% make first node to discover second one
-          ok = peer:call(Peer, inet_db, set_lookup, [[file]]),
-          ok = peer:call(Peer, inet_db, add_host, [Ip, ["two"]]),
-
-          %% join a cluster
-          true = peer:call(Peer, net_kernel, connect_node, [Node2]),
-          %% verify that second peer node has only the first node visible
-          [Node] = peer:call(Peer2, erlang, nodes, []),
-
-          %% stop peers, causing containers to also stop
-          peer:stop(Peer2),
-          peer:stop(Peer).
-
-      build_release(Dir) ->
-          %% load sasl.app file, otherwise application:get_key will fail
-          application:load(sasl),
-          %% create *.rel - release file
-          RelFile = filename:join(Dir, "lambda.rel"),
-          Release = {release, {"lambda", "1.0.0"},
-              {erts, erlang:system_info(version)},
-              [{App, begin {ok, Vsn} = application:get_key(App, vsn), Vsn end}
-                  || App &lt;- [kernel, stdlib, sasl]]},
-          ok = file:write_file(RelFile, list_to_binary(lists:flatten(
-              io_lib:format("~tp.", [Release])))),
-          RelFileNoExt = filename:join(Dir, "lambda"),
-
-          %% create boot script
-          {ok, systools_make, []} = systools:make_script(RelFileNoExt,
-              [silent, {outdir, Dir}]),
-          %% package release into *.tar.gz
-          ok = systools:make_tar(RelFileNoExt, [{erts, code:root_dir()}]).
-
-      build_image(Dir) ->
-          %% Create Dockerfile example, working only for Ubuntu 20.04
-          %% Expose port 4445, and make Erlang distribution to listen
-          %%  on this port, and connect to it without EPMD
-          %% Set cookie on both nodes to be the same.
-          BuildScript = filename:join(Dir, "Dockerfile"),
-          Dockerfile =
-            "FROM ubuntu:20.04 as runner\n"
-            "EXPOSE 4445\n"
-            "WORKDIR /opt/lambda\n"
-            "COPY lambda.tar.gz /tmp\n"
-            "RUN tar -zxvf /tmp/lambda.tar.gz -C /opt/lambda\n"
-            "ENTRYPOINT [\"/opt/lambda/erts-" ++ erlang:system_info(version) ++
-            "/bin/dyn_erl\", \"-boot\", \"/opt/lambda/releases/1.0.0/start\","
-            " \"-kernel\", \"inet_dist_listen_min\", \"4445\","
-            " \"-erl_epmd_port\", \"4445\","
-            " \"-setcookie\", \"secret\"]\n",
-          ok = file:write_file(BuildScript, Dockerfile),
-          os:cmd("docker build -t lambda " ++ Dir).
+docker(Config) when is_list(Config) ->
+    Docker = os:find_executable("docker"),
+    PrivDir = proplists:get_value(priv_dir, Config),
+    build_release(PrivDir),
+    build_image(PrivDir),
+
+    %% start two Docker containers
+    {ok, Peer, Node} = peer:start_link(#{name => lambda,
+        connection => standard_io,
+        exec => {Docker, ["run", "-h", "one", "-i", "lambda"]}}),
+    {ok, Peer2, Node2} = peer:start_link(#{name => lambda,
+        connection => standard_io,
+        exec => {Docker, ["run", "-h", "two", "-i", "lambda"]}}),
+
+    %% find IP address of the second node using alternative connection RPC
+    {ok, Ips} = peer:call(Peer2, inet, getifaddrs, []),
+    {"eth0", Eth0} = lists:keyfind("eth0", 1, Ips),
+    {addr, Ip} = lists:keyfind(addr, 1, Eth0),
+
+    %% make first node to discover second one
+    ok = peer:call(Peer, inet_db, set_lookup, [[file]]),
+    ok = peer:call(Peer, inet_db, add_host, [Ip, ["two"]]),
+
+    %% join a cluster
+    true = peer:call(Peer, net_kernel, connect_node, [Node2]),
+    %% verify that second peer node has only the first node visible
+    [Node] = peer:call(Peer2, erlang, nodes, []),
+
+    %% stop peers, causing containers to also stop
+    peer:stop(Peer2),
+    peer:stop(Peer).
+
+build_release(Dir) ->
+    %% load sasl.app file, otherwise application:get_key will fail
+    application:load(sasl),
+    %% create *.rel - release file
+    RelFile = filename:join(Dir, "lambda.rel"),
+    Release = {release, {"lambda", "1.0.0"},
+        {erts, erlang:system_info(version)},
+        [{App, begin {ok, Vsn} = application:get_key(App, vsn), Vsn end}
+            || App &lt;- [kernel, stdlib, sasl]]},
+    ok = file:write_file(RelFile, list_to_binary(lists:flatten(
+        io_lib:format("~tp.", [Release])))),
+    RelFileNoExt = filename:join(Dir, "lambda"),
+
+    %% create boot script
+    {ok, systools_make, []} = systools:make_script(RelFileNoExt,
+        [silent, {outdir, Dir}]),
+    %% package release into *.tar.gz
+    ok = systools:make_tar(RelFileNoExt, [{erts, code:root_dir()}]).
+
+build_image(Dir) ->
+    %% Create Dockerfile example, working only for Ubuntu 20.04
+    %% Expose port 4445, and make Erlang distribution to listen
+    %%  on this port, and connect to it without EPMD
+    %% Set cookie on both nodes to be the same.
+    BuildScript = filename:join(Dir, "Dockerfile"),
+    Dockerfile =
+      "FROM ubuntu:20.04 as runner\n"
+      "EXPOSE 4445\n"
+      "WORKDIR /opt/lambda\n"
+      "COPY lambda.tar.gz /tmp\n"
+      "RUN tar -zxvf /tmp/lambda.tar.gz -C /opt/lambda\n"
+      "ENTRYPOINT [\"/opt/lambda/erts-" ++ erlang:system_info(version) ++
+      "/bin/dyn_erl\", \"-boot\", \"/opt/lambda/releases/1.0.0/start\","
+      " \"-kernel\", \"inet_dist_listen_min\", \"4445\","
+      " \"-erl_epmd_port\", \"4445\","
+      " \"-setcookie\", \"secret\"]\n",
+    ok = file:write_file(BuildScript, Dockerfile),
+    os:cmd("docker build -t lambda " ++ Dir).
     </code>
   </section>
 
@@ -270,13 +270,6 @@
               is, <c>peer</c> follows compatibility behaviour and uses the origin node name.
             </p>
           </item>
-          <tag><c>host</c></tag>
-          <item>
-            <p>
-              Enforces a specific host name. Can be used to override the default
-              behaviour and start "node@localhost" instead of "node@realhostname".
-            </p>
-          </item>
           <tag><c>longnames</c></tag>
           <item>
             <p>
@@ -285,6 +278,13 @@
               short names is the default.
             </p>
           </item>
+          <tag><c>host</c></tag>
+          <item>
+            <p>
+              Enforces a specific host name. Can be used to override the default
+              behaviour and start "node@localhost" instead of "node@realhostname".
+            </p>
+          </item>
           <tag><c>peer_down</c></tag>
           <item>
             <p>
@@ -296,6 +296,11 @@
               the controlling process to exit abnormally.
             </p>
           </item>
+          <tag><c>connection</c></tag>
+          <item>
+            <p>Alternative connection specification. See the
+              <seetype marker="#connection"><c>connection</c> datatype</seetype>.</p>
+          </item>
           <tag><c>exec</c></tag>
           <item>
             <p>
@@ -303,11 +308,6 @@
               default bash.
             </p>
           </item>
-          <tag><c>connection</c></tag>
-          <item>
-            <p>Alternative connection specification. See the
-              <seetype marker="#connection"><c>connection</c> datatype</seetype>.</p>
-          </item>
           <tag><c>args</c></tag>
           <item>
             <p>Extra command line arguments to append to the "erl" command. Arguments are
diff --git a/lib/stdlib/src/peer.erl b/lib/stdlib/src/peer.erl
index e3b6619f25..dcb6eeeb65 100644
--- a/lib/stdlib/src/peer.erl
+++ b/lib/stdlib/src/peer.erl
@@ -113,8 +113,8 @@
           %%  saving exit reason in the state
           %% crash: when peer terminates, origin process
           %%  terminates with underlying reason
-          exec => exec(),                     %% path to executable, or SSH/Docker support
           connection => connection(),         %% alternative connection specification
+          exec => exec(),                     %% path to executable, or SSH/Docker support
           args => [string()],                 %% additional command line parameters to append
           env => [{string(), string()}],      %% additional environment variables
           wait_boot => wait_boot(),           %% default is synchronous start with 15 sec timeout
-- 
2.35.3

openSUSE Build Service is sponsored by