@@ -13291,7 +13291,7 @@ do_otp19482_simple_multi(#{iov_max := IOVMax,
1329113291 Clients),
1329213292
1329313293 ?P("~w -> await client success", [?FUNCTION_NAME]),
13294- case do_otp19482_simple_multi_await_client_success (Clients) of
13294+ case do_otp19482_simple_multi_await_client_completion (Clients) of
1329513295 {_, []} ->
1329613296 ?P("~w -> all clients successful - terminate clients",
1329713297 [?FUNCTION_NAME]),
@@ -13331,22 +13331,30 @@ do_otp19482_simple_multi(#{iov_max := IOVMax,
1333113331 end.
1333213332
1333313333
13334- do_otp19482_simple_multi_await_client_success (Clients) ->
13335- do_otp19482_simple_multi_await_client_success (Clients, [], []).
13334+ do_otp19482_simple_multi_await_client_completion (Clients) ->
13335+ do_otp19482_simple_multi_await_client_completion (Clients, [], []).
1333613336
13337- do_otp19482_simple_multi_await_client_success ([], Success, Failure) ->
13337+ do_otp19482_simple_multi_await_client_completion ([], Success, Failure) ->
1333813338 ?P("~w -> done when: "
1333913339 "~n Success: ~p"
1334013340 "~n Failure: ~p", [?FUNCTION_NAME, Success, Failure]),
1334113341 {Success, Failure};
13342- do_otp19482_simple_multi_await_client_success (Clients, Success, Failure) ->
13342+ do_otp19482_simple_multi_await_client_completion (Clients, Success, Failure) ->
1334313343 receive
1334413344 {Pid, done} ->
1334513345 Clients2 = lists:delete(Pid, Clients),
13346- ?P("~w -> -> client ~p done (~w)", [?FUNCTION_NAME, Pid, length(Clients)]),
13347- do_otp19482_simple_multi_await_client_success(Clients2,
13348- [Pid|Success],
13349- Failure);
13346+ ?P("~w -> -> client ~p done (~w)", [?FUNCTION_NAME,
13347+ Pid, length(Clients)]),
13348+ do_otp19482_simple_multi_await_client_completion(Clients2,
13349+ [Pid|Success],
13350+ Failure);
13351+
13352+ {'EXIT', _Pid, {timetrap_timeout, _, _}} ->
13353+ ?P("~w -> -> timetrap timeout when"
13354+ "~n Remaining clients: ~w)", [?FUNCTION_NAME,
13355+ length(Clients)]),
13356+ exit(timetrap_timeout);
13357+
1335013358 {'EXIT', Pid, Reason} ->
1335113359 ?P("~w -> received unexpected exit: "
1335213360 "~n Pid: ~p"
@@ -13355,19 +13363,22 @@ do_otp19482_simple_multi_await_client_success(Clients, Success, Failure) ->
1335513363 "~n Clients: ~p"
1335613364 "~n length(Success): ~p"
1335713365 "~n length(Failure): ~p",
13358- [?FUNCTION_NAME, Pid, Reason, Clients, length(Success), length(Failure)]),
13366+ [?FUNCTION_NAME,
13367+ Pid, Reason, Clients, length(Success), length(Failure)]),
1335913368 case lists:delete(Pid, Clients) of
1336013369 Clients ->
13361- ?P("~w -> ~p not a client", [?FUNCTION_NAME, Pid]),
13362- do_otp19482_simple_multi_await_client_success (Clients,
13363- Success,
13364- Failure);
13370+ ?P("~w -> ~p was not a client", [?FUNCTION_NAME, Pid]),
13371+ do_otp19482_simple_multi_await_client_completion (Clients,
13372+ Success,
13373+ Failure);
1336513374 Clients2 ->
13366- ?P("~w -> ~p a client", [?FUNCTION_NAME, Pid]),
13367- do_otp19482_simple_multi_await_client_success(Clients2,
13368- Success,
13369- [Pid|Failure])
13375+ ?P("~w -> ~p was a client", [?FUNCTION_NAME, Pid]),
13376+ do_otp19482_simple_multi_await_client_completion(
13377+ Clients2,
13378+ Success,
13379+ [Pid|Failure])
1337013380 end
13381+
1337113382 end.
1337213383
1337313384do_otp19482_simple_multi_collect_procs(undefined, []) ->
@@ -13457,13 +13468,21 @@ otp19482_simple_multi_acceptor_init(Parent, LSA, Num) ->
1345713468 ok
1345813469 end,
1345913470
13460- otp19482_simple_multi_acceptor_loop(Parent, LSock, undefined, 1, Num).
13471+ State = #{parent => Parent,
13472+ lsock => LSock,
13473+ ref => undefined,
13474+ next_id => 1,
13475+ data_sz => Num},
13476+ otp19482_simple_multi_acceptor_loop(State).
1346113477
1346213478
1346313479-define(SELECT_RES(Tag,Ref), {select, {select_info, (Tag), (Ref)}}).
1346413480-define(COMPLETION_RES(Tag,Ref), {completion, {completion_info, (Tag), (Ref)}}).
1346513481
13466- otp19482_simple_multi_acceptor_loop(Parent, LSock, undefined = Ref0, ID, Num) ->
13482+ otp19482_simple_multi_acceptor_loop(#{lsock := LSock,
13483+ ref := undefined,
13484+ next_id := ID,
13485+ data_sz := Num} = State) ->
1346713486 ?P("A(undefined,~w) -> try accept", [ID]),
1346813487 case socket:accept(LSock, nowait) of
1346913488 {ok, ASock} ->
@@ -13473,16 +13492,21 @@ otp19482_simple_multi_acceptor_loop(Parent, LSock, undefined = Ref0, ID, Num) ->
1347313492 ?P("A(undefined,~w) -> handler ~p started", [ID, Handler]),
1347413493 ok = otp19482_simple_multi_transfer_ownership(ASock, Handler),
1347513494 Handler ! {self(), continue, ASock},
13476- otp19482_simple_multi_acceptor_loop(Parent, LSock, Ref0, ID+1, Num);
13495+ NewState = State#{next_id => ID+1,
13496+ Handler => ID,
13497+ ID => Handler},
13498+ otp19482_simple_multi_acceptor_loop(NewState);
1347713499
1347813500 ?SELECT_RES(accept, Ref) ->
1347913501 ?P("A(undefined,~w) -> select: "
1348013502 "~n Ref: ~p", [ID, Ref]),
13481- otp19482_simple_multi_acceptor_loop(Parent, LSock, Ref, ID, Num);
13503+ NewState = State#{ref => Ref},
13504+ otp19482_simple_multi_acceptor_loop(NewState);
1348213505 ?COMPLETION_RES(accept, Ref) ->
1348313506 ?P("A(undefined,~w) -> completion: "
1348413507 "~n Ref: ~p", [ID, Ref]),
13485- otp19482_simple_multi_acceptor_loop(Parent, LSock, Ref, ID, Num);
13508+ NewState = State#{ref => Ref},
13509+ otp19482_simple_multi_acceptor_loop(NewState);
1348613510
1348713511 {error, Reason} ->
1348813512 ?P("A(undefined,~w) -> failure: "
@@ -13491,57 +13515,93 @@ otp19482_simple_multi_acceptor_loop(Parent, LSock, undefined = Ref0, ID, Num) ->
1349113515
1349213516 end;
1349313517
13494- otp19482_simple_multi_acceptor_loop(Parent, LSock, Ref, ID, Num) ->
13495- ?P("A(~p,~w) -> await socket (accept) messages", [Ref, ID]),
13518+ otp19482_simple_multi_acceptor_loop(#{parent := Parent,
13519+ lsock := LSock,
13520+ ref := Ref,
13521+ next_id := NextID,
13522+ data_sz := Num} = State) ->
13523+ ?P("A(~p,~w) -> await socket (accept) messages", [Ref, NextID]),
1349613524 receive
1349713525 {'$socket', LSock, select, Ref} ->
1349813526 ?P("A(~p,~w) -> select message received - try accept again",
13499- [Ref, ID ]),
13527+ [Ref, NextID ]),
1350013528 case socket:accept(LSock, Ref) of
1350113529 {ok, ASock} ->
1350213530 ?P("A(~p,~w) -> accepted: "
13503- "~n ASock: ~p", [Ref, ID, ASock]),
13504- Handler = otp19482_simple_multi_handler_start(ID, Num),
13505- ?P("A(~p,~w) -> handler ~p started", [Ref, ID, Handler]),
13531+ "~n ASock: ~p", [Ref, NextID, ASock]),
13532+ Handler = otp19482_simple_multi_handler_start(NextID, Num),
13533+ ?P("A(~p,~w) -> handler ~p started",
13534+ [Ref, NextID, Handler]),
1350613535 ok = otp19482_simple_multi_transfer_ownership(ASock,
1350713536 Handler),
1350813537 Handler ! {self(), continue, ASock},
13509- otp19482_simple_multi_acceptor_loop(Parent,
13510- LSock, undefined, ID+1,
13511- Num);
13538+ NewState = State#{next_id => NextID+1,
13539+ ref => undefined,
13540+ Handler => NextID,
13541+ NextID => Handler},
13542+ otp19482_simple_multi_acceptor_loop(NewState);
13543+
1351213544 ?SELECT_RES(accept, NewRef) ->
1351313545 ?P("A(~p,~w) -> select: "
13514- "~n NewRef: ~p", [Ref, ID, NewRef]),
13515- otp19482_simple_multi_acceptor_loop(Parent,
13516- LSock, NewRef, ID,
13517- Num);
13546+ "~n NewRef: ~p", [Ref, NextID, NewRef]),
13547+ otp19482_simple_multi_acceptor_loop(State);
1351813548
1351913549 {error, Reason} ->
1352013550 ?P("A(~p,~w) -> failure: "
13521- "~n Reason: ~p", [Ref, ID , Reason]),
13551+ "~n Reason: ~p", [Ref, NextID , Reason]),
1352213552 exit({accept_fail, Reason})
1352313553 end;
1352413554
1352513555 {'$socket', LSock, completion, {Ref, {ok, ASock}}} ->
1352613556 ?P("A(~p,~w) -> completion message received - with success:"
13527- "~n ASock: ~p", [Ref, ID , ASock]),
13528- Handler = otp19482_simple_multi_handler_start(ID , Num),
13529- ?P("A(~p,~w) -> handler ~p started", [Ref, ID , Handler]),
13557+ "~n ASock: ~p", [Ref, NextID , ASock]),
13558+ Handler = otp19482_simple_multi_handler_start(NextID , Num),
13559+ ?P("A(~p,~w) -> handler ~p started", [Ref, NextID , Handler]),
1353013560 ok = otp19482_simple_multi_transfer_ownership(ASock, Handler),
1353113561 Handler ! {self(), continue, ASock},
13532- otp19482_simple_multi_acceptor_loop(Parent,
13533- LSock, undefined, ID+1,
13534- Num);
13562+ NewState = State#{next_id => NextID+1,
13563+ ref => undefined,
13564+ Handler => NextID,
13565+ NextID => Handler},
13566+ otp19482_simple_multi_acceptor_loop(NewState);
1353513567
1353613568 {'$socket', LSock, completion, {Ref, ERROR}} ->
1353713569 ?P("A(~p,~w) -> completion message received - with error:"
13538- "~n ERROR: ~p", [Ref, ID , ERROR]),
13570+ "~n ERROR: ~p", [Ref, NextID , ERROR]),
1353913571 exit(ERROR);
1354013572
1354113573 {Parent, terminate} ->
13542- ?P("A(~p,~w) -> terminate", [Ref, ID ]),
13574+ ?P("A(~p,~w) -> terminate", [Ref, NextID ]),
1354313575 _ = socket:close(LSock),
13544- exit(normal)
13576+ exit(normal);
13577+
13578+ {'EXIT', Pid, normal} ->
13579+ case maps:get(Pid, State, undefined) of
13580+ undefined ->
13581+ ?P("A(~p,~w) -> unknown process ~p terminated normally",
13582+ [Ref, NextID, Pid]),
13583+ otp19482_simple_multi_acceptor_loop(State);
13584+ ID when is_integer(ID) ->
13585+ ?P("A(~p,~w) -> handler ~p (~w) terminated normally",
13586+ [Ref, NextID, Pid, ID]),
13587+ NewState = maps:remove(ID, maps:remove(Pid, State)),
13588+ otp19482_simple_multi_acceptor_loop(NewState)
13589+ end;
13590+
13591+ {'EXIT', Pid, Reason} ->
13592+ case maps:get(Pid, State, undefined) of
13593+ undefined ->
13594+ ?P("A(~p,~w) -> unknown process ~p terminated: "
13595+ "~n ~p",
13596+ [Ref, NextID, Pid, Reason]),
13597+ otp19482_simple_multi_acceptor_loop(State);
13598+ ID when is_integer(ID) ->
13599+ ?P("A(~p,~w) -> handler ~p (~w) terminated: "
13600+ "~n ~p",
13601+ [Ref, NextID, Pid, ID, Reason]),
13602+ exit({handler_faiulure, Pid, ID, Reason})
13603+ end
13604+
1354513605 end.
1354613606
1354713607otp19482_simple_multi_transfer_ownership(Sock, Pid) ->
@@ -13710,6 +13770,12 @@ otp19482_simple_multi_client_recv_loop(Sock, ID, Num) ->
1371013770 [ID, byte_size(Data)]),
1371113771 otp19482_simple_multi_client_recv_loop(Sock,
1371213772 ID, Num - byte_size(Data));
13773+
13774+ {error, {Reason, RestData}} when is_binary(RestData) ->
13775+ ?P("C[~w] recv-loop -> receive failure:"
13776+ "~n Reason: ~p"
13777+ "~n sz(RestData): ~w", [ID, Reason, byte_size(RestData)]),
13778+ ?FAIL({recv_failure, Reason});
1371313779 {error, Reason} ->
1371413780 ?P("C[~w] recv-loop -> receive failure:"
1371513781 "~n Reason: ~p", [ID, Reason]),
0 commit comments