File 2931-Implement-support-for-IPPROTO_MPTCP.patch of Package erlang

From f4825e70a966a52c443e195bdf9dd817073ce09e Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Fri, 17 Oct 2025 18:10:43 +0200
Subject: [PATCH 1/3] Implement support for IPPROTO_MPTCP

---
 erts/emulator/drivers/common/inet_drv.c | 48 +++++++++++++++++++------
 erts/preloaded/src/prim_inet.erl        | 19 +++++++---
 lib/kernel/src/gen_tcp.erl              | 14 +++++++-
 lib/kernel/src/inet.erl                 | 13 +++++--
 lib/kernel/src/inet6_tcp.erl            | 23 +++++++-----
 lib/kernel/src/inet_int.hrl             | 21 +++++++----
 lib/kernel/src/inet_tcp.erl             | 23 +++++++-----
 lib/kernel/src/local_tcp.erl            |  1 +
 8 files changed, 120 insertions(+), 42 deletions(-)

diff --git a/erts/emulator/drivers/common/inet_drv.c b/erts/emulator/drivers/common/inet_drv.c
index a5f8e92d38..8eb5186f7b 100644
--- a/erts/emulator/drivers/common/inet_drv.c
+++ b/erts/emulator/drivers/common/inet_drv.c
@@ -765,6 +765,13 @@ static size_t my_strnlen(const char *s, size_t maxlen)
 #define INET_TYPE_DGRAM     2
 #define INET_TYPE_SEQPACKET 3
 
+/* open protocol */
+#define INET_PROTO_DEFAULT  0
+#define INET_PROTO_TCP      1
+#define INET_PROTO_UDP      2
+#define INET_PROTO_SCTP     3
+#define INET_PROTO_MPTCP    4
+
 /* INET_LOPT_MODE options */
 #define INET_MODE_LIST      0
 #define INET_MODE_BINARY    1
@@ -1598,6 +1605,7 @@ static ErlDrvTermData am_sendfile;
 #endif
 
 static char str_eafnosupport[] = "eafnosupport";
+static char str_eprotonosupport[] = "eprotonosupport";
 static char str_einval[] = "einval";
 
 /* special errors for bad ports and sequences */
@@ -5059,11 +5067,12 @@ static int erl_inet_close(inet_descriptor* desc)
     return 0;
 }
 
-static ErlDrvSSizeT inet_ctl_open(inet_descriptor* desc, int domain, int type,
-				  char** rbuf, ErlDrvSizeT rsize)
+static
+ErlDrvSSizeT inet_ctl_open(inet_descriptor* desc,
+                           int domain, int type, int protocol,
+                           char** rbuf, ErlDrvSizeT rsize)
 {
     int save_errno;
-    int protocol;
 #ifdef HAVE_SETNS
     int current_ns, new_ns;
     current_ns = new_ns = 0;
@@ -5106,7 +5115,6 @@ static ErlDrvSSizeT inet_ctl_open(inet_descriptor* desc, int domain, int type,
 	}
     }
 #endif
-    protocol = desc->sprotocol;
 #ifdef HAVE_SYS_UN_H
     if (domain == AF_UNIX) protocol = 0;
 #endif
@@ -11784,13 +11792,13 @@ static ErlDrvSSizeT tcp_inet_ctl(ErlDrvData e, unsigned int cmd,
     switch(cmd) {
 
     case INET_REQ_OPEN: { /* open socket and return internal index */
-	int domain;
+	int domain, protocol;
 
 	DDBG(INETP(desc),
 	     ("INET-DRV-DBG[%d][%T] tcp_inet_ctl -> OPEN\r\n",
 	      __LINE__, driver_caller(desc->inet.port)) );
 
-	if (len != 2) return ctl_error(EINVAL, rbuf, rsize);
+	if (len != 3) return ctl_error(EINVAL, rbuf, rsize);
 	switch(buf[0]) {
 	case INET_AF_INET:
 	    domain = AF_INET;
@@ -11809,7 +11817,18 @@ static ErlDrvSSizeT tcp_inet_ctl(ErlDrvData e, unsigned int cmd,
 	    return ctl_xerror(str_eafnosupport, rbuf, rsize);
 	}
 	if (buf[1] != INET_TYPE_STREAM) return ctl_error(EINVAL, rbuf, rsize);
-	return inet_ctl_open(INETP(desc), domain, SOCK_STREAM, rbuf, rsize);
+        switch(buf[2]) {
+        case INET_PROTO_DEFAULT: protocol = 0; break;
+        case INET_PROTO_TCP: protocol = IPPROTO_TCP; break;
+#ifdef IPPROTO_MPTCP
+        case INET_PROTO_MPTCP: protocol = IPPROTO_MPTCP; break;
+#endif
+        default:
+            return ctl_xerror(str_eprotonosupport, rbuf, rsize);
+        }
+	return
+            inet_ctl_open(INETP(desc),
+                          domain, SOCK_STREAM, protocol, rbuf, rsize);
 	break;
     }
 
@@ -14301,8 +14320,9 @@ static ErlDrvSSizeT packet_inet_ctl(ErlDrvData e, unsigned int cmd, char* buf,
     ErlDrvSSizeT replen;
     udp_descriptor * udesc = (udp_descriptor *) e;
     inet_descriptor* desc  = INETP(udesc);
-    int type = SOCK_DGRAM;
     int af = AF_INET;
+    int type = SOCK_DGRAM;
+    int protocol;
 
     cmd -= ERTS_INET_DRV_CONTROL_MAGIC_NUMBER;
 
@@ -14311,7 +14331,7 @@ static ErlDrvSSizeT packet_inet_ctl(ErlDrvData e, unsigned int cmd, char* buf,
 	DDBG(desc,
 	     ("INET-DRV-DBG[%d][%T] packet_inet_ctl -> OPEN\r\n",
 	      __LINE__, driver_caller(desc->port)) );
-	if (len != 2) {
+	if (len != 3) {
 	    return ctl_error(EINVAL, rbuf, rsize);
 	}
 
@@ -14337,7 +14357,15 @@ static ErlDrvSSizeT packet_inet_ctl(ErlDrvData e, unsigned int cmd, char* buf,
 	    return ctl_error(EINVAL, rbuf, rsize);
 	}
 
-	replen = inet_ctl_open(desc, af, type, rbuf, rsize);
+        switch(buf[2]) {
+        case INET_PROTO_DEFAULT: protocol = 0; break;
+        case INET_PROTO_UDP: protocol = IPPROTO_UDP; break;
+        case INET_PROTO_SCTP: protocol = IPPROTO_SCTP; break;
+        default:
+            return ctl_xerror(str_eprotonosupport, rbuf, rsize);
+        }
+
+	replen = inet_ctl_open(desc, af, type, protocol, rbuf, rsize);
 
 	if ((*rbuf)[0] != INET_REP_ERROR) {
 	    if (desc->active)
diff --git a/erts/preloaded/src/prim_inet.erl b/erts/preloaded/src/prim_inet.erl
index f3d1f5928e..54fd777a17 100644
--- a/erts/preloaded/src/prim_inet.erl
+++ b/erts/preloaded/src/prim_inet.erl
@@ -75,10 +75,12 @@
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 open(Protocol, Family, Type) ->
-    open(Protocol, Family, Type, [], ?INET_REQ_OPEN, []).
+    P = enc_proto(Protocol),
+    open(Protocol, Family, Type, [], ?INET_REQ_OPEN, [P]).
 
 open(Protocol, Family, Type, Opts) ->
-    open(Protocol, Family, Type, Opts, ?INET_REQ_OPEN, []).
+    P = enc_proto(Protocol),
+    open(Protocol, Family, Type, Opts, ?INET_REQ_OPEN, [P]).
 
 %% FDOPEN(tcp|udp|sctp, inet|inet6|local, stream|dgram|seqpacket, integer())
 
@@ -124,15 +126,22 @@ enc_type(stream) -> ?INET_TYPE_STREAM;
 enc_type(dgram) -> ?INET_TYPE_DGRAM;
 enc_type(seqpacket) -> ?INET_TYPE_SEQPACKET.
 
-protocol2drv(tcp)  -> "tcp_inet";
-protocol2drv(udp)  -> "udp_inet";
-protocol2drv(sctp) -> "sctp_inet".
+protocol2drv(tcp)   -> "tcp_inet";
+protocol2drv(udp)   -> "udp_inet";
+protocol2drv(sctp)  -> "sctp_inet";
+protocol2drv(mptcp) -> "tcp_inet".
 
 drv2protocol("tcp_inet")  -> tcp;
 drv2protocol("udp_inet")  -> udp;
 drv2protocol("sctp_inet") -> sctp;
 drv2protocol(_)           -> undefined.
 
+enc_proto(default) -> ?INET_PROTO_DEFAULT;
+enc_proto(tcp)     -> ?INET_PROTO_TCP;
+enc_proto(udp)     -> ?INET_PROTO_UDP;
+enc_proto(sctp)    -> ?INET_PROTO_SCTP;
+enc_proto(mptcp)   -> ?INET_PROTO_MPTCP.
+
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %%
 %% Shutdown(insock(), atom()) -> ok
diff --git a/lib/kernel/doc/src/gen_tcp.xml b/lib/kernel/doc/src/gen_tcp.xml
index c095c43082..73aed6b2e6 100644
--- a/lib/kernel/doc/src/gen_tcp.xml
+++ b/lib/kernel/doc/src/gen_tcp.xml
@@ -393,6 +393,12 @@ do_recv(Sock, Bs) ->
           <tag><c>{tcp_module, module()}</c></tag>
           <item><p>Overrides which callback module is used. Defaults to
             <c>inet_tcp</c> for IPv4 and <c>inet6_tcp</c> for IPv6.</p></item>
+          <tag><c>{protocol, tcp|mptcp}</c></tag>
+          <item><p>With <c>mptcp</c> creates the socket with protocol IPPROTO_MPTCP,
+            if that is defined on the system.
+            Other than that the socket is regarded as a <c>tcp</c> socket.
+            If IPPROTO_MPTCP is not defined, `{error, eprotonosupport}`
+            is returned. <c>tcp</c> is the default value.</p></item>
           <tag><c>Opt</c></tag>
           <item><p>See
             <seemfa marker="inet#setopts/2"><c>inet:setopts/2</c></seemfa>.</p>
@@ -519,6 +525,12 @@ do_recv(Sock, Bs) ->
 	  <tag><c>{tcp_module, module()}</c></tag>
           <item><p>Overrides which callback module is used. Defaults to
             <c>inet_tcp</c> for IPv4 and <c>inet6_tcp</c> for IPv6.</p></item>
+          <tag><c>{protocol, tcp|mptcp}</c></tag>
+          <item><p>With <c>mptcp</c> creates the socket with protocol IPPROTO_MPTCP,
+            if that is defined on the system.
+            Other than that the socket is regarded as a <c>tcp</c> socket.
+            If IPPROTO_MPTCP is not defined, `{error, eprotonosupport}`
+            is returned. <c>tcp</c> is the default value.</p></item>
           <tag><c>Opt</c></tag>
 	  <item>
 	    <p>See
diff --git a/lib/kernel/src/inet.erl b/lib/kernel/src/inet.erl
index 3c12ee14b3..2aa5ffe604 100644
--- a/lib/kernel/src/inet.erl
+++ b/lib/kernel/src/inet.erl
@@ -3170,6 +3170,11 @@ con_opt([Opt | Opts], #connect_opts{ifaddr = IfAddr} = R, As) ->
 	{line_delimiter,C} when is_integer(C), C >= 0, C =< 255 ->
 	    con_add(line_delimiter, C, R, Opts, As);
 
+        {protocol, Proto}
+          when Proto =:= tcp;
+               Proto =:= mptcp ->
+            con_opt(Opts, R#connect_opts { protocol = Proto }, As);
+
 	{Name,Val} when is_atom(Name) -> con_add(Name, Val, R, Opts, As);
 
 	_ -> {error, badarg}
@@ -3254,6 +3259,10 @@ list_opt([Opt | Opts], #listen_opts{ifaddr = IfAddr} = R, As) ->
         {active,N} when is_integer(N), N < 32768, N >= -32768 ->
             NOpts = lists:keydelete(active, 1, R#listen_opts.opts),
             list_opt(Opts, R#listen_opts { opts = [{active,N}|NOpts] }, As);
+        {protocol, Proto}
+          when Proto =:= tcp;
+               Proto =:= mptcp ->
+            list_opt(Opts, R#listen_opts { protocol = Proto }, As);
 	{Name,Val} when is_atom(Name) -> list_add(Name, Val, R, Opts, As);
 	_ -> {error, badarg}
     end;
@@ -3920,7 +3929,7 @@ gethostbyaddr_tm_native(Addr, Timer, Opts) ->
 	     undefined, % Internal - no bind()
 	   BPort :: port_number(),
 	   Opts :: [socket_setopt()],
-	   Protocol :: socket_protocol(),
+	   Protocol :: socket_protocol() | 'mptcp',
 	   Family :: address_family(),
 	   Type :: socket_type(),
 	   Module :: atom()) ->
@@ -3975,7 +3984,7 @@ open(Fd_or_OpenOpts, BAddr, BPort, Opts, Protocol, Family, Type, Module) ->
                   undefined, % Internal - translated to 'any'
                 BPort :: port_number(),
                 Opts :: [socket_setopt()],
-                Protocol :: socket_protocol(),
+                Protocol :: socket_protocol() | 'mptcp',
                 Family :: address_family(),
                 Type :: socket_type(),
                 Module :: atom()) ->
diff --git a/lib/kernel/src/inet6_tcp.erl b/lib/kernel/src/inet6_tcp.erl
index 147fecbac5..2af69852c3 100644
--- a/lib/kernel/src/inet6_tcp.erl
+++ b/lib/kernel/src/inet6_tcp.erl
@@ -38,6 +38,8 @@
 
 %% -define(DBG(T), erlang:display({{self(), ?MODULE, ?LINE, ?FUNCTION_NAME}, T})).
 
+proto(undefined) -> ?PROTO;
+proto(Proto) -> Proto.
 
 %% my address family
 family() -> ?FAMILY.
@@ -132,17 +134,18 @@ do_connect2(SockAddr, Opts, Time) ->
     case inet:connect_options(Opts, ?MODULE) of
 	{error, Reason} -> exit(Reason);
 	{ok,
-	 #connect_opts{fd     = Fd,
-                       ifaddr = BAddr,
-                       port   = BPort,
-                       opts   = SockOpts}}
+	 #connect_opts{fd       = Fd,
+                       ifaddr   = BAddr,
+                       port     = BPort,
+                       opts     = SockOpts,
+                       protocol = Protocol}}
           when is_map(BAddr); % sockaddr_in6()
                ?port(BPort), ?ip6(BAddr);
                ?port(BPort), BAddr =:= undefined ->
 	    case
                 inet:open(
                   Fd, BAddr, BPort, SockOpts,
-                  ?PROTO, ?FAMILY, ?TYPE, ?MODULE)
+                  proto(Protocol), ?FAMILY, ?TYPE, ?MODULE)
             of
 		{ok, S} ->
 		    case prim_inet:connect(S, SockAddr, Time) of
@@ -163,13 +166,14 @@ do_connect(Addr = {A,B,C,D,E,F,G,H}, Port, Opts, Time)
 	    fd = Fd,
 	    ifaddr = BAddr,
 	    port = BPort,
-	    opts = SockOpts}}
+	    opts = SockOpts,
+            protocol = Protocol}}
           when ?port(BPort), ?ip6(BAddr);
                ?port(BPort), BAddr =:= undefined ->
 	    case
                 inet:open(
                   Fd, BAddr, BPort, SockOpts,
-                  ?PROTO, ?FAMILY, ?TYPE, ?MODULE)
+                  proto(Protocol), ?FAMILY, ?TYPE, ?MODULE)
             of
 		{ok, S} ->
 		    case prim_inet:connect(S, Addr, Port, Time) of
@@ -196,7 +200,8 @@ listen(Port, Opts) ->
 	    fd = Fd,
 	    ifaddr = BAddr,
 	    port = BPort,
-	    opts = SockOpts} = R}
+	    opts = SockOpts,
+            protocol = Protocol} = R}
           when is_map(BAddr); % sockaddr_in6()
                ?ip6(BAddr), ?port(BPort);
                BAddr =:= undefined, ?port(BPort) ->
@@ -207,7 +212,7 @@ listen(Port, Opts) ->
 	    case
                 inet:open_bind(
                   Fd, BAddr, BPort, SockOpts,
-                  ?PROTO, ?FAMILY, ?TYPE, ?MODULE)
+                  proto(Protocol), ?FAMILY, ?TYPE, ?MODULE)
             of
 		{ok, S} ->
 		    case prim_inet:listen(S, R#listen_opts.backlog) of
diff --git a/lib/kernel/src/inet_int.hrl b/lib/kernel/src/inet_int.hrl
index beab45fd19..ceec5bf87c 100644
--- a/lib/kernel/src/inet_int.hrl
+++ b/lib/kernel/src/inet_int.hrl
@@ -39,6 +39,13 @@
 -define(INET_TYPE_DGRAM,      2).
 -define(INET_TYPE_SEQPACKET,  3).
 
+%% protocols
+-define(INET_PROTO_DEFAULT,   0).
+-define(INET_PROTO_TCP,       1).
+-define(INET_PROTO_UDP,       2).
+-define(INET_PROTO_SCTP,      3).
+-define(INET_PROTO_MPTCP,     4).
+
 %% socket modes, INET_LOPT_MODE
 -define(INET_MODE_LIST,	      0).
 -define(INET_MODE_BINARY,     1).
@@ -413,22 +420,24 @@
 %% deliver = term
 %% active  = false
 %%
--record(connect_opts, 
-	{ 
+-record(connect_opts,
+	{
 	  ifaddr,           %% 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
+	  opts   = [],      %% [{active,true}] added in inet:connect_options
+          protocol = undefined
 	 }).
 
--record(listen_opts, 
-	{ 
+-record(listen_opts,
+	{
 	  ifaddr,                    %% interpreted as 'any' in *_tcp.erl
 	  port   = 0,                %% bind to port (default is dynamic port)
 	  backlog = ?LISTEN_BACKLOG, %% backlog
 	  fd      = -1,              %% %% fd >= 0 => already bound
-	  opts   = []                %% [{active,true}] added in 
+	  opts   = [],               %% [{active,true}] added in
 	                             %% inet:listen_options
+          protocol = undefined
 	 }).
 
 -record(udp_opts,
diff --git a/lib/kernel/src/inet_tcp.erl b/lib/kernel/src/inet_tcp.erl
index 99d151539b..932a6d3a2b 100644
--- a/lib/kernel/src/inet_tcp.erl
+++ b/lib/kernel/src/inet_tcp.erl
@@ -40,6 +40,8 @@
 
 %% -define(DBG(T), erlang:display({{self(), ?MODULE, ?LINE, ?FUNCTION_NAME}, T})).
 
+proto(undefined) -> ?PROTO;
+proto(Proto) -> Proto.
 
 %% my address family
 family() -> ?FAMILY.
@@ -129,17 +131,18 @@ do_connect2(SockAddr, Opts, Time) ->
     case inet:connect_options(Opts, ?MODULE) of
 	{error, Reason} -> exit(Reason);
 	{ok,
-	 #connect_opts{fd     = Fd,
-                       ifaddr = BAddr,
-                       port   = BPort,
-                       opts   = SockOpts}}
+	 #connect_opts{fd       = Fd,
+                       ifaddr   = BAddr,
+                       port     = BPort,
+                       opts     = SockOpts,
+                       protocol = Protocol}}
           when is_map(BAddr); % sockaddr_in()
                ?port(BPort), ?ip(BAddr);
                ?port(BPort), BAddr =:= undefined ->
 	    case
                 inet:open(
                   Fd, BAddr, BPort, SockOpts,
-                  ?PROTO, ?FAMILY, ?TYPE, ?MODULE)
+                  proto(Protocol), ?FAMILY, ?TYPE, ?MODULE)
             of
 		{ok, S} ->
 		    case prim_inet:connect(S, SockAddr, Time) of
@@ -160,13 +163,14 @@ do_connect(Addr = {A,B,C,D}, Port, Opts, Time)
 	    fd = Fd,
 	    ifaddr = BAddr,
 	    port = BPort,
-	    opts = SockOpts}}
+	    opts = SockOpts,
+            protocol = Protocol}}
           when ?port(BPort), ?ip(BAddr);
                ?port(BPort), BAddr =:= undefined ->
 	    case
                 inet:open(
                   Fd, BAddr, BPort, SockOpts,
-                  ?PROTO, ?FAMILY, ?TYPE, ?MODULE)
+                  proto(Protocol), ?FAMILY, ?TYPE, ?MODULE)
             of
 		{ok, S} ->
 		    case prim_inet:connect(S, Addr, Port, Time) of
@@ -190,7 +194,8 @@ listen(Port, Opts) ->
 	    fd = Fd,
 	    ifaddr = BAddr,
 	    port = BPort,
-	    opts = SockOpts} = R}
+	    opts = SockOpts,
+            protocol = Protocol} = R}
           when is_map(BAddr); % sockaddr_in()
                ?port(BPort), ?ip(BAddr);
                ?port(BPort), BAddr =:= undefined ->
@@ -201,7 +206,7 @@ listen(Port, Opts) ->
 	    case
                 inet:open_bind(
                   Fd, BAddr, BPort, SockOpts,
-                  ?PROTO, ?FAMILY, ?TYPE, ?MODULE)
+                  proto(Protocol), ?FAMILY, ?TYPE, ?MODULE)
             of
 		{ok, S} ->
 		    case prim_inet:listen(S, R#listen_opts.backlog) of
diff --git a/lib/kernel/src/local_tcp.erl b/lib/kernel/src/local_tcp.erl
index 46b995f251..92a3be1655 100644
--- a/lib/kernel/src/local_tcp.erl
+++ b/lib/kernel/src/local_tcp.erl
@@ -37,6 +37,7 @@
 -define(PROTO, tcp).
 -define(TYPE, stream).
 
+
 %% port lookup
 getserv(0) -> {ok, 0}.
 
-- 
2.51.0

openSUSE Build Service is sponsored by