File 2912-Extend-erl_call-with-a-new-flag-to-access-a-node-at-.patch of Package erlang

From ce4fcf0640d81a268c15af339a888406b757ced5 Mon Sep 17 00:00:00 2001
From: Kjell Winblad <kjellwinblad@gmail.com>
Date: Thu, 19 Dec 2019 15:54:51 +0100
Subject: [PATCH 2/2] Extend erl_call with a new flag to access a node at
 HOSTNAME:PORT

This commit adds the flag -address to the erl_call program. This flag
makes it possible for the user to use erl_call to interact with a node
even if no EPMD instance is running on the node's host.
---
 lib/erl_interface/doc/src/erl_call.xml    |  25 ++++++-
 lib/erl_interface/src/prog/erl_call.c     | 108 +++++++++++++++++++++++-------
 lib/erl_interface/test/erl_call_SUITE.erl |  97 +++++++++++++++++++++------
 3 files changed, 183 insertions(+), 47 deletions(-)

diff --git a/lib/erl_interface/doc/src/erl_call.xml b/lib/erl_interface/doc/src/erl_call.xml
index 73b9b13e4d..2ab5948db6 100644
--- a/lib/erl_interface/doc/src/erl_call.xml
+++ b/lib/erl_interface/doc/src/erl_call.xml
@@ -78,6 +78,22 @@
               <c>Fun</c>, and <c>Args</c> in a manner
               dependent on the behavior of your command shell.</p>
           </item>
+          <tag><c>-address [Hostname:]Port</c></tag>
+          <item>
+            <p>(One of <c>-n</c>, <c>-name</c>, <c>-sname</c> or
+            <c>-address</c> is required.) <c>Hostname</c> is the
+            hostname of the machine that is running the node that
+            <c>erl_call</c> shall communicate with. The default
+            hostname is the hostname of the local machine. <c>Port</c>
+            is the port number of the node that <c>erl_call</c> shall
+            communicate with. The <c>-address</c> flag cannot be
+            combined with any of the flags <c>-n</c>, <c>-name</c>,
+            <c>-sname</c> or <c>-s</c>.</p>
+            <p>The <c>-address</c> flag is typically useful when one
+            wants to call a node that is running on machine without an
+            accessible <seealso marker="epmd">epmd</seealso>
+            instance.</p>
+          </item>
           <tag><c>-c Cookie</c></tag>
           <item>
             <p>(<em>Optional.</em>) Use this option to specify a certain cookie.
@@ -112,13 +128,15 @@
           </item>
           <tag><c>-n Node</c></tag>
           <item>
-            <p>(One of <c>-n, -name, -sname</c> is required.)
+            <p>(One of <c>-n</c>, <c>-name</c>, <c>-sname</c> or
+            <c>-address</c> is required.)
               Has the same meaning as <c>-name</c> and can still be
               used for backward compatibility reasons.</p>
           </item>
           <tag><c>-name Node</c></tag>
           <item>
-            <p>(One of <c>-n, -name, -sname</c> is required.)
+            <p>(One of <c>-n</c>, <c>-name</c>, <c>-sname</c> or
+            <c>-address</c> is required.)
               <c>Node</c> is the name of the node to be
               started or communicated with. It is assumed that
               <c>Node</c> is started with
@@ -149,7 +167,8 @@
           </item>
           <tag><c>-sname Node</c></tag>
           <item>
-            <p>(One of <c>-n, -name, -sname</c> is required.)
+            <p>(One of <c>-n</c>, <c>-name</c>, <c>-sname</c> or
+            <c>-address</c> is required.)
               <c>Node</c> is the name of the node to be started
               or communicated with. It is assumed that <c>Node</c>
               is started with <c>erl -sname</c>, which means that
diff --git a/lib/erl_interface/src/prog/erl_call.c b/lib/erl_interface/src/prog/erl_call.c
index dce2ecdec2..dd714cc41c 100644
--- a/lib/erl_interface/src/prog/erl_call.c
+++ b/lib/erl_interface/src/prog/erl_call.c
@@ -104,6 +104,8 @@ struct call_flags {
     int debugp;
     int verbosep;
     int haltp;
+    long port;
+    char *hostname;
     char *cookie;
     char *node;
     char *hidden;
@@ -152,6 +154,8 @@ int erl_call(int argc, char **argv)
     struct call_flags flags = {0}; /* Default 0 and NULL in all fields */
     char* progname = argv[0];
     ei_cnode ec;
+    flags.port = -1;
+    flags.hostname = NULL;
 
     ei_init();
 
@@ -177,6 +181,29 @@ int erl_call(int argc, char **argv)
 	    flags.node = ei_chk_strdup(argv[i+1]);
 	    i++;
 	    flags.use_long_name = 1;
+	} else if (strcmp(argv[i], "-address") == 0) {  /* -address [HOST:]PORT */
+	    if (i+1 >= argc) {
+		usage_arg(progname, "-address ");
+	    }
+            {
+                char* hostname_port_arg = ei_chk_strdup(argv[i+1]);
+                char* address_string_end = strchr(hostname_port_arg, ':');
+                if (address_string_end == NULL) {
+                    flags.port = strtol(hostname_port_arg, NULL, 10);
+                } else {
+                    flags.port = strtol(address_string_end + 1, NULL, 10);
+                    /* Remove port part from hostname_port_arg*/
+                    *address_string_end = '\0';
+                    if (strlen(hostname_port_arg) > 0) {
+                        flags.hostname = hostname_port_arg;
+                    }
+                }
+
+                if (flags.port < 1 || flags.port > 65535) {
+                    usage_error(progname, "-address");
+                }
+                i++;
+            }
 	} else {
 	    if (strlen(argv[i]) != 2) {
 		usage_error(progname, argv[i]);
@@ -251,11 +278,12 @@ int erl_call(int argc, char **argv)
 
     } /* while */
 
-	
     /*
      * Can't have them both !
      */
-    if (flags.modp && flags.evalp) {
+    if ((flags.modp && flags.evalp) ||
+        (flags.port != -1 && flags.startp) ||
+        (flags.port != -1 && flags.node)) {
       usage(progname);
     }
 
@@ -284,7 +312,7 @@ int erl_call(int argc, char **argv)
     /* 
      * What we, at least, requires !
      */
-    if (flags.node == NULL) {
+    if (flags.node == NULL && flags.port == -1) {
 	usage(progname);
     }
 
@@ -345,10 +373,15 @@ int erl_call(int argc, char **argv)
       }
 
     }
-    if ((p = strchr((const char *)flags.node, (int) '@')) == 0) {
+    if (flags.port != -1 && flags.hostname != NULL) {
+        host = flags.hostname;
+        strcpy(host_name, flags.hostname);
+    } else if ((flags.port != -1 && flags.hostname == NULL) ||
+        (strchr((const char *)flags.node, (int) '@') == 0)) {
 	strcpy(host_name, ei_thishostname(&ec));
 	host = host_name;
     } else {
+        p = strchr((const char *)flags.node, (int) '@');
 	*p = 0;
 	host = p+1;
     }
@@ -367,28 +400,45 @@ int erl_call(int argc, char **argv)
     }
     strncpy(host_name, hp->h_name, EI_MAXHOSTNAMELEN);
     host_name[EI_MAXHOSTNAMELEN] = '\0';
-    if (strlen(flags.node) + strlen(host_name) + 2 > sizeof(nodename)) {
-	fprintf(stderr,"erl_call: nodename too long: %s\n", flags.node);
-	exit(1);
+    if (flags.port == -1) {
+        if (strlen(flags.node) + strlen(host_name) + 2 > sizeof(nodename)) {
+            fprintf(stderr,"erl_call: nodename too long: %s\n", flags.node);
+            exit(1);
+        }
+        sprintf(nodename, "%s@%s", flags.node, host_name);
     }
-    sprintf(nodename, "%s@%s", flags.node, host_name);
-
     /* 
      * Try to connect. Start an Erlang system if the
      * start option is on and no system is running.
      */
     if (flags.startp && !flags.haltp) {
 	fd = do_connect(&ec, nodename, &flags);
-    } else if ((fd = ei_connect(&ec, nodename)) < 0) {
-	/* We failed to connect ourself */
-	/* FIXME do we really know we failed because of node not up? */
-	if (flags.haltp) {
-	    exit(0);
-	} else {
-	    fprintf(stderr,"erl_call: failed to connect to node %s\n",
-		    nodename);
-	    exit(1);
-	}
+    } else if (flags.port == -1) {
+        if ((fd = ei_connect(&ec, nodename)) < 0) {
+            /* We failed to connect ourself */
+            /* FIXME do we really know we failed because of node not up? */
+            if (flags.haltp) {
+                exit(0);
+            } else {
+                fprintf(stderr,"erl_call: failed to connect to node %s\n",
+                        nodename);
+                exit(1);
+            }
+        }
+    } else {
+        /* Connect using address:port */
+        if ((fd = ei_connect_host_port(&ec, host, (int)flags.port)) < 0) {
+            /* We failed to connect ourself */
+            /* FIXME do we really know we failed because of node not up? */
+            if (flags.haltp) {
+                exit(0);
+            } else {
+                fprintf(stderr,"erl_call: failed to connect to node with address \"%s:%ld\"\n",
+                        flags.hostname == NULL ? "" : flags.hostname,
+                        flags.port);
+                exit(1);
+            }
+        }
     }
 
     /* If we are connected and the halt switch is set */
@@ -414,8 +464,14 @@ int erl_call(int argc, char **argv)
     }
 
     if (flags.verbosep) {
-	fprintf(stderr,"erl_call: we are now connected to node \"%s\"\n",
-		nodename);
+        if (flags.port == -1) {
+            fprintf(stderr,"erl_call: we are now connected to node \"%s\"\n",
+                    nodename);
+        } else {
+            fprintf(stderr,"erl_call: we are now connected to node with address \"%s:%ld\"\n",
+                    flags.hostname == NULL ? "": flags.hostname,
+                    flags.port);
+        }
     }
 
     /*
@@ -808,7 +864,7 @@ static int get_module(char **mbuf, char **mname)
 static void usage_noexit(const char *progname) {
   fprintf(stderr,"\nUsage: %s [-[demqrsv]] [-c Cookie] [-h HiddenName] \n", progname);
   fprintf(stderr,"            [-x ErlScript] [-a [Mod [Fun [Args]]]]\n");
-  fprintf(stderr,"            (-n Node | -sname Node | -name Node)\n\n");
+  fprintf(stderr,"            (-n Node | -sname Node | -name Node | -address [HOSTNAME:]PORT)\n\n");
 #ifdef __WIN32__
   fprintf(stderr,"  where: -a  apply(Mod,Fun,Args) (e.g -a \"erlang length [[a,b,c]]\"\n");
 #else
@@ -816,12 +872,18 @@ static void usage_noexit(const char *progname) {
 #endif
   fprintf(stderr,"         -c  cookie string; by default read from ~/.erlang.cookie\n");
   fprintf(stderr,"         -d  direct Erlang output to ~/.erl_call.out.<Nodename>\n");
-  fprintf(stderr,"         -e  evaluate contents of standard input (e.g echo \"X=1,Y=2,{X,Y}.\"|erl_call -e ...)\n");
+  fprintf(stderr,"         -e  evaluate contents of standard input (e.g., echo \"X=1,Y=2,{X,Y}.\"|%s -e ...)\n",
+          progname);
   fprintf(stderr,"         -h  specify a name for the erl_call client node\n");
   fprintf(stderr,"         -m  read and compile Erlang module from stdin\n");
   fprintf(stderr,"         -n  name of Erlang node, same as -name\n");
   fprintf(stderr,"         -name  name of Erlang node, expanded to a fully qualified\n");
   fprintf(stderr,"         -sname name of Erlang node, short form will be used\n");
+  fprintf(stderr,"         -address [HOSTNAME:]PORT of Erlang node\n"
+          "                  (the default hostname is the hostname of the local manchine)\n"
+          "                  (e.g., %s -address my_host:36303 ...)\n"
+          "                  (cannot be combinated with -s, -n, -name and -sname)\n",
+          progname);
   fprintf(stderr,"         -q  halt the Erlang node (overrides the -s switch)\n");
   fprintf(stderr,"         -r  use a random name for the erl_call client node\n");
   fprintf(stderr,"         -s  start a new Erlang node if necessary\n");
diff --git a/lib/erl_interface/test/erl_call_SUITE.erl b/lib/erl_interface/test/erl_call_SUITE.erl
index 9e2b2e4251..0d95a1361b 100644
--- a/lib/erl_interface/test/erl_call_SUITE.erl
+++ b/lib/erl_interface/test/erl_call_SUITE.erl
@@ -23,42 +23,88 @@
 
 -include_lib("common_test/include/ct.hrl").
 
--export([all/0, smoke/1]).
+-export([all/0, smoke/1, test_connect_to_host_port/1]).
 
-all() -> 
-    [smoke].
+all() ->
+    [smoke,
+     test_connect_to_host_port].
 
 smoke(Config) when is_list(Config) ->
-    ErlCall = find_erl_call(),
-    NameSwitch = case net_kernel:longnames() of
-                     true ->
-                         "-name";
-                     false ->
-                         "-sname"
-                 end,
     Name = atom_to_list(?MODULE)
         ++ "-"
         ++ integer_to_list(erlang:system_time(microsecond)),
 
-    ArgsList = ["-s", "-a", "erlang node", NameSwitch, Name],
-    io:format("erl_call: \"~ts\"\n~nargs list: ~p~n", [ErlCall, ArgsList]),
-    CmdRes = get_smoke_port_res(open_port({spawn_executable, ErlCall},
-                                          [{args, ArgsList}, eof]), []),
-    io:format("CmdRes: ~p~n", [CmdRes]),
+    RetNodeName = start_node_and_get_node_name(Name),
+
+    halt_node(Name),
 
     [_, Hostname] = string:lexemes(atom_to_list(node()), "@"),
     NodeName = list_to_atom(Name ++ "@" ++ Hostname),
-    io:format("NodeName: ~p~n~n", [NodeName]),
+    NodeName = list_to_atom(RetNodeName),
+    ok.
 
-    pong = net_adm:ping(NodeName),
-    rpc:cast(NodeName, erlang, halt, []),
-    NodeName = list_to_atom(string:trim(CmdRes, both, "'")),
+
+test_connect_to_host_port(Config) when is_list(Config) ->
+    Name = atom_to_list(?MODULE)
+        ++ "-"
+        ++ integer_to_list(erlang:system_time(microsecond)),
+    Port = start_node_and_get_port(Name),
+    AddressCaller =
+        fun(Address) ->
+                  get_erl_call_result(["-address",
+                                       Address,
+                                       "-a",
+                                       "erlang length [[1,2,3,4,5,6,7,8,9]]"])
+        end,
+    "9" = AddressCaller(erlang:integer_to_list(Port)),
+    "9" = AddressCaller(":" ++ erlang:integer_to_list(Port)),
+    [_, Hostname] = string:lexemes(atom_to_list(node()), "@"),
+    "9" = AddressCaller(Hostname ++ ":" ++ erlang:integer_to_list(Port)),
+    FailedRes = AddressCaller("80"),
+    case string:find(FailedRes, "80") of
+        nomatch -> ct:fail("Incorrect error message");
+        _ -> ok
+    end,
+    halt_node(Name),
     ok.
 
 %
 % Utility functions...
 %
 
+
+halt_node(Name) ->
+    [_, Hostname] = string:lexemes(atom_to_list(node()), "@"),
+    NodeName = list_to_atom(Name ++ "@" ++ Hostname),
+    io:format("NodeName: ~p~n~n", [NodeName]),
+
+    pong = net_adm:ping(NodeName),
+    rpc:cast(NodeName, erlang, halt, []).
+
+start_node_and_get_node_name(Name) ->
+    NameSwitch = case net_kernel:longnames() of
+                     true ->
+                         "-name";
+                     false ->
+                         "-sname"
+                 end,
+    string:trim(get_erl_call_result(["-s",
+                                     NameSwitch,
+                                     Name, "-a",
+                                     "erlang node"]),
+                both,
+                "'").
+
+start_node_and_get_port(Name) ->
+    start_node_and_get_node_name(Name),
+    {ok, NamePortList} = net_adm:names(),
+    {value, {_, Port}}
+        = lists:search(fun({N, _}) ->
+                               string:equal(N, Name)
+                       end,
+                       NamePortList),
+    Port.
+
 find_erl_call() ->
     ErlCallName = case os:type() of
                       {win32, _} -> "erl_call.exe";
@@ -86,10 +132,19 @@ find_erl_call() ->
             ErlCall
     end.
 
-get_smoke_port_res(Port, Acc) when is_port(Port) ->
+
+get_erl_call_result(ArgsList) ->
+    ErlCall = find_erl_call(),
+    io:format("erl_call: \"~ts\"\n~nargs list: ~p~n", [ErlCall, ArgsList]),
+    CmdRes = get_port_res(open_port({spawn_executable, ErlCall},
+                                    [{args, ArgsList}, eof, stderr_to_stdout]), []),
+    io:format("CmdRes: ~p~n", [CmdRes]),
+    CmdRes.
+
+get_port_res(Port, Acc) when is_port(Port) ->
     receive
         {Port, {data, Data}} ->
-            get_smoke_port_res(Port, [Acc|Data]);
+            get_port_res(Port, [Acc|Data]);
         {Port, eof} ->
             lists:flatten(Acc)
     end.
-- 
2.16.4

openSUSE Build Service is sponsored by