Skip to content

Commit 8bc9221

Browse files
committed
[kernel|test] Tweaked the 19482 test case(s)
1 parent 9e6f674 commit 8bc9221

File tree

1 file changed

+112
-46
lines changed

1 file changed

+112
-46
lines changed

lib/kernel/test/socket_SUITE.erl

Lines changed: 112 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -13246,7 +13246,7 @@ do_otp19482_simple_multi(#{iov_max := IOVMax,
1324613246
Clients),
1324713247

1324813248
?P("~w -> await client success", [?FUNCTION_NAME]),
13249-
case do_otp19482_simple_multi_await_client_success(Clients) of
13249+
case do_otp19482_simple_multi_await_client_completion(Clients) of
1325013250
{_, []} ->
1325113251
?P("~w -> all clients successful - terminate clients",
1325213252
[?FUNCTION_NAME]),
@@ -13286,22 +13286,30 @@ do_otp19482_simple_multi(#{iov_max := IOVMax,
1328613286
end.
1328713287

1328813288

13289-
do_otp19482_simple_multi_await_client_success(Clients) ->
13290-
do_otp19482_simple_multi_await_client_success(Clients, [], []).
13289+
do_otp19482_simple_multi_await_client_completion(Clients) ->
13290+
do_otp19482_simple_multi_await_client_completion(Clients, [], []).
1329113291

13292-
do_otp19482_simple_multi_await_client_success([], Success, Failure) ->
13292+
do_otp19482_simple_multi_await_client_completion([], Success, Failure) ->
1329313293
?P("~w -> done when: "
1329413294
"~n Success: ~p"
1329513295
"~n Failure: ~p", [?FUNCTION_NAME, Success, Failure]),
1329613296
{Success, Failure};
13297-
do_otp19482_simple_multi_await_client_success(Clients, Success, Failure) ->
13297+
do_otp19482_simple_multi_await_client_completion(Clients, Success, Failure) ->
1329813298
receive
1329913299
{Pid, done} ->
1330013300
Clients2 = lists:delete(Pid, Clients),
13301-
?P("~w -> -> client ~p done (~w)", [?FUNCTION_NAME, Pid, length(Clients)]),
13302-
do_otp19482_simple_multi_await_client_success(Clients2,
13303-
[Pid|Success],
13304-
Failure);
13301+
?P("~w -> -> client ~p done (~w)", [?FUNCTION_NAME,
13302+
Pid, length(Clients)]),
13303+
do_otp19482_simple_multi_await_client_completion(Clients2,
13304+
[Pid|Success],
13305+
Failure);
13306+
13307+
{'EXIT', _Pid, {timetrap_timeout, _, _}} ->
13308+
?P("~w -> -> timetrap timeout when"
13309+
"~n Remaining clients: ~w)", [?FUNCTION_NAME,
13310+
length(Clients)]),
13311+
exit(timetrap_timeout);
13312+
1330513313
{'EXIT', Pid, Reason} ->
1330613314
?P("~w -> received unexpected exit: "
1330713315
"~n Pid: ~p"
@@ -13310,19 +13318,22 @@ do_otp19482_simple_multi_await_client_success(Clients, Success, Failure) ->
1331013318
"~n Clients: ~p"
1331113319
"~n length(Success): ~p"
1331213320
"~n length(Failure): ~p",
13313-
[?FUNCTION_NAME, Pid, Reason, Clients, length(Success), length(Failure)]),
13321+
[?FUNCTION_NAME,
13322+
Pid, Reason, Clients, length(Success), length(Failure)]),
1331413323
case lists:delete(Pid, Clients) of
1331513324
Clients ->
13316-
?P("~w -> ~p not a client", [?FUNCTION_NAME, Pid]),
13317-
do_otp19482_simple_multi_await_client_success(Clients,
13318-
Success,
13319-
Failure);
13325+
?P("~w -> ~p was not a client", [?FUNCTION_NAME, Pid]),
13326+
do_otp19482_simple_multi_await_client_completion(Clients,
13327+
Success,
13328+
Failure);
1332013329
Clients2 ->
13321-
?P("~w -> ~p a client", [?FUNCTION_NAME, Pid]),
13322-
do_otp19482_simple_multi_await_client_success(Clients2,
13323-
Success,
13324-
[Pid|Failure])
13330+
?P("~w -> ~p was a client", [?FUNCTION_NAME, Pid]),
13331+
do_otp19482_simple_multi_await_client_completion(
13332+
Clients2,
13333+
Success,
13334+
[Pid|Failure])
1332513335
end
13336+
1332613337
end.
1332713338

1332813339
do_otp19482_simple_multi_collect_procs(undefined, []) ->
@@ -13412,13 +13423,21 @@ otp19482_simple_multi_acceptor_init(Parent, LSA, Num) ->
1341213423
ok
1341313424
end,
1341413425

13415-
otp19482_simple_multi_acceptor_loop(Parent, LSock, undefined, 1, Num).
13426+
State = #{parent => Parent,
13427+
lsock => LSock,
13428+
ref => undefined,
13429+
next_id => 1,
13430+
data_sz => Num},
13431+
otp19482_simple_multi_acceptor_loop(State).
1341613432

1341713433

1341813434
-define(SELECT_RES(Tag,Ref), {select, {select_info, (Tag), (Ref)}}).
1341913435
-define(COMPLETION_RES(Tag,Ref), {completion, {completion_info, (Tag), (Ref)}}).
1342013436

13421-
otp19482_simple_multi_acceptor_loop(Parent, LSock, undefined = Ref0, ID, Num) ->
13437+
otp19482_simple_multi_acceptor_loop(#{lsock := LSock,
13438+
ref := undefined,
13439+
next_id := ID,
13440+
data_sz := Num} = State) ->
1342213441
?P("A(undefined,~w) -> try accept", [ID]),
1342313442
case socket:accept(LSock, nowait) of
1342413443
{ok, ASock} ->
@@ -13428,16 +13447,21 @@ otp19482_simple_multi_acceptor_loop(Parent, LSock, undefined = Ref0, ID, Num) ->
1342813447
?P("A(undefined,~w) -> handler ~p started", [ID, Handler]),
1342913448
ok = otp19482_simple_multi_transfer_ownership(ASock, Handler),
1343013449
Handler ! {self(), continue, ASock},
13431-
otp19482_simple_multi_acceptor_loop(Parent, LSock, Ref0, ID+1, Num);
13450+
NewState = State#{next_id => ID+1,
13451+
Handler => ID,
13452+
ID => Handler},
13453+
otp19482_simple_multi_acceptor_loop(NewState);
1343213454

1343313455
?SELECT_RES(accept, Ref) ->
1343413456
?P("A(undefined,~w) -> select: "
1343513457
"~n Ref: ~p", [ID, Ref]),
13436-
otp19482_simple_multi_acceptor_loop(Parent, LSock, Ref, ID, Num);
13458+
NewState = State#{ref => Ref},
13459+
otp19482_simple_multi_acceptor_loop(NewState);
1343713460
?COMPLETION_RES(accept, Ref) ->
1343813461
?P("A(undefined,~w) -> completion: "
1343913462
"~n Ref: ~p", [ID, Ref]),
13440-
otp19482_simple_multi_acceptor_loop(Parent, LSock, Ref, ID, Num);
13463+
NewState = State#{ref => Ref},
13464+
otp19482_simple_multi_acceptor_loop(NewState);
1344113465

1344213466
{error, Reason} ->
1344313467
?P("A(undefined,~w) -> failure: "
@@ -13446,57 +13470,93 @@ otp19482_simple_multi_acceptor_loop(Parent, LSock, undefined = Ref0, ID, Num) ->
1344613470

1344713471
end;
1344813472

13449-
otp19482_simple_multi_acceptor_loop(Parent, LSock, Ref, ID, Num) ->
13450-
?P("A(~p,~w) -> await socket (accept) messages", [Ref, ID]),
13473+
otp19482_simple_multi_acceptor_loop(#{parent := Parent,
13474+
lsock := LSock,
13475+
ref := Ref,
13476+
next_id := NextID,
13477+
data_sz := Num} = State) ->
13478+
?P("A(~p,~w) -> await socket (accept) messages", [Ref, NextID]),
1345113479
receive
1345213480
{'$socket', LSock, select, Ref} ->
1345313481
?P("A(~p,~w) -> select message received - try accept again",
13454-
[Ref, ID]),
13482+
[Ref, NextID]),
1345513483
case socket:accept(LSock, Ref) of
1345613484
{ok, ASock} ->
1345713485
?P("A(~p,~w) -> accepted: "
13458-
"~n ASock: ~p", [Ref, ID, ASock]),
13459-
Handler = otp19482_simple_multi_handler_start(ID, Num),
13460-
?P("A(~p,~w) -> handler ~p started", [Ref, ID, Handler]),
13486+
"~n ASock: ~p", [Ref, NextID, ASock]),
13487+
Handler = otp19482_simple_multi_handler_start(NextID, Num),
13488+
?P("A(~p,~w) -> handler ~p started",
13489+
[Ref, NextID, Handler]),
1346113490
ok = otp19482_simple_multi_transfer_ownership(ASock,
1346213491
Handler),
1346313492
Handler ! {self(), continue, ASock},
13464-
otp19482_simple_multi_acceptor_loop(Parent,
13465-
LSock, undefined, ID+1,
13466-
Num);
13493+
NewState = State#{next_id => NextID+1,
13494+
ref => undefined,
13495+
Handler => NextID,
13496+
NextID => Handler},
13497+
otp19482_simple_multi_acceptor_loop(NewState);
13498+
1346713499
?SELECT_RES(accept, NewRef) ->
1346813500
?P("A(~p,~w) -> select: "
13469-
"~n NewRef: ~p", [Ref, ID, NewRef]),
13470-
otp19482_simple_multi_acceptor_loop(Parent,
13471-
LSock, NewRef, ID,
13472-
Num);
13501+
"~n NewRef: ~p", [Ref, NextID, NewRef]),
13502+
otp19482_simple_multi_acceptor_loop(State);
1347313503

1347413504
{error, Reason} ->
1347513505
?P("A(~p,~w) -> failure: "
13476-
"~n Reason: ~p", [Ref, ID, Reason]),
13506+
"~n Reason: ~p", [Ref, NextID, Reason]),
1347713507
exit({accept_fail, Reason})
1347813508
end;
1347913509

1348013510
{'$socket', LSock, completion, {Ref, {ok, ASock}}} ->
1348113511
?P("A(~p,~w) -> completion message received - with success:"
13482-
"~n ASock: ~p", [Ref, ID, ASock]),
13483-
Handler = otp19482_simple_multi_handler_start(ID, Num),
13484-
?P("A(~p,~w) -> handler ~p started", [Ref, ID, Handler]),
13512+
"~n ASock: ~p", [Ref, NextID, ASock]),
13513+
Handler = otp19482_simple_multi_handler_start(NextID, Num),
13514+
?P("A(~p,~w) -> handler ~p started", [Ref, NextID, Handler]),
1348513515
ok = otp19482_simple_multi_transfer_ownership(ASock, Handler),
1348613516
Handler ! {self(), continue, ASock},
13487-
otp19482_simple_multi_acceptor_loop(Parent,
13488-
LSock, undefined, ID+1,
13489-
Num);
13517+
NewState = State#{next_id => NextID+1,
13518+
ref => undefined,
13519+
Handler => NextID,
13520+
NextID => Handler},
13521+
otp19482_simple_multi_acceptor_loop(NewState);
1349013522

1349113523
{'$socket', LSock, completion, {Ref, ERROR}} ->
1349213524
?P("A(~p,~w) -> completion message received - with error:"
13493-
"~n ERROR: ~p", [Ref, ID, ERROR]),
13525+
"~n ERROR: ~p", [Ref, NextID, ERROR]),
1349413526
exit(ERROR);
1349513527

1349613528
{Parent, terminate} ->
13497-
?P("A(~p,~w) -> terminate", [Ref, ID]),
13529+
?P("A(~p,~w) -> terminate", [Ref, NextID]),
1349813530
_ = socket:close(LSock),
13499-
exit(normal)
13531+
exit(normal);
13532+
13533+
{'EXIT', Pid, normal} ->
13534+
case maps:get(Pid, State, undefined) of
13535+
undefined ->
13536+
?P("A(~p,~w) -> unknown process ~p terminated normally",
13537+
[Ref, NextID, Pid]),
13538+
otp19482_simple_multi_acceptor_loop(State);
13539+
ID when is_integer(ID) ->
13540+
?P("A(~p,~w) -> handler ~p (~w) terminated normally",
13541+
[Ref, NextID, Pid, ID]),
13542+
NewState = maps:remove(ID, maps:remove(Pid, State)),
13543+
otp19482_simple_multi_acceptor_loop(NewState)
13544+
end;
13545+
13546+
{'EXIT', Pid, Reason} ->
13547+
case maps:get(Pid, State, undefined) of
13548+
undefined ->
13549+
?P("A(~p,~w) -> unknown process ~p terminated: "
13550+
"~n ~p",
13551+
[Ref, NextID, Pid, Reason]),
13552+
otp19482_simple_multi_acceptor_loop(State);
13553+
ID when is_integer(ID) ->
13554+
?P("A(~p,~w) -> handler ~p (~w) terminated: "
13555+
"~n ~p",
13556+
[Ref, NextID, Pid, ID, Reason]),
13557+
exit({handler_faiulure, Pid, ID, Reason})
13558+
end
13559+
1350013560
end.
1350113561

1350213562
otp19482_simple_multi_transfer_ownership(Sock, Pid) ->
@@ -13665,6 +13725,12 @@ otp19482_simple_multi_client_recv_loop(Sock, ID, Num) ->
1366513725
[ID, byte_size(Data)]),
1366613726
otp19482_simple_multi_client_recv_loop(Sock,
1366713727
ID, Num - byte_size(Data));
13728+
13729+
{error, {Reason, RestData}} when is_binary(RestData) ->
13730+
?P("C[~w] recv-loop -> receive failure:"
13731+
"~n Reason: ~p"
13732+
"~n sz(RestData): ~w", [ID, Reason, byte_size(RestData)]),
13733+
?FAIL({recv_failure, Reason});
1366813734
{error, Reason} ->
1366913735
?P("C[~w] recv-loop -> receive failure:"
1367013736
"~n Reason: ~p", [ID, Reason]),

0 commit comments

Comments
 (0)