File 2023-Implement-TCP_KEEP-and-TCP_USER_TIMEOUT-for-gen_tcp.patch of Package erlang

From f5584207055758f4b320c222cd97bce7b624bd9d Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Mon, 17 Nov 2025 17:17:02 +0100
Subject: [PATCH 3/4] Implement TCP_KEEP* and TCP_USER_TIMEOUT for `gen_tcp`

Options TCP_KEEPCNT, TCP_KEEPIDLE, TCP_KEEPINTVL and TCP_USER_TIMEOUT
with Erlang names `keepcnt`, `keepidle`, `keepintvl` and `user_timeout`
for `gen_tcp` and `inet` `setopts` and `getopts`.
---
 erts/emulator/drivers/common/inet_drv.c | 72 +++++++++++++++++++++++++
 erts/preloaded/src/prim_inet.erl        | 16 +++++-
 lib/kernel/src/gen_tcp.erl              |  8 +++
 lib/kernel/src/gen_tcp_socket.erl       |  6 ++-
 lib/kernel/src/inet.erl                 | 15 +++++-
 lib/kernel/src/inet_int.hrl             |  7 ++-
 6 files changed, 118 insertions(+), 6 deletions(-)

diff --git a/erts/emulator/drivers/common/inet_drv.c b/erts/emulator/drivers/common/inet_drv.c
index afa268c089..6455c7a9aa 100644
--- a/erts/emulator/drivers/common/inet_drv.c
+++ b/erts/emulator/drivers/common/inet_drv.c
@@ -923,6 +923,10 @@ static size_t my_strnlen(const char *s, size_t maxlen)
 #define TCP_OPT_NOPUSH              48  /* super-Nagle, aka TCP_CORK */
 #define INET_LOPT_TCP_READ_AHEAD    49  /* Read ahead of packet data */
 #define INET_LOPT_NON_BLOCK_SEND    50  /* Non-blocking send, only SCTP */
+#define TCP_OPT_KEEPCNT             51  /* TCP_KEEPCNTK */
+#define TCP_OPT_KEEPIDLE            52  /* TCP_KEEPIDLE */
+#define TCP_OPT_KEEPINTVL           53  /* TCP_KEEPINTVL */
+#define TCP_OPT_USER_TIMEOUT        54  /* TCP_USER_TIMEOUT */
 #define INET_LOPT_DEBUG             99  /* Enable/disable DEBUG for a socket */
 
 /* SCTP options: a separate range, from 100: */
@@ -7493,6 +7497,50 @@ static int inet_set_opts(inet_descriptor* desc, char* ptr, int len)
 	    continue;
 #endif
 
+#if defined(TCP_KEEPCNT)
+	case TCP_OPT_KEEPCNT:
+            DDBG(desc,
+                 ("INET-DRV-DBG[%d][" SOCKET_FSTR ",%T] "
+                  "inet_set_opts(keepcnt) -> %d\r\n",
+                  __LINE__, desc->s, driver_caller(desc->port), ival) );
+	    proto = IPPROTO_TCP;
+	    type = TCP_KEEPCNT;
+	    break;
+#endif
+
+#if defined(TCP_KEEPIDLE)
+	case TCP_OPT_KEEPIDLE:
+            DDBG(desc,
+                 ("INET-DRV-DBG[%d][" SOCKET_FSTR ",%T] "
+                  "inet_set_opts(keepidle) -> %d\r\n",
+                  __LINE__, desc->s, driver_caller(desc->port), ival) );
+	    proto = IPPROTO_TCP;
+	    type = TCP_KEEPIDLE;
+	    break;
+#endif
+
+#if defined(TCP_KEEPINTVL)
+	case TCP_OPT_KEEPINTVL:
+            DDBG(desc,
+                 ("INET-DRV-DBG[%d][" SOCKET_FSTR ",%T] "
+                  "inet_set_opts(keepintvl) -> %d\r\n",
+                  __LINE__, desc->s, driver_caller(desc->port), ival) );
+	    proto = IPPROTO_TCP;
+	    type = TCP_KEEPINTVL;
+	    break;
+#endif
+
+#if defined(TCP_USER_TIMEOUT)
+	case TCP_OPT_USER_TIMEOUT:
+            DDBG(desc,
+                 ("INET-DRV-DBG[%d][" SOCKET_FSTR ",%T] "
+                  "inet_set_opts(user_timeout) -> %d\r\n",
+                  __LINE__, desc->s, driver_caller(desc->port), ival) );
+	    proto = IPPROTO_TCP;
+	    type = TCP_USER_TIMEOUT;
+	    break;
+#endif
+
 #if defined(HAVE_MULTICAST_SUPPORT) && defined(IPPROTO_IP)
 
 	case UDP_OPT_MULTICAST_TTL:
@@ -9380,6 +9428,30 @@ static ErlDrvSSizeT inet_fill_opts(inet_descriptor* desc,
 	    put_int32(0, ptr);
 	    continue;
 #endif
+#if defined(TCP_KEEPCNT)
+	case TCP_OPT_KEEPCNT:
+	    proto = IPPROTO_TCP;
+	    type = TCP_KEEPCNT;
+	    break;
+#endif
+#if defined(TCP_KEEPIDLE)
+	case TCP_OPT_KEEPIDLE:
+	    proto = IPPROTO_TCP;
+	    type = TCP_KEEPIDLE;
+	    break;
+#endif
+#if defined(TCP_KEEPINTVL)
+	case TCP_OPT_KEEPINTVL:
+	    proto = IPPROTO_TCP;
+	    type = TCP_KEEPINTVL;
+	    break;
+#endif
+#if defined(TCP_USER_TIMEOUT)
+	case TCP_OPT_USER_TIMEOUT:
+	    proto = IPPROTO_TCP;
+	    type = TCP_USER_TIMEOUT;
+	    break;
+#endif
 
 #if defined(HAVE_MULTICAST_SUPPORT) && defined(IPPROTO_IP)
 	case UDP_OPT_MULTICAST_TTL:
diff --git a/erts/preloaded/src/prim_inet.erl b/erts/preloaded/src/prim_inet.erl
index 4072a83697..78c415e7c5 100644
--- a/erts/preloaded/src/prim_inet.erl
+++ b/erts/preloaded/src/prim_inet.erl
@@ -1585,7 +1585,11 @@ enc_opt(line_delimiter)  -> ?INET_LOPT_LINE_DELIM;
 enc_opt(raw)             -> ?INET_OPT_RAW;
 enc_opt(bind_to_device)  -> ?INET_OPT_BIND_TO_DEVICE;
 enc_opt(read_ahead)      -> ?INET_LOPT_TCP_READ_AHEAD;
-enc_opt(non_block_send)  -> ?INET_OPT_NON_BLOCK_SEND;
+enc_opt(non_block_send)  -> ?INET_LOPT_NON_BLOCK_SEND;
+enc_opt(keepcnt)         -> ?TCP_OPT_KEEPCNT;
+enc_opt(keepidle)        -> ?TCP_OPT_KEEPIDLE;
+enc_opt(keepintvl)       -> ?TCP_OPT_KEEPINTVL;
+enc_opt(user_timeout)    -> ?TCP_OPT_USER_TIMEOUT;
 enc_opt(debug)           -> ?INET_OPT_DEBUG;
 % Names of SCTP opts:
 enc_opt(sctp_rtoinfo)	 	   -> ?SCTP_OPT_RTOINFO;
@@ -1658,7 +1662,11 @@ dec_opt(?INET_LOPT_LINE_DELIM)      -> line_delimiter;
 dec_opt(?INET_OPT_RAW)              -> raw;
 dec_opt(?INET_OPT_BIND_TO_DEVICE) -> bind_to_device;
 dec_opt(?INET_LOPT_TCP_READ_AHEAD) -> read_ahead;
-dec_opt(?INET_OPT_NON_BLOCK_SEND) -> non_block_send;
+dec_opt(?INET_LOPT_NON_BLOCK_SEND) -> non_block_send;
+dec_opt(?TCP_OPT_KEEPCNT)         -> keepcnt;
+dec_opt(?TCP_OPT_KEEPIDLE)        -> keepidle;
+dec_opt(?TCP_OPT_KEEPINTVL)       -> keepintvl;
+dec_opt(?TCP_OPT_USER_TIMEOUT)    -> user_timeout;
 dec_opt(?INET_OPT_DEBUG)          -> debug;
 dec_opt(I) when is_integer(I)     -> undefined.
 
@@ -1773,6 +1781,10 @@ type_opt_1(show_econnreset) -> bool;
 type_opt_1(bind_to_device)  -> binary;
 type_opt_1(read_ahead)      -> bool;
 type_opt_1(non_block_send)  -> bool;
+type_opt_1(keepcnt)         -> int;
+type_opt_1(keepidle)        -> int;
+type_opt_1(keepintvl)       -> int;
+type_opt_1(user_timeout)    -> uint;
 type_opt_1(debug)           -> bool;
 %% 
 %% SCTP options (to be set). If the type is a record type, the corresponding
diff --git a/lib/kernel/src/gen_tcp.erl b/lib/kernel/src/gen_tcp.erl
index 9b00ae369b..44e23ffc23 100644
--- a/lib/kernel/src/gen_tcp.erl
+++ b/lib/kernel/src/gen_tcp.erl
@@ -274,6 +274,9 @@ way, option `send_timeout` comes in handy.
         {high_msgq_watermark, pos_integer()} |
         {high_watermark,  non_neg_integer()} |
         {keepalive,       boolean()} |
+        {keepcnt,         integer()} |
+        {keepidle,        integer()} |
+        {keepintvl,       integer()} |
         {linger,          {boolean(), non_neg_integer()}} |
         {low_msgq_watermark, pos_integer()} |
         {low_watermark,   non_neg_integer()} |
@@ -302,6 +305,7 @@ way, option `send_timeout` comes in handy.
 	{recvtos,         boolean()} |
 	{recvtclass,      boolean()} |
 	{recvttl,         boolean()} |
+        {user_timeout,    non_neg_integer()} |
 	{ipv6_v6only,     boolean()}.
 
 -doc """
@@ -337,6 +341,9 @@ this value is returned from `inet:getopts/2` when called with the option name
         high_msgq_watermark |
         high_watermark |
         keepalive |
+        keepcnt |
+        keepidle |
+        keepintvl |
         linger |
         low_msgq_watermark |
         low_watermark |
@@ -365,6 +372,7 @@ this value is returned from `inet:getopts/2` when called with the option name
         recvtclass |
         recvttl |
         pktoptions |
+        user_timeout |
 	ipv6_v6only.
 -type connect_option() ::
         {fd, Fd :: non_neg_integer()} |
diff --git a/lib/kernel/src/gen_tcp_socket.erl b/lib/kernel/src/gen_tcp_socket.erl
index 4bd303d9bd..9bd03c9d6b 100644
--- a/lib/kernel/src/gen_tcp_socket.erl
+++ b/lib/kernel/src/gen_tcp_socket.erl
@@ -1284,7 +1284,11 @@ socket_opts() ->
 
           %%
           %% Level: tcp
-          nodelay => {tcp, nodelay},
+          keepcnt      => {tcp, keepcnt},
+          keepidle     => {tcp, keepidle},
+          keepintvl    => {tcp, keepintvl},
+          nodelay      => {tcp, nodelay},
+          user_timeout => {tcp, user_timeout},
 
           %%
           %% Level: ip
diff --git a/lib/kernel/src/inet.erl b/lib/kernel/src/inet.erl
index a0095fdcc8..073e16633c 100644
--- a/lib/kernel/src/inet.erl
+++ b/lib/kernel/src/inet.erl
@@ -1115,6 +1115,12 @@ The following options are available:
   other end does not respond, the connection is considered broken and an error
   message is sent to the controlling process. Defaults to `false`.
 
+- **`{keepcnt, Integer}` (TCP/IP sockets)** - Linux specific `TCP_KEEPCNT`.
+
+- **`{keepidle, Integer}` (TCP/IP sockets)** - Linux specific `TCP_KEEPIDLE`.
+
+- **`{keepintvl, Integer}` (TCP/IP sockets)** - Linux specific `TCP_KEEPINTVL`.
+
 - **`{linger, {true|false, Seconds}}`** [](){: #option-linger } -
   Determines the time-out, in seconds, for flushing unsent data
   in the [`close/1`](`close/1`) socket call.
@@ -1513,6 +1519,9 @@ The following options are available:
   different systems. The option is ignored on platforms where it is not
   implemented. Use with caution.
 
+- **`{user_timeout, Integer}` (TCP/IP sockets)** - Linux specific
+  `TCP_USER_TIMEOUT`.
+
 In addition to these options, _raw_ option specifications can be used. The raw
 options are specified as a tuple of arity four, beginning with tag `raw`,
 followed by the protocol level, the option number, and the option value
@@ -3101,7 +3110,8 @@ connect_options() ->
      header, active, packet, packet_size, buffer, mode, deliver, line_delimiter,
      exit_on_close, high_watermark, low_watermark, high_msgq_watermark,
      low_msgq_watermark, send_timeout, send_timeout_close, delay_send, raw,
-     show_econnreset, bind_to_device, read_ahead].
+     show_econnreset, bind_to_device, read_ahead,
+     keepcnt, keepidle, keepintvl, user_timeout].
 
 -doc false.
 connect_options(Opts, Mod) ->
@@ -3197,7 +3207,8 @@ listen_options() ->
      header, active, packet, buffer, mode, deliver, backlog, ipv6_v6only,
      exit_on_close, high_watermark, low_watermark, high_msgq_watermark,
      low_msgq_watermark, send_timeout, send_timeout_close, delay_send,
-     packet_size, raw, show_econnreset, bind_to_device, read_ahead].
+     packet_size, raw, show_econnreset, bind_to_device, read_ahead,
+     keepcnt, keepidle, keepintvl, user_timeout].
 
 -doc false.
 listen_options(Opts, Mod) ->
diff --git a/lib/kernel/src/inet_int.hrl b/lib/kernel/src/inet_int.hrl
index bb8457a605..c9bc4cc084 100644
--- a/lib/kernel/src/inet_int.hrl
+++ b/lib/kernel/src/inet_int.hrl
@@ -177,8 +177,13 @@
 -define(INET_OPT_RECVTTL,         47).
 -define(TCP_OPT_NOPUSH,           48).
 -define(INET_LOPT_TCP_READ_AHEAD, 49).
--define(INET_OPT_NON_BLOCK_SEND,  50).
+-define(INET_LOPT_NON_BLOCK_SEND, 50).
+-define(TCP_OPT_KEEPCNT,          51).
+-define(TCP_OPT_KEEPIDLE,         52).
+-define(TCP_OPT_KEEPINTVL,        53).
+-define(TCP_OPT_USER_TIMEOUT,     54).
 -define(INET_OPT_DEBUG,           99).
+
 % Specific SCTP options: separate range:
 -define(SCTP_OPT_RTOINFO,	 	100).
 -define(SCTP_OPT_ASSOCINFO,	 	101).
-- 
2.51.0

openSUSE Build Service is sponsored by