Skip to content

Commit f558420

Browse files
committed
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`.
1 parent 94b7171 commit f558420

File tree

6 files changed

+118
-6
lines changed

6 files changed

+118
-6
lines changed

erts/emulator/drivers/common/inet_drv.c

Lines changed: 72 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -923,6 +923,10 @@ static size_t my_strnlen(const char *s, size_t maxlen)
923923
#define TCP_OPT_NOPUSH 48 /* super-Nagle, aka TCP_CORK */
924924
#define INET_LOPT_TCP_READ_AHEAD 49 /* Read ahead of packet data */
925925
#define INET_LOPT_NON_BLOCK_SEND 50 /* Non-blocking send, only SCTP */
926+
#define TCP_OPT_KEEPCNT 51 /* TCP_KEEPCNTK */
927+
#define TCP_OPT_KEEPIDLE 52 /* TCP_KEEPIDLE */
928+
#define TCP_OPT_KEEPINTVL 53 /* TCP_KEEPINTVL */
929+
#define TCP_OPT_USER_TIMEOUT 54 /* TCP_USER_TIMEOUT */
926930
#define INET_LOPT_DEBUG 99 /* Enable/disable DEBUG for a socket */
927931

928932
/* SCTP options: a separate range, from 100: */
@@ -7493,6 +7497,50 @@ static int inet_set_opts(inet_descriptor* desc, char* ptr, int len)
74937497
continue;
74947498
#endif
74957499

7500+
#if defined(TCP_KEEPCNT)
7501+
case TCP_OPT_KEEPCNT:
7502+
DDBG(desc,
7503+
("INET-DRV-DBG[%d][" SOCKET_FSTR ",%T] "
7504+
"inet_set_opts(keepcnt) -> %d\r\n",
7505+
__LINE__, desc->s, driver_caller(desc->port), ival) );
7506+
proto = IPPROTO_TCP;
7507+
type = TCP_KEEPCNT;
7508+
break;
7509+
#endif
7510+
7511+
#if defined(TCP_KEEPIDLE)
7512+
case TCP_OPT_KEEPIDLE:
7513+
DDBG(desc,
7514+
("INET-DRV-DBG[%d][" SOCKET_FSTR ",%T] "
7515+
"inet_set_opts(keepidle) -> %d\r\n",
7516+
__LINE__, desc->s, driver_caller(desc->port), ival) );
7517+
proto = IPPROTO_TCP;
7518+
type = TCP_KEEPIDLE;
7519+
break;
7520+
#endif
7521+
7522+
#if defined(TCP_KEEPINTVL)
7523+
case TCP_OPT_KEEPINTVL:
7524+
DDBG(desc,
7525+
("INET-DRV-DBG[%d][" SOCKET_FSTR ",%T] "
7526+
"inet_set_opts(keepintvl) -> %d\r\n",
7527+
__LINE__, desc->s, driver_caller(desc->port), ival) );
7528+
proto = IPPROTO_TCP;
7529+
type = TCP_KEEPINTVL;
7530+
break;
7531+
#endif
7532+
7533+
#if defined(TCP_USER_TIMEOUT)
7534+
case TCP_OPT_USER_TIMEOUT:
7535+
DDBG(desc,
7536+
("INET-DRV-DBG[%d][" SOCKET_FSTR ",%T] "
7537+
"inet_set_opts(user_timeout) -> %d\r\n",
7538+
__LINE__, desc->s, driver_caller(desc->port), ival) );
7539+
proto = IPPROTO_TCP;
7540+
type = TCP_USER_TIMEOUT;
7541+
break;
7542+
#endif
7543+
74967544
#if defined(HAVE_MULTICAST_SUPPORT) && defined(IPPROTO_IP)
74977545

74987546
case UDP_OPT_MULTICAST_TTL:
@@ -9380,6 +9428,30 @@ static ErlDrvSSizeT inet_fill_opts(inet_descriptor* desc,
93809428
put_int32(0, ptr);
93819429
continue;
93829430
#endif
9431+
#if defined(TCP_KEEPCNT)
9432+
case TCP_OPT_KEEPCNT:
9433+
proto = IPPROTO_TCP;
9434+
type = TCP_KEEPCNT;
9435+
break;
9436+
#endif
9437+
#if defined(TCP_KEEPIDLE)
9438+
case TCP_OPT_KEEPIDLE:
9439+
proto = IPPROTO_TCP;
9440+
type = TCP_KEEPIDLE;
9441+
break;
9442+
#endif
9443+
#if defined(TCP_KEEPINTVL)
9444+
case TCP_OPT_KEEPINTVL:
9445+
proto = IPPROTO_TCP;
9446+
type = TCP_KEEPINTVL;
9447+
break;
9448+
#endif
9449+
#if defined(TCP_USER_TIMEOUT)
9450+
case TCP_OPT_USER_TIMEOUT:
9451+
proto = IPPROTO_TCP;
9452+
type = TCP_USER_TIMEOUT;
9453+
break;
9454+
#endif
93839455

93849456
#if defined(HAVE_MULTICAST_SUPPORT) && defined(IPPROTO_IP)
93859457
case UDP_OPT_MULTICAST_TTL:

erts/preloaded/src/prim_inet.erl

Lines changed: 14 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1585,7 +1585,11 @@ enc_opt(line_delimiter) -> ?INET_LOPT_LINE_DELIM;
15851585
enc_opt(raw) -> ?INET_OPT_RAW;
15861586
enc_opt(bind_to_device) -> ?INET_OPT_BIND_TO_DEVICE;
15871587
enc_opt(read_ahead) -> ?INET_LOPT_TCP_READ_AHEAD;
1588-
enc_opt(non_block_send) -> ?INET_OPT_NON_BLOCK_SEND;
1588+
enc_opt(non_block_send) -> ?INET_LOPT_NON_BLOCK_SEND;
1589+
enc_opt(keepcnt) -> ?TCP_OPT_KEEPCNT;
1590+
enc_opt(keepidle) -> ?TCP_OPT_KEEPIDLE;
1591+
enc_opt(keepintvl) -> ?TCP_OPT_KEEPINTVL;
1592+
enc_opt(user_timeout) -> ?TCP_OPT_USER_TIMEOUT;
15891593
enc_opt(debug) -> ?INET_OPT_DEBUG;
15901594
% Names of SCTP opts:
15911595
enc_opt(sctp_rtoinfo) -> ?SCTP_OPT_RTOINFO;
@@ -1658,7 +1662,11 @@ dec_opt(?INET_LOPT_LINE_DELIM) -> line_delimiter;
16581662
dec_opt(?INET_OPT_RAW) -> raw;
16591663
dec_opt(?INET_OPT_BIND_TO_DEVICE) -> bind_to_device;
16601664
dec_opt(?INET_LOPT_TCP_READ_AHEAD) -> read_ahead;
1661-
dec_opt(?INET_OPT_NON_BLOCK_SEND) -> non_block_send;
1665+
dec_opt(?INET_LOPT_NON_BLOCK_SEND) -> non_block_send;
1666+
dec_opt(?TCP_OPT_KEEPCNT) -> keepcnt;
1667+
dec_opt(?TCP_OPT_KEEPIDLE) -> keepidle;
1668+
dec_opt(?TCP_OPT_KEEPINTVL) -> keepintvl;
1669+
dec_opt(?TCP_OPT_USER_TIMEOUT) -> user_timeout;
16621670
dec_opt(?INET_OPT_DEBUG) -> debug;
16631671
dec_opt(I) when is_integer(I) -> undefined.
16641672

@@ -1773,6 +1781,10 @@ type_opt_1(show_econnreset) -> bool;
17731781
type_opt_1(bind_to_device) -> binary;
17741782
type_opt_1(read_ahead) -> bool;
17751783
type_opt_1(non_block_send) -> bool;
1784+
type_opt_1(keepcnt) -> int;
1785+
type_opt_1(keepidle) -> int;
1786+
type_opt_1(keepintvl) -> int;
1787+
type_opt_1(user_timeout) -> uint;
17761788
type_opt_1(debug) -> bool;
17771789
%%
17781790
%% SCTP options (to be set). If the type is a record type, the corresponding

lib/kernel/src/gen_tcp.erl

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -274,6 +274,9 @@ way, option `send_timeout` comes in handy.
274274
{high_msgq_watermark, pos_integer()} |
275275
{high_watermark, non_neg_integer()} |
276276
{keepalive, boolean()} |
277+
{keepcnt, integer()} |
278+
{keepidle, integer()} |
279+
{keepintvl, integer()} |
277280
{linger, {boolean(), non_neg_integer()}} |
278281
{low_msgq_watermark, pos_integer()} |
279282
{low_watermark, non_neg_integer()} |
@@ -302,6 +305,7 @@ way, option `send_timeout` comes in handy.
302305
{recvtos, boolean()} |
303306
{recvtclass, boolean()} |
304307
{recvttl, boolean()} |
308+
{user_timeout, non_neg_integer()} |
305309
{ipv6_v6only, boolean()}.
306310

307311
-doc """
@@ -337,6 +341,9 @@ this value is returned from `inet:getopts/2` when called with the option name
337341
high_msgq_watermark |
338342
high_watermark |
339343
keepalive |
344+
keepcnt |
345+
keepidle |
346+
keepintvl |
340347
linger |
341348
low_msgq_watermark |
342349
low_watermark |
@@ -365,6 +372,7 @@ this value is returned from `inet:getopts/2` when called with the option name
365372
recvtclass |
366373
recvttl |
367374
pktoptions |
375+
user_timeout |
368376
ipv6_v6only.
369377
-type connect_option() ::
370378
{fd, Fd :: non_neg_integer()} |

lib/kernel/src/gen_tcp_socket.erl

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1284,7 +1284,11 @@ socket_opts() ->
12841284

12851285
%%
12861286
%% Level: tcp
1287-
nodelay => {tcp, nodelay},
1287+
keepcnt => {tcp, keepcnt},
1288+
keepidle => {tcp, keepidle},
1289+
keepintvl => {tcp, keepintvl},
1290+
nodelay => {tcp, nodelay},
1291+
user_timeout => {tcp, user_timeout},
12881292

12891293
%%
12901294
%% Level: ip

lib/kernel/src/inet.erl

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1115,6 +1115,12 @@ The following options are available:
11151115
other end does not respond, the connection is considered broken and an error
11161116
message is sent to the controlling process. Defaults to `false`.
11171117

1118+
- **`{keepcnt, Integer}` (TCP/IP sockets)** - Linux specific `TCP_KEEPCNT`.
1119+
1120+
- **`{keepidle, Integer}` (TCP/IP sockets)** - Linux specific `TCP_KEEPIDLE`.
1121+
1122+
- **`{keepintvl, Integer}` (TCP/IP sockets)** - Linux specific `TCP_KEEPINTVL`.
1123+
11181124
- **`{linger, {true|false, Seconds}}`** [](){: #option-linger } -
11191125
Determines the time-out, in seconds, for flushing unsent data
11201126
in the [`close/1`](`close/1`) socket call.
@@ -1513,6 +1519,9 @@ The following options are available:
15131519
different systems. The option is ignored on platforms where it is not
15141520
implemented. Use with caution.
15151521

1522+
- **`{user_timeout, Integer}` (TCP/IP sockets)** - Linux specific
1523+
`TCP_USER_TIMEOUT`.
1524+
15161525
In addition to these options, _raw_ option specifications can be used. The raw
15171526
options are specified as a tuple of arity four, beginning with tag `raw`,
15181527
followed by the protocol level, the option number, and the option value
@@ -3101,7 +3110,8 @@ connect_options() ->
31013110
header, active, packet, packet_size, buffer, mode, deliver, line_delimiter,
31023111
exit_on_close, high_watermark, low_watermark, high_msgq_watermark,
31033112
low_msgq_watermark, send_timeout, send_timeout_close, delay_send, raw,
3104-
show_econnreset, bind_to_device, read_ahead].
3113+
show_econnreset, bind_to_device, read_ahead,
3114+
keepcnt, keepidle, keepintvl, user_timeout].
31053115

31063116
-doc false.
31073117
connect_options(Opts, Mod) ->
@@ -3197,7 +3207,8 @@ listen_options() ->
31973207
header, active, packet, buffer, mode, deliver, backlog, ipv6_v6only,
31983208
exit_on_close, high_watermark, low_watermark, high_msgq_watermark,
31993209
low_msgq_watermark, send_timeout, send_timeout_close, delay_send,
3200-
packet_size, raw, show_econnreset, bind_to_device, read_ahead].
3210+
packet_size, raw, show_econnreset, bind_to_device, read_ahead,
3211+
keepcnt, keepidle, keepintvl, user_timeout].
32013212

32023213
-doc false.
32033214
listen_options(Opts, Mod) ->

lib/kernel/src/inet_int.hrl

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -177,8 +177,13 @@
177177
-define(INET_OPT_RECVTTL, 47).
178178
-define(TCP_OPT_NOPUSH, 48).
179179
-define(INET_LOPT_TCP_READ_AHEAD, 49).
180-
-define(INET_OPT_NON_BLOCK_SEND, 50).
180+
-define(INET_LOPT_NON_BLOCK_SEND, 50).
181+
-define(TCP_OPT_KEEPCNT, 51).
182+
-define(TCP_OPT_KEEPIDLE, 52).
183+
-define(TCP_OPT_KEEPINTVL, 53).
184+
-define(TCP_OPT_USER_TIMEOUT, 54).
181185
-define(INET_OPT_DEBUG, 99).
186+
182187
% Specific SCTP options: separate range:
183188
-define(SCTP_OPT_RTOINFO, 100).
184189
-define(SCTP_OPT_ASSOCINFO, 101).

0 commit comments

Comments
 (0)