File 1136-inet_tcp-inet6_tcp-do-not-bind-connecting-sockets-by.patch of Package erlang

From 8aaf960030fc933f34ecc15e12c5bf01572e7a9a Mon Sep 17 00:00:00 2001
From: Maxim Fedorov <maximfca@gmail.com>
Date: Tue, 19 Jan 2021 19:14:59 -0800
Subject: [PATCH 1/2] inet_tcp, inet6_tcp: do not bind connecting sockets by
 default

There is no need to bind a socket intended to be used for outgoing
connection. This operation exhaust ephemeral port range, preventing
large number of concurrent outgoing connections.
Omitting bind call also saves an extra trip to kernel.

There is no reliable way to test this, as different platforms have
various limitations on number of file descriptors open, ephemeral
port count and socket allocation mechanisms.

Manual testing can be done using this code:

  verify(0) ->
      ok;
  verify(Remain) ->
      receive
          {result, {error, Good}} when Good =:= timeout; Good =:= econnrefused ->
              verify(Remain - 1);
          {result, Any} ->
              Any
      end.

  test_conn() ->
      Self = self(),
      Expect = 32000, %% this number is guaranteed to be larger than ephemeral port count
      [spawn(
          fun() ->
              Res = catch (gen_tcp:connect(
                  {10, 20, (Seq div 254 + 1) rem 254, Seq rem 254 + 1}, 12345, [], 5000)),
              Self ! {result, Res}
          end) || Seq <- lists:seq(1, Expect)],
      verify(Expect).

To run this code, system must be configured for high file descriptor limit
(e.g."ulimit -n 100000").
---
 lib/kernel/src/inet6_tcp.erl | 13 ++++++++++---
 lib/kernel/src/inet_int.hrl  |  2 +-
 lib/kernel/src/inet_tcp.erl  | 13 ++++++++++---
 3 files changed, 21 insertions(+), 7 deletions(-)

diff --git a/lib/kernel/src/inet6_tcp.erl b/lib/kernel/src/inet6_tcp.erl
index 347b8b9a1b..cdb101e86a 100644
--- a/lib/kernel/src/inet6_tcp.erl
+++ b/lib/kernel/src/inet6_tcp.erl
@@ -120,12 +120,12 @@ do_connect(Addr = {A,B,C,D,E,F,G,H}, Port, Opts, Time)
 	{ok,
 	 #connect_opts{
 	    fd = Fd,
-	    ifaddr = BAddr = {Ab,Bb,Cb,Db,Eb,Fb,Gb,Hb},
+	    ifaddr = BAddr,
 	    port = BPort,
 	    opts = SockOpts}}
-	when ?ip6(Ab,Bb,Cb,Db,Eb,Fb,Gb,Hb), ?port(BPort) ->
+	when ?port(BPort) ->
 	    case inet:open(
-		   Fd, BAddr, BPort, SockOpts,
+		   Fd, check_ip_format(BAddr), BPort, SockOpts,
 		   ?PROTO, ?FAMILY, ?TYPE, ?MODULE) of
 		{ok, S} ->
 		    case prim_inet:connect(S, Addr, Port, Time) of
@@ -137,6 +137,13 @@ do_connect(Addr = {A,B,C,D,E,F,G,H}, Port, Opts, Time)
 	{ok, _} -> exit(badarg)
     end.
 
+check_ip_format(undefined) ->
+	undefined;
+check_ip_format(Ip = {Ab,Bb,Cb,Db,Eb,Fb,Gb,Hb}) when ?ip6(Ab,Bb,Cb,Db,Eb,Fb,Gb,Hb) ->
+	Ip;
+check_ip_format(_) ->
+	exit(badarg).
+
 %% 
 %% Listen
 %%
diff --git a/lib/kernel/src/inet_int.hrl b/lib/kernel/src/inet_int.hrl
index f6525d7261..4c69d7359c 100644
--- a/lib/kernel/src/inet_int.hrl
+++ b/lib/kernel/src/inet_int.hrl
@@ -395,7 +395,7 @@
 %%
 -record(connect_opts, 
 	{ 
-	  ifaddr = any,     %% bind to interface address
+	  ifaddr = undefined,   %% don't bind explicitly, let connect decide
 	  port   = 0,       %% bind to port (default is dynamic port)
 	  fd     = -1,      %% fd >= 0 => already bound
 	  opts   = []       %% [{active,true}] added in inet:connect_options
diff --git a/lib/kernel/src/inet_tcp.erl b/lib/kernel/src/inet_tcp.erl
index f1e3116856..5bee75d7a2 100644
--- a/lib/kernel/src/inet_tcp.erl
+++ b/lib/kernel/src/inet_tcp.erl
@@ -117,12 +117,12 @@ do_connect(Addr = {A,B,C,D}, Port, Opts, Time)
 	{ok,
 	 #connect_opts{
 	    fd = Fd,
-	    ifaddr = BAddr = {Ab,Bb,Cb,Db},
+	    ifaddr = BAddr,
 	    port = BPort,
 	    opts = SockOpts}}
-	when ?ip(Ab,Bb,Cb,Db), ?port(BPort) ->
+	when ?port(BPort) ->
 	    case inet:open(
-		   Fd, BAddr, BPort, SockOpts,
+		   Fd, check_ip_format(BAddr), BPort, SockOpts,
 		   ?PROTO, ?FAMILY, ?TYPE, ?MODULE) of
 		{ok, S} ->
 		    case prim_inet:connect(S, Addr, Port, Time) of
@@ -134,6 +134,13 @@ do_connect(Addr = {A,B,C,D}, Port, Opts, Time)
 	{ok, _} -> exit(badarg)
     end.
 
+check_ip_format(undefined) ->
+	undefined;
+check_ip_format(Ip = {Ab,Bb,Cb,Db}) when ?ip(Ab,Bb,Cb,Db) ->
+	Ip;
+check_ip_format(_) ->
+	exit(badarg).
+
 %% 
 %% Listen
 %%
-- 
2.26.2

openSUSE Build Service is sponsored by