Skip to content

Commit 731e75c

Browse files
author
Erlang/OTP
committed
Merge branch 'raimo/blocking-sctp-send/OTP-19061' into maint-26
* raimo/blocking-sctp-send/OTP-19061: Make gen_sctp:send blocking instead of returning ewouldblock # Conflicts: # erts/preloaded/ebin/prim_inet.beam
2 parents 63fb5e9 + 5538b74 commit 731e75c

File tree

4 files changed

+298
-165
lines changed

4 files changed

+298
-165
lines changed

erts/emulator/drivers/common/inet_drv.c

Lines changed: 77 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1338,6 +1338,7 @@ static int packet_inet_init(void);
13381338
static void packet_inet_stop(ErlDrvData);
13391339
static void packet_inet_command(ErlDrvData, char*, ErlDrvSizeT);
13401340
static void packet_inet_drv_input(ErlDrvData data, ErlDrvEvent event);
1341+
static void packet_inet_drv_output(ErlDrvData data, ErlDrvEvent event);
13411342
static ErlDrvData udp_inet_start(ErlDrvPort, char* command);
13421343
#ifdef HAVE_SCTP
13431344
static ErlDrvData sctp_inet_start(ErlDrvPort, char* command);
@@ -1359,10 +1360,10 @@ static struct erl_drv_entry udp_inet_driver_entry =
13591360
packet_inet_command,
13601361
#ifdef __WIN32__
13611362
packet_inet_event,
1362-
NULL,
1363+
NULL,
13631364
#else
13641365
packet_inet_drv_input,
1365-
NULL,
1366+
packet_inet_drv_output,
13661367
#endif
13671368
"udp_inet",
13681369
NULL,
@@ -1394,10 +1395,10 @@ static struct erl_drv_entry sctp_inet_driver_entry =
13941395
packet_inet_command,
13951396
#ifdef __WIN32__
13961397
packet_inet_event,
1397-
NULL,
1398+
NULL,
13981399
#else
13991400
packet_inet_drv_input,
1400-
NULL,
1401+
packet_inet_drv_output,
14011402
#endif
14021403
"sctp_inet",
14031404
NULL,
@@ -2590,9 +2591,35 @@ inet_reply_finish(inet_descriptor *desc, ErlDrvTermData *spec, int i) {
25902591
}
25912592

25922593
/* send:
2593-
** {inet_reply, S, ok[, CallerTag]}
2594+
** {inet_reply, S, CallerTag}
25942595
*/
2595-
static int inet_reply_ok(inet_descriptor* desc)
2596+
static int inet_reply_caller_ref(inet_descriptor* desc)
2597+
{
2598+
ErlDrvTermData
2599+
spec[2*LOAD_ATOM_CNT + LOAD_PORT_CNT + LOAD_TUPLE_CNT +
2600+
LOAD_EXT_CNT];
2601+
CallerRef *cref_p = &desc->caller_ref;
2602+
int i = 0;
2603+
2604+
if (is_not_internal_pid(desc->caller)) return 0; /* XXX what value for error? */
2605+
i = LOAD_ATOM(spec, i, am_inet_reply);
2606+
i = LOAD_PORT(spec, i, desc->dport);
2607+
if (cref_p->tag_buf != NULL) {
2608+
i = LOAD_EXT(spec, i, cref_p->tag_buf, cref_p->tag_len);
2609+
}
2610+
else {
2611+
i = LOAD_ATOM(spec, i, am_undefined);
2612+
}
2613+
i = LOAD_TUPLE(spec, i, 3);
2614+
2615+
ASSERT(sizeof(spec)/sizeof(*spec) >= i);
2616+
return erl_drv_send_term(desc->dport, desc->caller, spec, i);
2617+
}
2618+
2619+
/* send:
2620+
** {inet_reply, S, Atom[, CallerTag]}
2621+
*/
2622+
static int inet_reply_am(inet_descriptor* desc, ErlDrvTermData am)
25962623
{
25972624
ErlDrvTermData
25982625
spec[2*LOAD_ATOM_CNT + LOAD_PORT_CNT + LOAD_TUPLE_CNT +
@@ -2603,13 +2630,21 @@ static int inet_reply_ok(inet_descriptor* desc)
26032630

26042631
i = LOAD_ATOM(spec, i, am_inet_reply);
26052632
i = LOAD_PORT(spec, i, desc->dport);
2606-
i = LOAD_ATOM(spec, i, am_ok);
2633+
i = LOAD_ATOM(spec, i, am);
26072634
i = LOAD_TUPLE(spec, i, 3);
26082635
ASSERT(i == sizeof(spec)/sizeof(*spec) - LOAD_EXT_CNT);
26092636
done:
26102637
return inet_reply_finish(desc, spec, i);
26112638
}
26122639

2640+
/* send:
2641+
** {inet_reply, S, ok[, CallerTag]}
2642+
*/
2643+
static int inet_reply_ok(inet_descriptor* desc)
2644+
{
2645+
return inet_reply_am(desc, am_ok);
2646+
}
2647+
26132648
#ifdef HAVE_SCTP
26142649
static int inet_reply_ok_port(inet_descriptor* desc, ErlDrvTermData dport)
26152650
{
@@ -14447,7 +14482,7 @@ static void packet_inet_command(ErlDrvData e, char* buf, ErlDrvSizeT len)
1444714482
char* qtr;
1444814483
char* xerror;
1444914484
ErlDrvSizeT sz;
14450-
int code;
14485+
long code;
1445114486
inet_address other;
1445214487

1445314488
if (! init_caller(&desc->caller, &desc->caller_ref,
@@ -14505,7 +14540,8 @@ static void packet_inet_command(ErlDrvData e, char* buf, ErlDrvSizeT len)
1450514540
/* Now do the actual sending. NB: "flags" in "sendmsg" itself are NOT
1450614541
used: */
1450714542
code = sock_sendmsg(desc->s, &mhdr, 0);
14508-
goto check_result_code;
14543+
14544+
goto check_result_code;
1450914545
}
1451014546
#endif
1451114547
{
@@ -14585,16 +14621,30 @@ static void packet_inet_command(ErlDrvData e, char* buf, ErlDrvSizeT len)
1458514621

1458614622
#ifdef HAVE_SCTP
1458714623
check_result_code:
14588-
/* "code" analysis is the same for both SCTP and UDP cases above: */
14624+
/* "code" analysis is the same for both SCTP and UDP above,
14625+
* although ERRNO_BLOCK | EINTR never happens for UDP
14626+
*/
1458914627
#endif
1459014628
if (IS_SOCKET_ERROR(code)) {
14591-
int err = sock_errno();
14592-
inet_reply_error(desc, err);
14629+
int err = sock_errno();
14630+
if ((err != ERRNO_BLOCK) && (err != EINTR)) {
14631+
inet_reply_error(desc, err);
14632+
return;
14633+
}
14634+
else {
14635+
/* XXX if(! INET_IGNORED(INETP(desc))) */
14636+
sock_select(desc, (FD_WRITE|FD_CLOSE), 1);
14637+
set_busy_port(desc->port, 1);
14638+
/* XXX add_multi_timer(... desc->send_timeout, ...); */
14639+
inet_reply_caller_ref(desc);
14640+
return;
14641+
}
1459314642
}
14594-
else
14595-
inet_reply_ok(desc);
14596-
return;
14597-
14643+
else {
14644+
inet_reply_ok(desc);
14645+
return;
14646+
}
14647+
1459814648
return_einval:
1459914649
inet_reply_error(desc, EINVAL);
1460014650
return;
@@ -14621,6 +14671,17 @@ static void packet_inet_event(ErlDrvData e, ErlDrvEvent event)
1462114671
}
1462214672
}
1462314673

14674+
#endif /* #ifdef __WIN32__ */
14675+
14676+
#ifdef HAVE_UDP
14677+
static void packet_inet_drv_output(ErlDrvData e, ErlDrvEvent event)
14678+
{
14679+
inet_descriptor *desc = INETP((udp_descriptor *) e);
14680+
14681+
sock_select(desc, (FD_WRITE|FD_CLOSE), 0);
14682+
set_busy_port(desc->port, 0);
14683+
inet_reply_ok(desc);
14684+
}
1462414685
#endif
1462514686

1462614687
#ifdef HAVE_UDP

erts/preloaded/ebin/prim_inet.beam

416 Bytes
Binary file not shown.

erts/preloaded/src/prim_inet.erl

Lines changed: 32 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
%%
22
%% %CopyrightBegin%
33
%%
4-
%% Copyright Ericsson AB 2000-2023. All Rights Reserved.
4+
%% Copyright Ericsson AB 2000-2024. All Rights Reserved.
55
%%
66
%% Licensed under the Apache License, Version 2.0 (the "License");
77
%% you may not use this file except in compliance with the License.
@@ -564,25 +564,49 @@ peeloff(S, AssocId) ->
564564
%%
565565
send(S, Data, OptList) when is_port(S), is_list(OptList) ->
566566
?DBG_FORMAT("prim_inet:send(~p, _, ~p)~n", [S,OptList]),
567-
Mref = monitor(port, S),
568-
MrefBin = term_to_binary(Mref, [local]),
569-
MrefBinSize = byte_size(MrefBin),
570-
MrefBinSize = MrefBinSize band 16#FFFF,
567+
send(S, Data, OptList, monitor(port, S), make_ref()).
568+
569+
send(S, Data, OptList, Mref, Sref) ->
570+
SrefBin = term_to_binary(Sref, [local]),
571+
SrefBinSize = byte_size(SrefBin),
572+
SrefBinSize = SrefBinSize band 16#FFFF,
571573
try
572574
erlang:port_command(
573-
S, [<<MrefBinSize:16,MrefBin/binary>>, Data], OptList)
575+
S, [<<SrefBinSize:16,SrefBin/binary>>, Data], OptList)
574576
of
575577
false -> % Port busy when nosuspend option was passed
576578
?DBG_FORMAT("prim_inet:send() -> {error,busy}~n", []),
577579
{error,busy};
578580
true ->
579581
receive
580-
{inet_reply,S,Status,Mref} ->
582+
{inet_reply,S,Sref} ->
583+
%% This causes a wait even though nosuspend was used.
584+
%% It only happens when the OS send operation returns
585+
%% that it would block, which should only happen
586+
%% for SCTP (seqpacket), never for UDP (dgram)
587+
%%
588+
%% To fix this we probably need to pass down
589+
%% the nosuspend option to inform inet_drv
590+
%% to not use driver_select and send a late second reply.
591+
%%
592+
?DBG_FORMAT(
593+
"prim_inet:send(~p,,,) Waiting~n",
594+
[S]),
595+
receive
596+
{inet_reply,S,ok,Sref} ->
597+
send(S, Data, OptList, Mref, make_ref());
598+
{'DOWN',Mref,_,_,_Reason} ->
599+
?DBG_FORMAT(
600+
"prim_inet:send(~p,,,) 'DOWN' ~p~n",
601+
[S,_Reason]),
602+
{error,closed}
603+
end;
604+
{inet_reply,S,Status,Sref} ->
581605
demonitor(Mref, [flush]),
582606
Status;
583607
{'DOWN',Mref,_,_,_Reason} ->
584608
?DBG_FORMAT(
585-
"prim_inet:send_recv_reply(~p, _) 'DOWN' ~p~n",
609+
"prim_inet:send(~p,,,) 'DOWN' ~p~n",
586610
[S,_Reason]),
587611
{error,closed}
588612
end

0 commit comments

Comments
 (0)