Skip to content

Commit 5187d4e

Browse files
committed
Merge branch 'bmk/esock/20250319/post_merge_fixup/OTP-19469'
2 parents 18fd9c5 + b0c6232 commit 5187d4e

File tree

5 files changed

+145
-60
lines changed

5 files changed

+145
-60
lines changed

erts/emulator/nifs/win32/win_socket_asyncio.c

Lines changed: 26 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -9433,10 +9433,32 @@ ERL_NIF_TERM esaio_completion_recv_partial_part(ErlNifEnv* env,
94339433
ssize_t read,
94349434
DWORD flags)
94359435
{
9436-
/* This is just a "placeholder". Is this really all we need to do? */
9437-
return esaio_completion_recv_partial_done(env, descP,
9438-
opEnv, opDataP,
9439-
read, flags);
9436+
ERL_NIF_TERM sockRef = opDataP->sockRef;
9437+
ERL_NIF_TERM data;
9438+
9439+
ESOCK_CNT_INC(env, descP, sockRef,
9440+
esock_atom_read_pkg, &descP->readPkgCnt, 1);
9441+
ESOCK_CNT_INC(env, descP, sockRef,
9442+
esock_atom_read_byte, &descP->readByteCnt, read);
9443+
9444+
if (read > descP->readPkgMax)
9445+
descP->readPkgMax = read;
9446+
9447+
/* This transfers "ownership" of the *allocated* binary to an
9448+
* erlang term (no need for an explicit free).
9449+
*/
9450+
data = MKBIN(opEnv, &opDataP->buf);
9451+
data = MKSBIN(opEnv, data, 0, read);
9452+
9453+
(void) flags;
9454+
9455+
SSDBG( descP,
9456+
("WIN-ESAIO",
9457+
"esaio_completion_recv_partial_part(%T) {%d} -> done\r\n",
9458+
sockRef, descP->sock) );
9459+
9460+
return MKT2(env, esock_atom_more, data);
9461+
94409462
}
94419463

94429464

lib/kernel/src/gen_tcp_socket.erl

Lines changed: 35 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
%%
22
%% %CopyrightBegin%
33
%%
4-
%% Copyright Ericsson AB 2019-2024. All Rights Reserved.
4+
%% Copyright Ericsson AB 2019-2025. 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.
@@ -60,6 +60,9 @@
6060
%% -define(DBG(T),
6161
%% erlang:display({{self(), ?MODULE, ?LINE, ?FUNCTION_NAME}, T})).
6262

63+
%% -define(P(F), ?P(F, [])).
64+
%% -define(P(F, A), d("~w:~w(~w) -> " ++ F, [?MODULE, ?FUNCTION_NAME, ?LINE | A])).
65+
6366

6467
%% -------------------------------------------------------------------------
6568

@@ -879,20 +882,23 @@ socket_sendv(Socket, Data, Timeout) ->
879882
end.
880883

881884
-compile({inline, [socket_send_error/1]}).
882-
socket_send_error(Result) ->
883-
case Result of
884-
{error, epipe} -> {error, econnreset};
885-
{error, Reason} when is_atom(Reason) -> Result;
886-
{error, #{info := Reason}} ->
887-
case Reason of
888-
netname_deleted ->
889-
{error, econnreset};
890-
too_many_cmds ->
891-
{error, closed};
892-
_ ->
893-
Result
894-
end
895-
end.
885+
socket_send_error({error, Reason}) ->
886+
{error, socket_send_reason(Reason)}.
887+
888+
-compile({inline, [socket_send_reason/1]}).
889+
socket_send_reason({completion_status, CS}) ->
890+
socket_send_reason(CS);
891+
socket_send_reason(#{info := Info}) ->
892+
socket_send_reason(Info);
893+
socket_send_reason(epipe) ->
894+
econnreset;
895+
socket_send_reason(netname_deleted) ->
896+
econnreset;
897+
socket_send_reason(too_many_cmds) ->
898+
closed;
899+
socket_send_reason(Reason) ->
900+
Reason.
901+
896902

897903

898904
-compile({inline, [socket_recv/2]}).
@@ -2042,7 +2048,7 @@ handle_event(
20422048
#recv{info = ?completion_info(CompletionRef)} = _State,
20432049
{#params{socket = Socket} = P, D}) ->
20442050
%% ?DBG(['abort msg', {reason, Reason}]),
2045-
handle_recv_error(P, D, [], completion_status_reason(Reason));
2051+
handle_recv_error(P, D, [], Reason);
20462052

20472053
handle_event(
20482054
{timeout, recv}, recv, #recv{info = Info},
@@ -2312,6 +2318,10 @@ handle_recv(P, #{buffer := Buffer} = D, ActionsR, CS) ->
23122318
handle_recv(
23132319
P, D, ActionsR, buffer(Data, Buffer),
23142320
BufferSize + byte_size(Data), recv);
2321+
{more, <<Data/binary>>} ->
2322+
handle_recv(
2323+
P, D, ActionsR, buffer(Data, Buffer),
2324+
BufferSize + byte_size(Data), recv);
23152325
{error, {Reason, <<Data/binary>>}} ->
23162326
handle_recv(
23172327
P, D, ActionsR, buffer(Data, Buffer),
@@ -2670,14 +2680,22 @@ handle_send_error(#params{socket = Socket} = P, D_0, State, From, Reason) ->
26702680
end.
26712681

26722682
%% -> CuratedReason
2683+
curated_error_reason(D, {completion_status, CS}) ->
2684+
curated_error_reason(D, CS);
2685+
curated_error_reason(D, #{info := Info}) ->
2686+
curated_error_reason(D, Info);
26732687
curated_error_reason(D, Reason) ->
26742688
if
26752689
Reason =:= econnreset;
2676-
Reason =:= econnaborted ->
2690+
Reason =:= econnaborted;
2691+
Reason =:= netname_deleted;
2692+
Reason =:= epipe ->
26772693
case maps:get(show_econnreset, D) of
26782694
true -> econnreset;
26792695
false -> closed
26802696
end;
2697+
Reason =:= too_many_commands ->
2698+
closed;
26812699
true ->
26822700
Reason
26832701
end.

lib/kernel/src/socket.erl

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -392,6 +392,9 @@ server(Addr, Port) ->
392392
%% -define(DBG(T),
393393
%% erlang:display({{self(), ?MODULE, ?LINE, ?FUNCTION_NAME}, T})).
394394

395+
%% -define(P(F), ?P(F, [])).
396+
%% -define(P(F, A), p("~w:~w(~w) -> " ++ F, [?MODULE, ?FUNCTION_NAME, ?LINE | A])).
397+
395398
%% Also in prim_socket
396399
-define(REGISTRY, socket_registry).
397400

@@ -6904,8 +6907,8 @@ f(F, A) ->
69046907
%% [YYYY, MM, DD, Hour, Min, Sec] ++ ArgsExtra),
69056908
%% lists:flatten(FormatDate).
69066909

6907-
%% p(F) ->
6908-
%% p(F, []).
6910+
%% %% p(F) ->
6911+
%% %% p(F, []).
69096912

69106913
%% p(F, A) ->
69116914
%% p(get(sname), F, A).

lib/kernel/test/gen_tcp_misc_SUITE.erl

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -29,15 +29,17 @@
2929
%%
3030
%% (cd /mnt/c/$LOCAL_TESTS/26/kernel_test/ && $ERL_TOP/bin/win32/erl.exe -sname kernel-26-tester -pa c:$LOCAL_TESTS/26/test_server)
3131
%% application:set_env(kernel, test_inet_backends, true).
32+
%%
3233
%% S = fun() -> ts:run(kernel, gen_tcp_misc_SUITE, [batch]) end.
3334
%% S = fun(SUITE) -> ts:run(kernel, SUITE, [batch]) end.
34-
%% S = fun() -> ct:run_test([{suite, gen_tcp_misc_SUITE}]) end.
35-
%% S = fun(SUITE) -> ct:run_test([{suite, SUITE}]) end.
3635
%% G = fun(GROUP) -> ts:run(kernel, gen_tcp_misc_SUITE, {group, GROUP}, [batch]) end.
3736
%% G = fun(SUITE, GROUP) -> ts:run(kernel, SUITE, {group, GROUP}, [batch]) end.
37+
%% T = fun(TC) -> ts:run(kernel, gen_tcp_misc_SUITE, TC, [batch]) end.
38+
%%
39+
%% S = fun() -> ct:run_test([{suite, gen_tcp_misc_SUITE}]) end.
40+
%% S = fun(SUITE) -> ct:run_test([{suite, SUITE}]) end.
3841
%% G = fun(GROUP) -> ct:run_test([{suite, gen_tcp_misc_SUITE}, {group, GROUP}]) end.
3942
%% G = fun(SUITE, GROUP) -> ct:run_test([{suite, SUITE}, {group, GROUP}]) end.
40-
%% T = fun(TC) -> ts:run(kernel, gen_tcp_misc_SUITE, TC, [batch]) end.
4143
%% T = fun(TC) -> ct:run_test([{suite, gen_tcp_misc_SUITE}, {testcase, TC}]) end.
4244
%% T = fun(TC) -> ct:run_test([{suite, gen_tcp_misc_SUITE}, {group, inet_backend_socket}, {testcase, TC}]) end.
4345
%% T = fun(S, TC) -> ct:run_test([{suite, S}, {testcase, TC}]) end.
@@ -2045,12 +2047,16 @@ do_show_econnreset_active(Config, Addr) ->
20452047
{ok, S1} = gen_tcp:accept(L1),
20462048
ok = gen_tcp:close(L1),
20472049
ok = inet:setopts(Client1, [{linger, {true, 0}}]),
2050+
%% ok = inet:setopts(S1, [{debug, true}]),
2051+
?P("close client(1) socket"),
20482052
ok = gen_tcp:close(Client1),
2053+
?P("await accepted socket econnreset tcp-error message"),
20492054
receive
20502055
{tcp_error, S1, econnreset} ->
2056+
?P("received accepted socket expected tcp-error message (econnreset)"),
20512057
receive
20522058
{tcp_closed, S1} ->
2053-
?P("done"),
2059+
?P("received accepted socket tcp-closed message - done"),
20542060
ok;
20552061
Other1 ->
20562062
?P("UNEXPECTED (expected closed):"

0 commit comments

Comments
 (0)