@@ -13291,7 +13291,7 @@ do_otp19482_simple_multi(#{iov_max := IOVMax,
13291
13291
Clients),
13292
13292
13293
13293
?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
13295
13295
{_, []} ->
13296
13296
?P("~w -> all clients successful - terminate clients",
13297
13297
[?FUNCTION_NAME]),
@@ -13331,22 +13331,30 @@ do_otp19482_simple_multi(#{iov_max := IOVMax,
13331
13331
end.
13332
13332
13333
13333
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, [], []).
13336
13336
13337
- do_otp19482_simple_multi_await_client_success ([], Success, Failure) ->
13337
+ do_otp19482_simple_multi_await_client_completion ([], Success, Failure) ->
13338
13338
?P("~w -> done when: "
13339
13339
"~n Success: ~p"
13340
13340
"~n Failure: ~p", [?FUNCTION_NAME, Success, Failure]),
13341
13341
{Success, Failure};
13342
- do_otp19482_simple_multi_await_client_success (Clients, Success, Failure) ->
13342
+ do_otp19482_simple_multi_await_client_completion (Clients, Success, Failure) ->
13343
13343
receive
13344
13344
{Pid, done} ->
13345
13345
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
+
13350
13358
{'EXIT', Pid, Reason} ->
13351
13359
?P("~w -> received unexpected exit: "
13352
13360
"~n Pid: ~p"
@@ -13355,19 +13363,22 @@ do_otp19482_simple_multi_await_client_success(Clients, Success, Failure) ->
13355
13363
"~n Clients: ~p"
13356
13364
"~n length(Success): ~p"
13357
13365
"~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)]),
13359
13368
case lists:delete(Pid, Clients) of
13360
13369
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);
13365
13374
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])
13370
13380
end
13381
+
13371
13382
end.
13372
13383
13373
13384
do_otp19482_simple_multi_collect_procs(undefined, []) ->
@@ -13457,13 +13468,21 @@ otp19482_simple_multi_acceptor_init(Parent, LSA, Num) ->
13457
13468
ok
13458
13469
end,
13459
13470
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).
13461
13477
13462
13478
13463
13479
-define(SELECT_RES(Tag,Ref), {select, {select_info, (Tag), (Ref)}}).
13464
13480
-define(COMPLETION_RES(Tag,Ref), {completion, {completion_info, (Tag), (Ref)}}).
13465
13481
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) ->
13467
13486
?P("A(undefined,~w) -> try accept", [ID]),
13468
13487
case socket:accept(LSock, nowait) of
13469
13488
{ok, ASock} ->
@@ -13473,16 +13492,21 @@ otp19482_simple_multi_acceptor_loop(Parent, LSock, undefined = Ref0, ID, Num) ->
13473
13492
?P("A(undefined,~w) -> handler ~p started", [ID, Handler]),
13474
13493
ok = otp19482_simple_multi_transfer_ownership(ASock, Handler),
13475
13494
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);
13477
13499
13478
13500
?SELECT_RES(accept, Ref) ->
13479
13501
?P("A(undefined,~w) -> select: "
13480
13502
"~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);
13482
13505
?COMPLETION_RES(accept, Ref) ->
13483
13506
?P("A(undefined,~w) -> completion: "
13484
13507
"~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);
13486
13510
13487
13511
{error, Reason} ->
13488
13512
?P("A(undefined,~w) -> failure: "
@@ -13491,57 +13515,93 @@ otp19482_simple_multi_acceptor_loop(Parent, LSock, undefined = Ref0, ID, Num) ->
13491
13515
13492
13516
end;
13493
13517
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]),
13496
13524
receive
13497
13525
{'$socket', LSock, select, Ref} ->
13498
13526
?P("A(~p,~w) -> select message received - try accept again",
13499
- [Ref, ID ]),
13527
+ [Ref, NextID ]),
13500
13528
case socket:accept(LSock, Ref) of
13501
13529
{ok, ASock} ->
13502
13530
?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]),
13506
13535
ok = otp19482_simple_multi_transfer_ownership(ASock,
13507
13536
Handler),
13508
13537
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
+
13512
13544
?SELECT_RES(accept, NewRef) ->
13513
13545
?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);
13518
13548
13519
13549
{error, Reason} ->
13520
13550
?P("A(~p,~w) -> failure: "
13521
- "~n Reason: ~p", [Ref, ID , Reason]),
13551
+ "~n Reason: ~p", [Ref, NextID , Reason]),
13522
13552
exit({accept_fail, Reason})
13523
13553
end;
13524
13554
13525
13555
{'$socket', LSock, completion, {Ref, {ok, ASock}}} ->
13526
13556
?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]),
13530
13560
ok = otp19482_simple_multi_transfer_ownership(ASock, Handler),
13531
13561
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);
13535
13567
13536
13568
{'$socket', LSock, completion, {Ref, ERROR}} ->
13537
13569
?P("A(~p,~w) -> completion message received - with error:"
13538
- "~n ERROR: ~p", [Ref, ID , ERROR]),
13570
+ "~n ERROR: ~p", [Ref, NextID , ERROR]),
13539
13571
exit(ERROR);
13540
13572
13541
13573
{Parent, terminate} ->
13542
- ?P("A(~p,~w) -> terminate", [Ref, ID ]),
13574
+ ?P("A(~p,~w) -> terminate", [Ref, NextID ]),
13543
13575
_ = 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
+
13545
13605
end.
13546
13606
13547
13607
otp19482_simple_multi_transfer_ownership(Sock, Pid) ->
@@ -13710,6 +13770,12 @@ otp19482_simple_multi_client_recv_loop(Sock, ID, Num) ->
13710
13770
[ID, byte_size(Data)]),
13711
13771
otp19482_simple_multi_client_recv_loop(Sock,
13712
13772
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});
13713
13779
{error, Reason} ->
13714
13780
?P("C[~w] recv-loop -> receive failure:"
13715
13781
"~n Reason: ~p", [ID, Reason]),
0 commit comments