Skip to content

Commit 0131a3e

Browse files
committed
Merge branch 'raimo/mptcp-maint/OTP-19857' into maint
* raimo/mptcp-maint/OTP-19857: Update preloaded Implement TCP_KEEP* and TCP_USER_TIMEOUT for `gen_tcp` Implement TCP_USER_TIMEOUT for `socket` Implement `mptcp` for `gen_tcp_socket` compatibility module
2 parents 3b1a2be + 3892da4 commit 0131a3e

File tree

11 files changed

+240
-19
lines changed

11 files changed

+240
-19
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:
@@ -9385,6 +9433,30 @@ static ErlDrvSSizeT inet_fill_opts(inet_descriptor* desc,
93859433
put_int32(0, ptr);
93869434
continue;
93879435
#endif
9436+
#if defined(TCP_KEEPCNT)
9437+
case TCP_OPT_KEEPCNT:
9438+
proto = IPPROTO_TCP;
9439+
type = TCP_KEEPCNT;
9440+
break;
9441+
#endif
9442+
#if defined(TCP_KEEPIDLE)
9443+
case TCP_OPT_KEEPIDLE:
9444+
proto = IPPROTO_TCP;
9445+
type = TCP_KEEPIDLE;
9446+
break;
9447+
#endif
9448+
#if defined(TCP_KEEPINTVL)
9449+
case TCP_OPT_KEEPINTVL:
9450+
proto = IPPROTO_TCP;
9451+
type = TCP_KEEPINTVL;
9452+
break;
9453+
#endif
9454+
#if defined(TCP_USER_TIMEOUT)
9455+
case TCP_OPT_USER_TIMEOUT:
9456+
proto = IPPROTO_TCP;
9457+
type = TCP_USER_TIMEOUT;
9458+
break;
9459+
#endif
93889460

93899461
#if defined(HAVE_MULTICAST_SUPPORT) && defined(IPPROTO_IP)
93909462
case UDP_OPT_MULTICAST_TTL:

erts/emulator/nifs/common/prim_socket_int.h

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -567,6 +567,11 @@ extern BOOLEAN_T esock_getopt_int(SOCKET sock,
567567
int opt,
568568
int* valP);
569569

570+
extern BOOLEAN_T esock_getopt_uint(SOCKET sock,
571+
int level,
572+
int opt,
573+
unsigned int *valP);
574+
570575

571576
/* ** Socket Registry functions *** */
572577
extern void esock_send_reg_add_msg(ErlNifEnv* env,

erts/emulator/nifs/common/prim_socket_nif.c

Lines changed: 84 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1310,6 +1310,10 @@ static ERL_NIF_TERM esock_getopt_int_opt(ErlNifEnv* env,
13101310
ESockDescriptor* descP,
13111311
int level,
13121312
int opt);
1313+
static ERL_NIF_TERM esock_getopt_uint_opt(ErlNifEnv* env,
1314+
ESockDescriptor* descP,
1315+
int level,
1316+
int opt);
13131317
static ERL_NIF_TERM esock_getopt_size_opt(ErlNifEnv* env,
13141318
ESockDescriptor* descP,
13151319
int level,
@@ -1719,6 +1723,11 @@ static ERL_NIF_TERM esock_setopt_int_opt(ErlNifEnv* env,
17191723
int level,
17201724
int opt,
17211725
ERL_NIF_TERM eVal);
1726+
static ERL_NIF_TERM esock_setopt_uint_opt(ErlNifEnv* env,
1727+
ESockDescriptor* descP,
1728+
int level,
1729+
int opt,
1730+
ERL_NIF_TERM eVal);
17221731
#if (defined(SO_RCVTIMEO) || defined(SO_SNDTIMEO)) \
17231732
&& defined(ESOCK_USE_RCVSNDTIMEO)
17241733
static ERL_NIF_TERM esock_setopt_timeval_opt(ErlNifEnv* env,
@@ -3762,7 +3771,14 @@ static struct ESockOpt optLevelTCP[] =
37623771
#endif
37633772
&esock_atom_nopush},
37643773
{0, NULL, NULL, &esock_atom_syncnt},
3765-
{0, NULL, NULL, &esock_atom_user_timeout}
3774+
{
3775+
#ifdef TCP_USER_TIMEOUT
3776+
TCP_USER_TIMEOUT,
3777+
esock_setopt_uint_opt, esock_getopt_uint_opt,
3778+
#else
3779+
0, NULL, NULL,
3780+
#endif
3781+
&esock_atom_user_timeout}
37663782

37673783
};
37683784

@@ -8302,6 +8318,31 @@ ERL_NIF_TERM esock_setopt_int_opt(ErlNifEnv* env,
83028318

83038319

83048320

8321+
/* esock_setopt_uint_opt - set an option that has an unsigned integer value
8322+
*/
8323+
8324+
static
8325+
ERL_NIF_TERM esock_setopt_uint_opt(ErlNifEnv* env,
8326+
ESockDescriptor* descP,
8327+
int level,
8328+
int opt,
8329+
ERL_NIF_TERM eVal)
8330+
{
8331+
ERL_NIF_TERM result;
8332+
unsigned int val;
8333+
8334+
if (GET_UINT(env, eVal, &val)) {
8335+
result =
8336+
esock_setopt_level_opt(env, descP, level, opt,
8337+
&val, sizeof(val));
8338+
} else {
8339+
result = esock_make_invalid(env, esock_atom_value);
8340+
}
8341+
return result;
8342+
}
8343+
8344+
8345+
83058346
/* esock_setopt_str_opt - set an option that has an string value
83068347
*/
83078348

@@ -9908,6 +9949,24 @@ ERL_NIF_TERM esock_getopt_int_opt(ErlNifEnv* env,
99089949

99099950

99109951

9952+
/* esock_getopt_uint_opt - get an unsigned integer option
9953+
*/
9954+
static
9955+
ERL_NIF_TERM esock_getopt_uint_opt(ErlNifEnv* env,
9956+
ESockDescriptor* descP,
9957+
int level,
9958+
int opt)
9959+
{
9960+
unsigned int val;
9961+
9962+
if (! esock_getopt_uint(descP->sock, level, opt, &val))
9963+
return esock_make_error_errno(env, sock_errno());
9964+
9965+
return esock_make_ok2(env, MKUI(env, val));
9966+
}
9967+
9968+
9969+
99119970
/* esock_getopt_int - get an integer option
99129971
*/
99139972
extern
@@ -9932,6 +9991,30 @@ BOOLEAN_T esock_getopt_int(SOCKET sock,
99329991

99339992

99349993

9994+
/* esock_getopt_uint - get an unsigned integer option
9995+
*/
9996+
extern
9997+
BOOLEAN_T esock_getopt_uint(SOCKET sock,
9998+
int level,
9999+
int opt,
10000+
unsigned int *valP)
10001+
{
10002+
unsigned int val = 0;
10003+
SOCKOPTLEN_T valSz = sizeof(val);
10004+
10005+
#ifdef __WIN32__
10006+
if (sock_getopt(sock, level, opt, (char*) &val, &valSz) != 0)
10007+
#else
10008+
if (sock_getopt(sock, level, opt, &val, &valSz) != 0)
10009+
#endif
10010+
return FALSE;
10011+
10012+
*valP = val;
10013+
return TRUE;
10014+
}
10015+
10016+
10017+
993510018
static
993610019
ERL_NIF_TERM esock_getopt_size_opt(ErlNifEnv* env,
993710020
ESockDescriptor* descP,

erts/preloaded/ebin/prim_inet.beam

152 Bytes
Binary file not shown.

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/doc/guides/socket_usage.md

Lines changed: 13 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -626,16 +626,19 @@ _Table: ipv6 options_
626626
[](){: #socket_options_tcp }
627627
Options for level `tcp`:
628628

629-
| Option Name | Value Type | Set | Get | Other Requirements and comments |
630-
| ----------- | ---------- | --- | --- | -------------------------------------------------------------------------------------------------------- |
631-
| congestion | string() | yes | yes | none |
632-
| cork | boolean() | yes | yes | 'nopush' one some platforms (FreeBSD) |
633-
| keepcnt | integer() | yes | yes | On Windows (at least), it is illegal to set to a value greater than 255. |
634-
| keepidle | integer() | yes | yes | none |
635-
| keepintvl | integer() | yes | yes | none |
636-
| maxseg | integer() | yes | yes | Set not allowed on all platforms. |
637-
| nodelay | boolean() | yes | yes | none |
638-
| nopush | boolean() | yes | yes | 'cork' on some platforms (Linux). On Darwin this has a different meaning than on, for instance, FreeBSD. |
629+
| Option Name | Value Type | Set | Get | Other Requirements and comments |
630+
| ------------ | -------------- | --- | --- | ---------------------------------------------------- |
631+
| congestion | string() | yes | yes | none |
632+
| cork | boolean() | yes | yes | 'nopush' one some platforms (FreeBSD) |
633+
| keepcnt | integer() | yes | yes | On Windows (at least), it is illegal to set to |
634+
| | | | | a value greater than 255. |
635+
| keepidle | integer() | yes | yes | none |
636+
| keepintvl | integer() | yes | yes | none |
637+
| maxseg | integer() | yes | yes | Set not allowed on all platforms. |
638+
| nodelay | boolean() | yes | yes | none |
639+
| nopush | boolean() | yes | yes | 'cork' on some platforms (Linux). On Darwin this has |
640+
| | | | | a different meaning than on, for instance, FreeBSD. |
641+
| user_timeout | integer() >= 0 | yes | yes | none |
639642

640643
_Table: tcp options_
641644

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: 15 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1059,7 +1059,14 @@ split_open_opts([], OpenOpts, OtherOpts) ->
10591059
split_open_opts([{debug, _} = Opt|Opts], OpenOpts, OtherOpts) ->
10601060
split_open_opts(Opts, [Opt|OpenOpts], OtherOpts);
10611061
split_open_opts([Opt|Opts], OpenOpts, OtherOpts) ->
1062-
split_open_opts(Opts, OpenOpts, [Opt|OtherOpts]).
1062+
case Opt of
1063+
{debug, _} ->
1064+
split_open_opts(Opts, [Opt|OpenOpts], OtherOpts);
1065+
{protocol, _} ->
1066+
split_open_opts(Opts, [Opt|OpenOpts], OtherOpts);
1067+
_ ->
1068+
split_open_opts(Opts, OpenOpts, [Opt|OtherOpts])
1069+
end.
10631070

10641071

10651072
%%
@@ -1277,7 +1284,11 @@ socket_opts() ->
12771284

12781285
%%
12791286
%% Level: tcp
1280-
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},
12811292

12821293
%%
12831294
%% Level: ip
@@ -1585,9 +1596,10 @@ socket_open(Domain, #{fd := FD} = ExtraOpts, Extra) ->
15851596
%% ?DBG([{fd, FD}, {opts, Opts}]),
15861597
socket:open(FD, Opts);
15871598
socket_open(Domain, ExtraOpts, Extra) ->
1599+
Proto = maps:get(protocol, ExtraOpts, proto(Domain)),
15881600
Opts = maps:merge(Extra, ExtraOpts),
15891601
%% ?DBG([{domain, Domain}, {extra_opts, ExtraOpts}, {extra, Extra}]),
1590-
socket:open(Domain, stream, proto(Domain), Opts).
1602+
socket:open(Domain, stream, Proto, Opts).
15911603

15921604
proto(Domain) ->
15931605
case Domain of

0 commit comments

Comments
 (0)