File 2911-Add-functions-to-connect-to-a-port-to-the-erl_interf.patch of Package erlang
From 14109f1e4eb3472d3d1b63572fe23b29fcf23d1a Mon Sep 17 00:00:00 2001
From: Kjell Winblad <kjellwinblad@gmail.com>
Date: Thu, 19 Dec 2019 15:41:27 +0100
Subject: [PATCH 1/2] Add functions to connect to a port to the erl_interface
API
This commit adds a family of functions to the erl_interface API that
make it possible to connect to a node without asking an EPMD instance
for a port. The new functions are useful in environments where EPMD is
not available.
---
lib/erl_interface/doc/src/ei_connect.xml | 25 ++-
lib/erl_interface/include/ei.h | 4 +
lib/erl_interface/src/connect/ei_connect.c | 210 ++++++++++++++-------
lib/erl_interface/test/ei_connect_SUITE.erl | 32 +++-
.../test/ei_connect_SUITE_data/ei_connect_test.c | 21 +++
5 files changed, 213 insertions(+), 79 deletions(-)
diff --git a/lib/erl_interface/doc/src/ei_connect.xml b/lib/erl_interface/doc/src/ei_connect.xml
index 795f1249b3..06fe9d1960 100644
--- a/lib/erl_interface/doc/src/ei_connect.xml
+++ b/lib/erl_interface/doc/src/ei_connect.xml
@@ -422,6 +422,8 @@ typedef struct {
<func>
<name since=""><ret>int</ret><nametext>ei_connect(ei_cnode* ec, char *nodename)</nametext></name>
<name since=""><ret>int</ret><nametext>ei_xconnect(ei_cnode* ec, Erl_IpAddr adr, char *alivename)</nametext></name>
+ <name since="OTP 23.0"><ret>int</ret><nametext>ei_connect_host_port(ei_cnode* ec, char *hostname, int port)</nametext></name>
+ <name since="OTP 23.0"><ret>int</ret><nametext>ei_xconnect_host_port(ei_cnode* ec, Erl_IpAddr adr, int port)</nametext></name>
<fsummary>Establish a connection to an Erlang node.</fsummary>
<desc>
<p>Sets up a connection to an Erlang node.</p>
@@ -429,13 +431,21 @@ typedef struct {
remote host and the alive name of the remote node to be
specified. <c>ei_connect()</c> provides an alternative
interface and determines the information from the node name
- provided.</p>
+ provided. The <c>ei_xconnect_host_port()</c> function provides
+ yet another alternative that will work even if there is no
+ EPMD instance on the host where the remote node is running. The
+ <c>ei_xconnect_host_port()</c> function requires the IP
+ address and port of the remote node to be specified.
+ The <c>ei_connect_host_port()</c> function is an alternative
+ to <c>ei_xconnect_host_port()</c> that lets the user specify
+ a hostname instead of an IP address.</p>
<list type="bulleted">
- <item><c>addr</c> is the 32-bit IP address of the remote
+ <item><c>adr</c> is the 32-bit IP address of the remote
host.</item>
<item><c>alive</c> is the alivename of the remote node.
</item>
<item><c>node</c> is the name of the remote node.</item>
+ <item><c>port</c> is the port number of the remote node.</item>
</list>
<p>These functions return an open file descriptor on success, or
a negative value indicating that an error occurred. In the latter
@@ -571,13 +581,16 @@ if (ei_connect_init(&ec, "madonna", "cookie...", n++) < 0) {
<func>
<name since=""><ret>int</ret><nametext>ei_connect_tmo(ei_cnode* ec, char *nodename, unsigned timeout_ms)</nametext></name>
<name since=""><ret>int</ret><nametext>ei_xconnect_tmo(ei_cnode* ec, Erl_IpAddr adr, char *alivename, unsigned timeout_ms)</nametext></name>
+ <name since="OTP 23.0"><ret>int</ret><nametext>ei_connect_host_port_tmo(ei_cnode* ec, char *hostname, int port, unsigned ms)</nametext></name>
+ <name since="OTP 23.0"><ret>int</ret><nametext>ei_xconnect_host_port_tmo(ei_cnode* ec, Erl_IpAddr adr, int port, unsigned ms)</nametext></name>
<fsummary>Establish a connection to an Erlang node with optional
time-out.</fsummary>
<desc>
- <p>Equivalent to
- <c>ei_connect</c> and <c>ei_xconnect</c> with an optional time-out
- argument, see the description at the beginning of this manual
- page.</p>
+ <p>Equivalent to <c>ei_connect</c>, <c>ei_xconnect</c>,
+ <c>ei_connect_host_port</c> and
+ <c>ei_xconnect_host_port</c> with an optional time-out
+ argument, see the description at the beginning of this manual
+ page.</p>
</desc>
</func>
diff --git a/lib/erl_interface/include/ei.h b/lib/erl_interface/include/ei.h
index 7d39043bb2..93c6b3dfa7 100644
--- a/lib/erl_interface/include/ei.h
+++ b/lib/erl_interface/include/ei.h
@@ -404,8 +404,12 @@ int ei_connect_xinit_ussi(ei_cnode* ec, const char *thishostname,
int ei_connect(ei_cnode* ec, char *nodename);
int ei_connect_tmo(ei_cnode* ec, char *nodename, unsigned ms);
+int ei_connect_host_port(ei_cnode* ec, char *hostname, int port);
+int ei_connect_host_port_tmo(ei_cnode* ec, char *hostname, int port, unsigned ms);
int ei_xconnect(ei_cnode* ec, Erl_IpAddr adr, char *alivename);
int ei_xconnect_tmo(ei_cnode* ec, Erl_IpAddr adr, char *alivename, unsigned ms);
+int ei_xconnect_host_port(ei_cnode* ec, Erl_IpAddr adr, int port);
+int ei_xconnect_host_port_tmo(ei_cnode* ec, Erl_IpAddr adr, int port, unsigned ms);
int ei_receive(int fd, unsigned char *bufp, int bufsize);
int ei_receive_tmo(int fd, unsigned char *bufp, int bufsize, unsigned ms);
diff --git a/lib/erl_interface/src/connect/ei_connect.c b/lib/erl_interface/src/connect/ei_connect.c
index f84c89f304..aab3043b9f 100644
--- a/lib/erl_interface/src/connect/ei_connect.c
+++ b/lib/erl_interface/src/connect/ei_connect.c
@@ -145,6 +145,12 @@ static int send_name(ei_socket_callbacks *cbs, void *ctx, int pkt_sz,
static int recv_name(ei_socket_callbacks *cbs, void *ctx, int pkt_sz,
unsigned *version, unsigned *flags, char *namebuf,
unsigned ms);
+static int ei_connect_helper(ei_cnode* ec,
+ Erl_IpAddr ip_addr,
+ char *alivename,
+ unsigned ms,
+ int rport,
+ int dist);
static struct hostent*
dyn_gethostbyname_r(const char *name, struct hostent *hostp, char **buffer_p,
@@ -874,78 +880,57 @@ struct hostent *dyn_gethostbyname_r(const char *name,
#endif
}
- /*
- * Set up a connection to a given Node, and
- * interchange hand shake messages with it.
- * Returns a valid file descriptor at success,
- * otherwise a negative error code.
-*/
-int ei_connect_tmo(ei_cnode* ec, char *nodename, unsigned ms)
+/* Finds the the IP address for hostname and saves that IP address at
+ the location that ip_wb points to. Returns a negative error code if
+ the IP address cannot be found for the hostname. */
+static int ip_address_from_hostname(char* hostname,
+ char** buffer_p,
+ size_t buffer_size,
+ Erl_IpAddr* ip_wb)
{
- char *hostname, alivename[BUFSIZ];
struct hostent *hp;
-#if !defined (__WIN32__)
+#ifndef __WIN32__
/* these are needed for the call to gethostbyname_r */
struct hostent host;
- char buffer[1024];
- char *buf = buffer;
int ei_h_errno;
-#endif /* !win32 */
- int res;
-
- if (strlen(nodename) > MAXNODELEN) {
- EI_TRACE_ERR0("ei_connect","Too long nodename");
- return ERL_ERROR;
- }
-
- /* extract the host and alive parts from nodename */
- if (!(hostname = strchr(nodename,'@'))) {
- EI_TRACE_ERR0("ei_connect","Node name has no @ in name");
- return ERL_ERROR;
- } else {
- strncpy(alivename, nodename, hostname - nodename);
- alivename[hostname - nodename] = 0x0;
- hostname++;
- }
-
-#ifndef __WIN32__
- hp = dyn_gethostbyname_r(hostname,&host,&buf,sizeof(buffer),&ei_h_errno);
+ hp = dyn_gethostbyname_r(hostname,&host,buffer_p,buffer_size,&ei_h_errno);
if (hp == NULL) {
char thishostname[EI_MAXHOSTNAMELEN+1];
/* gethostname requires len to be max(hostname) + 1*/
if (gethostname(thishostname,EI_MAXHOSTNAMELEN+1) < 0) {
- EI_TRACE_ERR0("ei_connect_tmo",
+ EI_TRACE_ERR0("ip_address_from_hostname",
"Failed to get name of this host");
erl_errno = EHOSTUNREACH;
return ERL_ERROR;
} else {
char *ct;
- /* We use a short node name */
+ /* We use a short node name */
if ((ct = strchr(thishostname, '.')) != NULL) *ct = '\0';
}
if (strcmp(hostname,thishostname) == 0)
/* Both nodes on same standalone host, use loopback */
- hp = dyn_gethostbyname_r("localhost",&host,&buf,sizeof(buffer),&ei_h_errno);
+ hp = dyn_gethostbyname_r("localhost",&host,buffer_p,buffer_size,&ei_h_errno);
if (hp == NULL) {
EI_TRACE_ERR2("ei_connect",
- "Can't find host for %s: %d\n",nodename,ei_h_errno);
+ "Can't find host for %s: %d\n",hostname,ei_h_errno);
erl_errno = EHOSTUNREACH;
return ERL_ERROR;
}
}
+ *ip_wb = (Erl_IpAddr) *hp->h_addr_list;
#else /* __WIN32__ */
if ((hp = ei_gethostbyname(hostname)) == NULL) {
char thishostname[EI_MAXHOSTNAMELEN+1];
/* gethostname requires len to be max(hostname) + 1 */
if (gethostname(thishostname,EI_MAXHOSTNAMELEN+1) < 0) {
- EI_TRACE_ERR1("ei_connect_tmo",
- "Failed to get name of this host: %d",
+ EI_TRACE_ERR1("ip_address_from_hostname",
+ "Failed to get name of this host: %d",
WSAGetLastError());
erl_errno = EHOSTUNREACH;
return ERL_ERROR;
} else {
char *ct;
- /* We use a short node name */
+ /* We use a short node name */
if ((ct = strchr(thishostname, '.')) != NULL) *ct = '\0';
}
if (strcmp(hostname,thishostname) == 0)
@@ -955,41 +940,27 @@ int ei_connect_tmo(ei_cnode* ec, char *nodename, unsigned ms)
char reason[1024];
win32_error(reason,sizeof(reason));
EI_TRACE_ERR2("ei_connect",
- "Can't find host for %s: %s",nodename,reason);
+ "Can't find host for %s: %s",hostname,reason);
erl_errno = EHOSTUNREACH;
return ERL_ERROR;
}
}
+ *ip_wb = (Erl_IpAddr) *hp->h_addr_list;
#endif /* win32 */
-
- res = ei_xconnect_tmo(ec, (Erl_IpAddr) *hp->h_addr_list, alivename, ms);
-
-#ifndef __WIN32__
- if (buf != buffer)
- free(buf);
-#endif
- return res;
-} /* ei_connect */
-
-int ei_connect(ei_cnode* ec, char *nodename)
-{
- return ei_connect_tmo(ec, nodename, 0);
+ return 0;
}
-
- /* ip_addr is now in network byte order
- *
- * first we have to get hold of the portnumber to
- * the node through epmd at that host
- *
-*/
-int ei_xconnect_tmo(ei_cnode* ec, Erl_IpAddr ip_addr, char *alivename, unsigned ms)
+/* Helper function for ei_connect family of functions */
+static int ei_connect_helper(ei_cnode* ec,
+ Erl_IpAddr ip_addr, /* network byte order */
+ char *alivename,
+ unsigned ms,
+ int rport,
+ int dist)
{
ei_socket_callbacks *cbs = ec->cbs;
void *ctx;
- int rport = 0; /*uint16 rport = 0;*/
int sockd;
- int dist = 0;
unsigned her_flags, her_version;
unsigned our_challenge, her_challenge;
unsigned char our_digest[16];
@@ -999,14 +970,13 @@ int ei_xconnect_tmo(ei_cnode* ec, Erl_IpAddr ip_addr, char *alivename, unsigned
unsigned tmo = ms == 0 ? EI_SCLBK_INF_TMO : ms;
erl_errno = EIO; /* Default error code */
-
- EI_TRACE_CONN1("ei_xconnect","-> CONNECT attempt to connect to %s",
- alivename);
-
- if ((rport = ei_epmd_port_tmo(ip_addr,alivename,&dist, tmo)) < 0) {
- EI_TRACE_ERR0("ei_xconnect","-> CONNECT can't get remote port");
- /* ei_epmd_port_tmo() has set erl_errno */
- return ERL_NO_PORT;
+
+ if (alivename != NULL) {
+ EI_TRACE_CONN1("ei_xconnect","-> CONNECT attempt to connect to %s",
+ alivename);
+ } else {
+ EI_TRACE_CONN1("ei_xconnect","-> CONNECT attempt to connect to port %d",
+ rport);
}
if (dist <= 4) {
@@ -1077,8 +1047,12 @@ int ei_xconnect_tmo(ei_cnode* ec, Erl_IpAddr ip_addr, char *alivename, unsigned
return ERL_ERROR;
}
}
-
- EI_TRACE_CONN1("ei_xconnect","-> CONNECT (ok) remote = %s",alivename);
+
+ if (alivename != NULL) {
+ EI_TRACE_CONN1("ei_xconnect","-> CONNECT (ok) remote = %s",alivename);
+ } else {
+ EI_TRACE_CONN1("ei_xconnect","-> CONNECT (ok) remote port = %d",rport);
+ }
erl_errno = 0;
return sockd;
@@ -1089,11 +1063,103 @@ error:
return ERL_ERROR;
} /* ei_xconnect */
+ /*
+ * Set up a connection to a given Node, and
+ * interchange hand shake messages with it.
+ * Returns a valid file descriptor at success,
+ * otherwise a negative error code.
+*/
+int ei_connect_tmo(ei_cnode* ec, char *nodename, unsigned ms)
+{
+ char *hostname, alivename[BUFSIZ];
+ Erl_IpAddr ip;
+ int res;
+ char buffer[1024];
+ char* buf = buffer;
+
+ if (strlen(nodename) > MAXNODELEN) {
+ EI_TRACE_ERR0("ei_connect","Too long nodename");
+ return ERL_ERROR;
+ }
+
+ /* extract the host and alive parts from nodename */
+ if (!(hostname = strchr(nodename,'@'))) {
+ EI_TRACE_ERR0("ei_connect","Node name has no @ in name");
+ return ERL_ERROR;
+ } else {
+ strncpy(alivename, nodename, hostname - nodename);
+ alivename[hostname - nodename] = 0x0;
+ hostname++;
+ }
+
+ res = ip_address_from_hostname(hostname, &buf, sizeof(buffer), &ip);
+
+ if (res < 0) {
+ return res;
+ }
+
+ res = ei_xconnect_tmo(ec, ip, alivename, ms);
+
+ if(buf != buffer) {
+ free(buf);
+ }
+
+ return res;
+} /* ei_connect */
+
+int ei_connect(ei_cnode* ec, char *nodename)
+{
+ return ei_connect_tmo(ec, nodename, 0);
+}
+
+int ei_connect_host_port_tmo(ei_cnode* ec, char *host, int port, unsigned ms)
+{
+ Erl_IpAddr ip;
+ char buffer[1024];
+ char* buf = buffer;
+ int res = ip_address_from_hostname(host, &buf, sizeof(buffer), &ip);
+ if (res < 0) {
+ return res;
+ }
+ if(buf != buffer) {
+ free(buf);
+ }
+ return ei_xconnect_host_port_tmo(ec, ip, port, ms);
+}
+
+int ei_connect_host_port(ei_cnode* ec, char *host, int port)
+{
+ return ei_connect_host_port_tmo(ec, host, port, 0);
+}
+
+int ei_xconnect_tmo(ei_cnode* ec, Erl_IpAddr ip_addr, char *alivename, unsigned ms)
+{
+ int dist = 0;
+ int port;
+ unsigned tmo = ms == 0 ? EI_SCLBK_INF_TMO : ms;
+ if ((port = ei_epmd_port_tmo(ip_addr,alivename,&dist, tmo)) < 0) {
+ EI_TRACE_ERR0("ei_xconnect","-> CONNECT can't get remote port");
+ /* ei_epmd_port_tmo() has set erl_errno */
+ return ERL_NO_PORT;
+ }
+ return ei_connect_helper(ec, ip_addr, alivename, ms, port, dist);
+}
+
int ei_xconnect(ei_cnode* ec, Erl_IpAddr ip_addr, char *alivename)
{
return ei_xconnect_tmo(ec, ip_addr, alivename, 0);
}
+int ei_xconnect_host_port_tmo(ei_cnode* ec, Erl_IpAddr ip_addr, int port, unsigned ms)
+{
+ return ei_connect_helper(ec, ip_addr, NULL, ms, port, 5);
+}
+
+int ei_xconnect_host_port(ei_cnode* ec, Erl_IpAddr ip_addr, int port)
+{
+ return ei_xconnect_host_port_tmo(ec, ip_addr, port, 0);
+}
+
int ei_listen(ei_cnode *ec, int *port, int backlog)
{
struct in_addr ip_addr;
diff --git a/lib/erl_interface/test/ei_connect_SUITE.erl b/lib/erl_interface/test/ei_connect_SUITE.erl
index 95a995a171..2ec1237e8e 100644
--- a/lib/erl_interface/test/ei_connect_SUITE.erl
+++ b/lib/erl_interface/test/ei_connect_SUITE.erl
@@ -34,7 +34,8 @@
rpc_test/1,
ei_send_funs/1,
ei_threaded_send/1,
- ei_set_get_tracelevel/1]).
+ ei_set_get_tracelevel/1,
+ ei_connect_host_port_test/1]).
-import(runner, [get_term/1,send_term/2]).
@@ -44,6 +45,7 @@ suite() ->
all() ->
[ei_send, ei_reg_send, ei_reg_send_large, ei_rpc, ei_format_pid, ei_send_funs,
+ ei_connect_host_port_test,
ei_threaded_send, ei_set_get_tracelevel].
init_per_testcase(Case, Config) ->
runner:init_per_testcase(?MODULE, Case, Config).
@@ -185,6 +187,27 @@ ei_set_get_tracelevel(Config) when is_list(Config) ->
ok.
+ei_connect_host_port_test(Config) when is_list(Config) ->
+ P = runner:start(Config, ?interpret),
+ 0 = ei_connect_init(P, 42, erlang:get_cookie(), 0, default),
+ [NodeName, Hostname] = string:lexemes(atom_to_list(node()), "@"),
+ {ok, NamePortList} = net_adm:names(),
+ {value, {_, Port}}
+ = lists:search(fun({N, _}) ->
+ string:equal(N, NodeName)
+ end,
+ NamePortList),
+ {ok,Fd} = ei_connect_host_port(P,
+ erlang:list_to_atom(Hostname),
+ Port),
+ ok = ei_send(P, Fd, self(), AMsg={a,message}),
+ receive AMsg -> ok end,
+
+ runner:send_eot(P),
+ runner:recv_eot(P),
+ ok.
+
+
%%% Interface functions for ei (erl_interface) functions.
ei_connect_init(P, Num, Cookie, Creation) ->
@@ -200,6 +223,13 @@ ei_connect(P, Node) ->
{term,{-1,Errno}} -> {error,Errno}
end.
+ei_connect_host_port(P, Hostname, Port) ->
+ send_command(P, ei_connect_host_port, [Hostname, Port]),
+ case get_term(P) of
+ {term,{Fd,_}} when Fd >= 0 -> {ok,Fd};
+ {term,{-1,Errno}} -> {error,Errno}
+ end.
+
ei_set_get_tracelevel(P, Tracelevel) ->
send_command(P, ei_set_get_tracelevel, [Tracelevel]),
case get_term(P) of
diff --git a/lib/erl_interface/test/ei_connect_SUITE_data/ei_connect_test.c b/lib/erl_interface/test/ei_connect_SUITE_data/ei_connect_test.c
index e15ebe99cb..293aa40ec7 100644
--- a/lib/erl_interface/test/ei_connect_SUITE_data/ei_connect_test.c
+++ b/lib/erl_interface/test/ei_connect_SUITE_data/ei_connect_test.c
@@ -35,6 +35,7 @@
static void cmd_ei_connect_init(char* buf, int len);
static void cmd_ei_connect(char* buf, int len);
+static void cmd_ei_connect_host_port(char* buf, int len);
static void cmd_ei_send(char* buf, int len);
static void cmd_ei_format_pid(char* buf, int len);
static void cmd_ei_send_funs(char* buf, int len);
@@ -54,6 +55,7 @@ static struct {
} commands[] = {
"ei_connect_init", 3, cmd_ei_connect_init,
"ei_connect", 1, cmd_ei_connect,
+ "ei_connect_host_port", 2, cmd_ei_connect_host_port,
"ei_send", 3, cmd_ei_send,
"ei_send_funs", 3, cmd_ei_send_funs,
"ei_reg_send", 3, cmd_ei_reg_send,
@@ -144,6 +146,25 @@ static void cmd_ei_connect(char* buf, int len)
send_errno_result(i);
}
+static void cmd_ei_connect_host_port(char* buf, int len)
+{
+ int index = 0;
+ char hostname[256];
+ int i;
+ long port;
+ if (ei_decode_atom(buf, &index, hostname) < 0)
+ fail("expected atom");
+ if (ei_decode_long(buf, &index, &port) < 0)
+ fail("expected int");
+ i = ei_connect_host_port(&ec, hostname, (int)port);
+#ifdef VXWORKS
+ if(i >= 0) {
+ save_fd(i);
+ }
+#endif
+ send_errno_result(i);
+}
+
static void cmd_ei_set_get_tracelevel(char* buf, int len)
{
int index = 0;
--
2.16.4