File 2531-Introduce-ei_make_ref-and-ei_make_pid.patch of Package erlang
From 337e253aeabe4259ad215b31f6b29a9cb519c415 Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Mon, 4 May 2020 11:21:02 +0200
Subject: [PATCH 1/2] Introduce ei_make_ref() and ei_make_pid()
---
 lib/erl_interface/doc/src/ei_connect.xml      |  41 +++
 lib/erl_interface/include/ei.h                |   3 +
 lib/erl_interface/src/connect/ei_connect.c    | 274 ++++++++++++++++++
 lib/erl_interface/test/ei_connect_SUITE.erl   | 110 ++++++-
 .../ei_connect_SUITE_data/ei_connect_test.c   |  78 +++++
 5 files changed, 504 insertions(+), 2 deletions(-)
diff --git a/lib/erl_interface/doc/src/ei_connect.xml b/lib/erl_interface/doc/src/ei_connect.xml
index f991165df7..767d8d7508 100644
--- a/lib/erl_interface/doc/src/ei_connect.xml
+++ b/lib/erl_interface/doc/src/ei_connect.xml
@@ -648,6 +648,47 @@ if (ei_connect_init(&ec, "madonna", "cookie...", n++) < 0) {
       </desc>
     </func>
 
+    <func>
+      <name since="OTP 23.0"><ret>int</ret><nametext>ei_make_pid(ei_cnode *ec, erlang_pid *pid)</nametext></name>
+      <fsummary>Create a new process identifier</fsummary>
+      <desc>
+	<p>
+	  Creates a new process identifier in the argument <c>pid</c>. This process identifier
+	  refers to a conseptual process residing on the C-node identified by the argument
+	  <c>ec</c>. On success <c>0</c> is returned. On failure <c>ERL_ERROR</c> is
+	  returned and <c>erl_errno</c> is set.
+	</p>
+	<p>
+	  The C-node identified by <c>ec</c> must have been initialized and must have
+	  received a name prior to the call to <c>ei_make_pid()</c>. Initialization
+	  of the C-node is done by a call to
+	  <seealso marker="#ei_connect_init"><c>ei_connect_init()</c></seealso>
+	  or friends. If the name is dynamically assigned from the peer node, the
+	  C-node also has to be connected.
+	</p>
+      </desc>
+    </func>
+    
+    <func>
+      <name since="OTP 23.0"><ret>int</ret><nametext>ei_make_ref(ei_cnode *ec, erlang_ref *ref)</nametext></name>
+      <fsummary>Create a new reference</fsummary>
+      <desc>
+	<p>
+	  Creates a new reference in the argument <c>ref</c>. This reference originates
+	  from the C-node identified by the argument <c>ec</c>. On success <c>0</c> is
+	  returned. On failure <c>ERL_ERROR</c> is returned and <c>erl_errno</c> is set.
+	</p>
+	<p>
+	  The C-node identified by <c>ec</c> must have been initialized and must have
+	  received a name prior to the call to <c>ei_make_ref()</c>. Initialization
+	  of the C-node is done by a call to
+	  <seealso marker="#ei_connect_init"><c>ei_connect_init()</c></seealso>
+	  or friends. If the name is dynamically assigned from the peer node, the
+	  C-node also has to be connected.
+	</p>
+      </desc>
+    </func>
+    
     <func>
       <name since=""><ret>int</ret><nametext>ei_publish(ei_cnode *ec, int port)</nametext></name>
       <fsummary>Publish a node name.</fsummary>
diff --git a/lib/erl_interface/include/ei.h b/lib/erl_interface/include/ei.h
index 6859c71c29..605caaa0e5 100644
--- a/lib/erl_interface/include/ei.h
+++ b/lib/erl_interface/include/ei.h
@@ -366,6 +366,7 @@ typedef struct ei_cnode_s {
     erlang_pid self;
     ei_socket_callbacks *cbs;
     void *setup_context;
+    unsigned int pidsn;
 } ei_cnode;
 
 typedef struct in_addr *Erl_IpAddr; 
@@ -446,6 +447,8 @@ const char *ei_thishostname(const ei_cnode* ec);
 const char *ei_thisalivename(const ei_cnode* ec);
 
 erlang_pid *ei_self(ei_cnode* ec);
+int ei_make_pid(ei_cnode *ec, erlang_pid *pid);
+int ei_make_ref(ei_cnode *ec, erlang_ref *ref);
 
 /* 
  * settings 
diff --git a/lib/erl_interface/src/connect/ei_connect.c b/lib/erl_interface/src/connect/ei_connect.c
index 40efdd101a..9a8c7b5cb9 100644
--- a/lib/erl_interface/src/connect/ei_connect.c
+++ b/lib/erl_interface/src/connect/ei_connect.c
@@ -525,11 +525,272 @@ const char *ei_thiscookie(const ei_cnode* ec)
     return (const char *)ec->ei_connect_cookie;
 }
 
+static int
+check_initialized_node(ei_cnode *ec)
+{
+    /*
+     * Try to guard against returning garbage pids and refs
+     * by verifying that the node has got its name...
+     */
+    int i, at, end;
+    char *nodename = &ec->thisnodename[0];
+
+    for (i = at = end = 0; i < sizeof(ec->thisnodename); i++) {
+        if (!nodename[i]) {
+            end = !0;
+            break;
+        }
+        if (nodename[i] == '@')
+            at = !0;
+    }
+
+    if (!at || !end) {
+        erl_errno = EINVAL;
+        return ERL_ERROR;
+    }
+
+    return 0;
+}
+
 erlang_pid *ei_self(ei_cnode* ec)
 {
+    int err = check_initialized_node(ec);
+    if (err)
+        return NULL;
     return &ec->self;
 }
 
+/*
+ * ei_make_pid()
+ */
+
+#undef EI_MAKE_PID_ATOMIC__
+#ifdef _REENTRANT
+#  if (SIZEOF_INT == 4                                  \
+       && (ETHR_HAVE___atomic_compare_exchange_n & 4)   \
+       && (ETHR_HAVE___atomic_load_n & 4))
+#    define EI_MAKE_PID_ATOMIC__
+#  else /* !EI_MAKE_PID_ATOMIC__ */
+static ei_mutex_t *pid_mtx = NULL;
+#  endif /* !EI_MAKE_PID_ATOMIC__ */
+#endif /* _REENTRANT */
+
+static int
+init_make_pid(int late)
+{
+#if defined(_REENTRANT) && !defined(EI_MAKE_PID_ATOMIC__)
+
+    if (late)
+        return ENOTSUP; /* Refuse doing unsafe initialization... */
+
+    pid_mtx = ei_mutex_create();
+    if (!pid_mtx)
+        return ENOMEM;
+    
+#endif /* _REENTRANT */
+
+    return 0;
+}
+
+int ei_make_pid(ei_cnode *ec, erlang_pid *pid)
+{
+    unsigned int new;
+    int err;
+    
+    if (!ei_connect_initialized) {
+	fprintf(stderr,"<ERROR> erl_interface not initialized\n");
+        exit(1);
+    }
+
+    err = check_initialized_node(ec);
+    if (err) {
+        /*
+         * write invalid utf8 in nodename which will make
+         * ei_encode_pid() fail if used...
+         */
+        pid->node[0] = 0xff;
+        pid->node[1] = 0;
+        pid->serial = -1;
+        pid->num = -1;
+        return err;
+    }
+    
+    strcpy(pid->node, ec->thisnodename);
+    pid->creation = ec->creation;
+
+    /*
+     * We avoid creating pids with serial set to 0 since the
+     * documentation previously gave some really bad advise
+     * of modifying the 'num' field in the pid returned by
+     * ei_self(). Since 'serial' field in pid returned by
+     * ei_self() is initialized to 0, pids created by
+     * ei_make_pid() wont clash with such badly created pids
+     * using ei_self() unless user also modified serial, but
+     * that has at least never been suggested by the
+     * documentation.
+     */
+
+#ifdef EI_MAKE_PID_ATOMIC__
+    {
+        unsigned int xchg = __atomic_load_n(&ec->pidsn, __ATOMIC_RELAXED);
+        do {
+            new = xchg + 1;
+            if ((new & 0x0fff8000) == 0)
+                new = 0x8000; /* serial==0 -> serial=1 num=0 */
+        } while(!__atomic_compare_exchange_n(&ec->pidsn, &xchg, new, 0,
+                                             __ATOMIC_ACQ_REL,
+                                             __ATOMIC_RELAXED));
+    }
+#else /* !EI_MAKE_PID_ATOMIC__ */
+
+#ifdef _REENTRANT
+    ei_mutex_lock(pid_mtx, 0);
+#endif
+
+    new = ec->pidsn + 1;
+    if ((new & 0x0fff8000) == 0)
+        new = 0x8000; /* serial==0 -> serial=1 num=0 */
+
+    ec->pidsn = new;
+    
+#ifdef _REENTRANT
+    ei_mutex_unlock(pid_mtx);
+#endif
+
+#endif /* !EI_MAKE_PID_ATOMIC__ */
+
+    pid->num = new & 0x7fff; /* 15-bits */
+    pid->serial = (new >> 15) & 0x1fff; /* 13-bits */
+    
+    return 0;
+}
+
+/*
+ * ei_make_ref()
+ */
+
+#undef EI_MAKE_REF_ATOMIC__
+#ifdef _REENTRANT
+#  if ((SIZEOF_LONG == 8 || SIZEOF_LONGLONG == 8)         \
+       && (ETHR_HAVE___atomic_compare_exchange_n & 8)     \
+       && (ETHR_HAVE___atomic_load_n & 8))
+#    define EI_MAKE_REF_ATOMIC__
+#    if SIZEOF_LONG == 8
+typedef unsigned long ei_atomic_ref__;
+#    else
+typedef unsigned long long ei_atomic_ref__;
+#    endif
+#  else /* !EI_MAKE_REF_ATOMIC__ */
+static ei_mutex_t *ref_mtx = NULL;
+#  endif /* !EI_MAKE_REF_ATOMIC__ */
+#endif /* _REENTRANT */
+
+/*
+ * We use a global counter for all c-nodes in this process.
+ * We wont wrap anyway due to the enormous amount of values
+ * available.
+ */
+#ifdef EI_MAKE_REF_ATOMIC__
+static ei_atomic_ref__ ref_count;
+#else
+static unsigned int ref_count[3];
+#endif
+
+static int
+init_make_ref(int late)
+{
+    
+#ifdef EI_MAKE_REF_ATOMIC__
+    ref_count = 0;
+#else /* !EI_MAKE_REF_ATOMIC__ */
+
+#ifdef _REENTRANT
+
+    if (late)
+        return ENOTSUP; /* Refuse doing unsafe initialization... */
+
+    ref_mtx = ei_mutex_create();
+    if (!ref_mtx)
+        return ENOMEM;
+    
+#endif /* _REENTRANT */
+
+    ref_count[0] = 0;
+    ref_count[1] = 0;
+    ref_count[2] = 0;
+
+#endif /* !EI_MAKE_REF_ATOMIC__ */
+
+    return 0;
+}
+
+int ei_make_ref(ei_cnode *ec, erlang_ref *ref)
+{
+    int err;
+    if (!ei_connect_initialized) {
+	fprintf(stderr,"<ERROR> erl_interface not initialized\n");
+        exit(1);
+    }
+
+    err = check_initialized_node(ec);
+    if (err) {
+        /*
+         * write invalid utf8 in nodename which will make
+         * ei_encode_ref() fail if used...
+         */
+        ref->node[0] = 0xff;
+        ref->node[1] = 0;
+        ref->len = -1;
+        return err;
+    }
+    
+    strcpy(ref->node, ec->thisnodename);
+    ref->creation = ec->creation;
+    ref->len = 3;
+
+#ifdef EI_MAKE_REF_ATOMIC__
+    {
+        ei_atomic_ref__ xchg, new;
+        xchg = __atomic_load_n(&ref_count, __ATOMIC_RELAXED);
+        do {
+            new = xchg + 1;
+        } while(!__atomic_compare_exchange_n(&ref_count, &xchg, new, 0,
+                                             __ATOMIC_ACQ_REL,
+                                             __ATOMIC_RELAXED));
+        ref->n[0] = (unsigned int) (new & 0x3ffff);
+        ref->n[1] = (unsigned int) ((new >> 18) & 0xffffffff);
+        ref->n[2] = (unsigned int) ((new >> (18+32)) & 0xffffffff);
+    }
+#else /* !EI_MAKE_REF_ATOMIC__ */
+
+#ifdef _REENTRANT
+    ei_mutex_lock(ref_mtx, 0);
+#endif
+
+    ref->n[0] = ref_count[0];
+    ref->n[1] = ref_count[1];
+    ref->n[2] = ref_count[2];
+    
+    ref_count[0]++;
+    ref_count[0] &= 0x3ffff;
+    if (ref_count[0] == 0) {
+        ref_count[1]++;
+        ref_count[1] &= 0xffffffff;
+        if (ref_count[1] == 0) {
+            ref_count[2]++;
+            ref_count[2] &= 0xffffffff;
+        }
+    }
+    
+#ifdef _REENTRANT
+    ei_mutex_unlock(ref_mtx);
+#endif
+
+#endif /* !EI_MAKE_REF_ATOMIC__ */
+    
+    return 0;
+}
+
 /* two internal functions that will let us support different cookies
 * (to be able to connect to other nodes that don't have the same
 * cookie as each other or us)
@@ -616,6 +877,18 @@ static int init_connect(int late)
         return error;
     }
 
+    error = init_make_ref(late);
+    if (error) {
+        EI_TRACE_ERR0("ei_init_connect","can't initiate ei_make_ref()");
+        return error;
+    }
+
+    error = init_make_pid(late);
+    if (error) {
+        EI_TRACE_ERR0("ei_init_connect","can't initiate ei_make_pid()");
+        return error;
+    }
+
     ei_connect_initialized = !0;
     return 0;
 }
@@ -650,6 +923,7 @@ int ei_connect_xinit_ussi(ei_cnode* ec, const char *thishostname,
     }
     
     ec->creation = creation & 0x3; /* 2 bits */
+    ec->pidsn = 0;
     
     if (cookie) {
 	if (strlen(cookie) >= sizeof(ec->ei_connect_cookie)) { 
diff --git a/lib/erl_interface/test/ei_connect_SUITE.erl b/lib/erl_interface/test/ei_connect_SUITE.erl
index 224608ba71..0506359b71 100644
--- a/lib/erl_interface/test/ei_connect_SUITE.erl
+++ b/lib/erl_interface/test/ei_connect_SUITE.erl
@@ -34,7 +34,9 @@
          ei_send_funs/1,
          ei_threaded_send/1,
          ei_set_get_tracelevel/1,
-         ei_connect_host_port_test/1]).
+         ei_connect_host_port_test/1,
+         ei_make_ref/1,
+         ei_make_pid/1]).
 
 -import(runner, [get_term/1,send_term/2]).
 
@@ -54,7 +56,9 @@ groups() ->
                ei_set_get_tracelevel,
                ei_reg_send,
                ei_reg_send_large,
-               ei_rpc],
+               ei_rpc,
+               ei_make_ref,
+               ei_make_pid],
     [{default, [], Members},
      {ussi, [], Members}].
 
@@ -207,6 +211,100 @@ ei_connect_host_port_test(Config) when is_list(Config) ->
     runner:recv_eot(P),
     ok.
 
+ei_make_ref(Config) when is_list(Config) ->
+    P = runner:start(Config, ?interpret),
+    0 = ei_connect_init(P, 42, erlang:get_cookie(), 0, get_group(Config)),
+    {ok,Fd} = ei_connect(P, node()),
+
+    %% Call ei_make_ref() enough times for it to
+    %% wrap the first internal integer..
+
+    N = 270,
+    {CNode, Refs} = make_refs(N, undefined, P, Fd, []),
+    io:format("Last Ref ~p~n", [hd(Refs)]),
+
+    io:format("CNode = ~p", [CNode]),
+
+    true = lists:member(CNode, nodes(hidden)),
+
+    %% Ensure that all references are
+    %% unique...
+    RefsLen = N*1000,
+    RefsLen = length(lists:usort(Refs)),
+
+    runner:send_eot(P),
+    runner:recv_eot(P),
+    ok.
+
+make_refs(0, CNode, _P, _Fd, Refs) ->
+    {CNode, Refs};
+make_refs(N, CNode, P, Fd, Refs) ->
+    ok = ei_make_refs(P, Fd, self()),
+    receive
+        {Node, NewRefs} ->
+            NewNode = if CNode == undefined ->
+                              Node;
+                         true ->
+                              CNode = Node
+                      end,
+            make_refs(N-1, NewNode, P, Fd,
+                      chk_refs(NewRefs, NewNode, Refs))
+    end.
+
+chk_refs([], _CNode, Refs) ->
+    Refs;
+chk_refs([NewRef|NewRefs], CNode, Refs) ->
+    true = is_reference(NewRef),
+    CNode = node(NewRef),
+    chk_refs(NewRefs, CNode, [NewRef|Refs]).
+
+ei_make_pid(Config) when is_list(Config) ->
+    P = runner:start(Config, ?interpret),
+    0 = ei_connect_init(P, 42, erlang:get_cookie(), 0, get_group(Config)),
+    {ok,Fd} = ei_connect(P, node()),
+
+    %%
+    %% Ensure to wrap all num values...
+    %%
+    N = 200,
+    {CNode, Pids} = make_pids(N, undefined, P, Fd, []),
+    io:format("Last Pid ~p~n", [hd(Pids)]),
+
+    io:format("CNode = ~p", [CNode]),
+
+    true = lists:member(CNode, nodes(hidden)),
+
+    %% Ensure that all pid created by ei_make_pid()
+    %% are unique. Note that ei_self() is passed
+    %% along in each call as well...
+    PidsLen = N*1000 + 1,
+    PidsLen = length(lists:usort(Pids)),
+
+    runner:send_eot(P),
+    runner:recv_eot(P),
+    ok.
+
+make_pids(0, CNode, _P, _Fd, Pids) ->
+    {CNode, Pids};
+make_pids(N, CNode, P, Fd, Pids) ->
+    ok = ei_make_pids(P, Fd, self()),
+    receive
+        {Node, NewPids} ->
+            NewNode = if CNode == undefined ->
+                              Node;
+                         true ->
+                              CNode = Node
+                      end,
+            make_pids(N-1, NewNode, P, Fd,
+                      chk_pids(NewPids, NewNode, Pids))
+    end.
+
+chk_pids([], _CNode, Pids) ->
+    Pids;
+chk_pids([NewPid|NewPids], CNode, Pids) ->
+    true = is_pid(NewPid),
+    CNode = node(NewPid),
+    chk_pids(NewPids, CNode, [NewPid|Pids]).
 
 %%% Interface functions for ei (erl_interface) functions.
 
@@ -256,6 +354,14 @@ ei_rpc(P, Fd, To, Func, Msg) ->
     send_command(P, ei_rpc, [Fd, To, Func, Msg]),
     get_term(P).
 
+ei_make_refs(P, Fd, To) ->
+    send_command(P, ei_make_refs, [Fd,To]),
+    get_send_result(P).
+
+ei_make_pids(P, Fd, To) ->
+    send_command(P, ei_make_pids, [Fd,To]),
+    get_send_result(P).
+
 
 get_send_result(P) ->
     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 1dcd62400a..0aa6879adf 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
@@ -40,6 +40,8 @@ static void cmd_ei_send_funs(char* buf, int len);
 static void cmd_ei_reg_send(char* buf, int len);
 static void cmd_ei_rpc(char* buf, int len);
 static void cmd_ei_set_get_tracelevel(char* buf, int len);
+static void cmd_ei_make_refs(char* buf, int len);
+static void cmd_ei_make_pids(char* buf, int len);
 
 static void send_errno_result(int value);
 
@@ -60,6 +62,8 @@ static struct {
     "ei_rpc",  		     4, cmd_ei_rpc,
     "ei_set_get_tracelevel", 1, cmd_ei_set_get_tracelevel,
     "ei_format_pid",         2, cmd_ei_format_pid,
+    "ei_make_refs",          2, cmd_ei_make_refs,
+    "ei_make_pids",          2, cmd_ei_make_pids,
 };
 
 
@@ -210,6 +214,80 @@ static void cmd_ei_send(char* buf, int len)
     ei_x_free(&x);
 }
 
+static void cmd_ei_make_refs(char* buf, int len)
+{
+    int index = 0;
+    long fd;
+    erlang_pid pid;
+    ei_x_buff x;
+    int i;
+    int nref = 1000;
+
+    if (ei_decode_long(buf, &index, &fd) < 0)
+	fail("expected long");
+    if (ei_decode_pid(buf, &index, &pid) < 0)
+	fail("expected pid (node)");
+    if (ei_x_new_with_version(&x) < 0)
+	fail("ei_x_new_with_version");
+    if (ei_x_encode_tuple_header(&x, 2) < 0)
+        fail("ei_x_encode_tuple_header() failed");
+    if (ei_x_encode_atom(&x, ei_thisnodename(&ec)) < 0)
+        fail("ei_x_encode_atom() failed");
+    if (ei_x_encode_list_header(&x, nref) < 0)
+        fail("ei_x_encode_list_header() failed");
+    for (i = 0; i < nref; i++) {
+        erlang_ref ref;
+        if (ei_make_ref(&ec, &ref))
+            fail("ei_make_ref() failed");
+        if (ei_x_encode_ref(&x, &ref))
+            fail("ei_x_encode_ref() failed");
+    }
+    if (ei_x_encode_empty_list(&x) < 0)
+        fail("ei_x_encode_empty_list() failed");
+    send_errno_result(ei_send(fd, &pid, x.buff, x.index));
+    ei_x_free(&x);
+}
+
+static void cmd_ei_make_pids(char* buf, int len)
+{
+    int index = 0;
+    long fd;
+    erlang_pid from_pid;
+    erlang_pid *self;
+    ei_x_buff x;
+    int i;
+    int npid = 1000;
+
+    if (ei_decode_long(buf, &index, &fd) < 0)
+	fail("expected long");
+    if (ei_decode_pid(buf, &index, &from_pid) < 0)
+	fail("expected pid (node)");
+    if (ei_x_new_with_version(&x) < 0)
+	fail("ei_x_new_with_version");
+    if (ei_x_encode_tuple_header(&x, 2) < 0)
+        fail("ei_x_encode_tuple_header() failed");
+    if (ei_x_encode_atom(&x, ei_thisnodename(&ec)) < 0)
+        fail("ei_x_encode_atom() failed");
+    if (ei_x_encode_list_header(&x, 1+npid) < 0)
+        fail("ei_x_encode_list_header() failed");
+    self = ei_self(&ec);
+    if (!self)
+        fail("ei_self() failed");
+    if (ei_x_encode_pid(&x, self))
+        fail("ei_x_encode_pid() failed");
+    for (i = 0; i < npid; i++) {
+        erlang_pid pid;
+        if (ei_make_pid(&ec, &pid))
+            fail("ei_make_pid() failed");
+        if (ei_x_encode_pid(&x, &pid))
+            fail("ei_x_encode_pid() failed");
+    }
+    if (ei_x_encode_empty_list(&x) < 0)
+        fail("ei_x_encode_empty_list() failed");
+    send_errno_result(ei_send(fd, &from_pid, x.buff, x.index));
+    ei_x_free(&x);
+}
+
 static void cmd_ei_format_pid(char* buf, int len)
 {
     int index = 0;
-- 
2.26.1