File 0881-megaco-test-Tweaked-transaction-counter-test-case.patch of Package erlang

From 69222b9673b77e20aed03cdc86a8ce1a1ea3468b Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Tue, 9 Feb 2021 19:51:03 +0100
Subject: [PATCH 1/2] [megaco|test] Tweaked transaction counter test case

---
 lib/megaco/test/megaco_config_SUITE.erl | 273 ++++++++++++++----------
 1 file changed, 155 insertions(+), 118 deletions(-)

diff --git a/lib/megaco/test/megaco_config_SUITE.erl b/lib/megaco/test/megaco_config_SUITE.erl
index 4d34e09d0d..2f9c9573c6 100644
--- a/lib/megaco/test/megaco_config_SUITE.erl
+++ b/lib/megaco/test/megaco_config_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2000-2019. All Rights Reserved.
+%% Copyright Ericsson AB 2000-2021. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -600,7 +600,7 @@ transaction_id_counter_mg(Config) when is_list(Config) ->
 
     %% Await the counter worker procs termination
     i("await the counter working procs completion"),
-    await_completion_counter_working_procs(Pids),
+    ok = await_completion_counter_working_procs(Pids),
 
     %% Verify result
     i("verify counter result"),
@@ -656,14 +656,35 @@ start_counter_working_procs([Pid | Pids]) ->
     Pid ! start,
     start_counter_working_procs(Pids).
 
-await_completion_counter_working_procs([]) ->
-    ok;
 await_completion_counter_working_procs(Pids) ->
+    await_completion_counter_working_procs(Pids, [], []).
+
+await_completion_counter_working_procs([], _OKs, [] = _ERRs) ->
+    ok;
+await_completion_counter_working_procs([], _OKs, ERRs) ->
+    {error, ERRs};
+await_completion_counter_working_procs(Pids, OKs, ERRs) ->
     receive
 	{'EXIT', Pid, normal} ->
+            %% i("counter working process completion[~w, ~w, ~w] -> "
+            %%   "Expected exit from counter process: "
+            %%   "~n      Pid: ~p",
+            %%   [length(Pids), length(OKs), length(ERRs), Pid]),
+	    Pids2 = lists:delete(Pid, Pids),
+	    await_completion_counter_working_procs(Pids2, [Pid | OKs], ERRs);
+	{'EXIT', Pid, Reason} ->
+            e("counter working process completion[~w, ~w, ~w] -> "
+              "Unexpected exit from counter process: "
+              "~n      Pid:    ~p"
+              "~n      Reason: ~p",
+              [length(Pids), length(OKs), length(ERRs), Pid, Reason]),
 	    Pids2 = lists:delete(Pid, Pids),
-	    await_completion_counter_working_procs(Pids2);
-	_Any ->
+	    await_completion_counter_working_procs(Pids2, OKs, [Pid | ERRs]);
+
+	Any ->
+            e("counter working process completion[~w, ~w, ~w] -> "
+              "Unexpected message: "
+              "~n      ~p", [length(Pids), length(OKs), length(ERRs), Any]),
 	    await_completion_counter_working_procs(Pids)
     end.
     
@@ -677,119 +698,123 @@ transaction_id_counter_mgc(doc) ->
      "transaction counter handling of the application "
      "in with several connections (MGC). "];
 transaction_id_counter_mgc(Config) when is_list(Config) ->
-    put(verbosity, ?TEST_VERBOSITY),
-    put(sname,     "TEST"),
-    put(tc,        transaction_id_counter_mgc),
-    process_flag(trap_exit, true),
-
-    i("starting"),
-
-    {ok, _ConfigPid} = megaco_config:start_link(),
-
-    %% Basic user data
-    UserMid = {deviceName, "mgc"},
-    UserConfig = [
-		  {min_trans_id, 1}
-		 ],
-
-    %% Basic connection data
-    RemoteMids = 
-	[
-	 {deviceName, "mg01"},
-	 {deviceName, "mg02"},
-	 {deviceName, "mg03"},
-	 {deviceName, "mg04"},
-	 {deviceName, "mg05"},
-	 {deviceName, "mg06"},
-	 {deviceName, "mg07"},
-	 {deviceName, "mg08"},
-	 {deviceName, "mg09"},
-	 {deviceName, "mg10"}
-	], 
-    RecvHandles = 
-	[
-	 #megaco_receive_handle{local_mid     = UserMid,
-	 			encoding_mod    = ?MODULE,
-	 			encoding_config = [],
-	 			send_mod        = ?MODULE},
-	 #megaco_receive_handle{local_mid     = UserMid,
-	 			encoding_mod    = ?MODULE,
-	 			encoding_config = [],
-	 			send_mod        = ?MODULE},
-	 #megaco_receive_handle{local_mid     = UserMid,
-	 			encoding_mod    = ?MODULE,
-	 			encoding_config = [],
-	 			send_mod        = ?MODULE},
-	 #megaco_receive_handle{local_mid     = UserMid,
-	 			encoding_mod    = ?MODULE,
-	 			encoding_config = [],
-	 			send_mod        = ?MODULE},
-	 #megaco_receive_handle{local_mid     = UserMid,
-	 			encoding_mod    = ?MODULE,
-	 			encoding_config = [],
-	 			send_mod        = ?MODULE},
-	 #megaco_receive_handle{local_mid     = UserMid,
-	 			encoding_mod    = ?MODULE,
-	 			encoding_config = [],
-	 			send_mod        = ?MODULE},
-	 #megaco_receive_handle{local_mid     = UserMid,
-	 			encoding_mod    = ?MODULE,
-	 			encoding_config = [],
-	 			send_mod        = ?MODULE},
-	 #megaco_receive_handle{local_mid     = UserMid,
-	 			encoding_mod    = ?MODULE,
-	 			encoding_config = [],
-	 			send_mod        = ?MODULE},
-	 #megaco_receive_handle{local_mid     = UserMid,
-	 			encoding_mod    = ?MODULE,
-	 			encoding_config = [],
-	 			send_mod        = ?MODULE},
-	 #megaco_receive_handle{local_mid     = UserMid,
-				encoding_mod    = ?MODULE,
-				encoding_config = [],
-				send_mod        = ?MODULE}
-	],
-    SendHandle = dummy_send_handle,
-    ControlPid = self(), 
+    Name = transaction_id_counter_mgc,
+    Pre = fun() ->
+                  i("starting config server"),
+                  {ok, _ConfigPid} = megaco_config:start_link(),
+
+                  %% Basic user data
+                  UserMid = {deviceName, "mgc"},
+                  UserConfig = [
+                                {min_trans_id, 1}
+                               ],
+
+                  %% Basic connection data
+                  RemoteMids = 
+                      [
+                       {deviceName, "mg01"},
+                       {deviceName, "mg02"},
+                       {deviceName, "mg03"},
+                       {deviceName, "mg04"},
+                       {deviceName, "mg05"},
+                       {deviceName, "mg06"},
+                       {deviceName, "mg07"},
+                       {deviceName, "mg08"},
+                       {deviceName, "mg09"},
+                       {deviceName, "mg10"}
+                      ], 
+                  RecvHandles = 
+                      [
+                       #megaco_receive_handle{local_mid     = UserMid,
+                                              encoding_mod    = ?MODULE,
+                                              encoding_config = [],
+                                              send_mod        = ?MODULE},
+                       #megaco_receive_handle{local_mid     = UserMid,
+                                              encoding_mod    = ?MODULE,
+                                              encoding_config = [],
+                                              send_mod        = ?MODULE},
+                       #megaco_receive_handle{local_mid     = UserMid,
+                                              encoding_mod    = ?MODULE,
+                                              encoding_config = [],
+                                              send_mod        = ?MODULE},
+                       #megaco_receive_handle{local_mid     = UserMid,
+                                              encoding_mod    = ?MODULE,
+                                              encoding_config = [],
+                                              send_mod        = ?MODULE},
+                       #megaco_receive_handle{local_mid     = UserMid,
+                                              encoding_mod    = ?MODULE,
+                                              encoding_config = [],
+                                              send_mod        = ?MODULE},
+                       #megaco_receive_handle{local_mid     = UserMid,
+                                              encoding_mod    = ?MODULE,
+                                              encoding_config = [],
+                                              send_mod        = ?MODULE},
+                       #megaco_receive_handle{local_mid     = UserMid,
+                                              encoding_mod    = ?MODULE,
+                                              encoding_config = [],
+                                              send_mod        = ?MODULE},
+                       #megaco_receive_handle{local_mid     = UserMid,
+                                              encoding_mod    = ?MODULE,
+                                              encoding_config = [],
+                                              send_mod        = ?MODULE},
+                       #megaco_receive_handle{local_mid     = UserMid,
+                                              encoding_mod    = ?MODULE,
+                                              encoding_config = [],
+                                              send_mod        = ?MODULE},
+                       #megaco_receive_handle{local_mid     = UserMid,
+                                              encoding_mod    = ?MODULE,
+                                              encoding_config = [],
+                                              send_mod        = ?MODULE}
+                      ],
+                  SendHandle = dummy_send_handle,
+                  ControlPid = self(),
     
-    %% Start user
-    i("start user"),
-    ok = megaco_config:start_user(UserMid, UserConfig),
-
-    %% Create connection
-    i("create connection(s)"),
-    CDs = create_connections(RecvHandles, RemoteMids, SendHandle, ControlPid),
+                  %% Start user
+                  i("start user"),
+                  ok = megaco_config:start_user(UserMid, UserConfig),
+
+                  %% Create connection
+                  i("create connection(s)"),
+                  CDs = create_connections(RecvHandles,
+                                           RemoteMids,
+                                           SendHandle,
+                                           ControlPid),
+
+                  %% Set counter limits
+                  i("set counter max limit(s)"),
+                  set_counter_max_limits(CDs, 1000),
+
+                  {UserMid, CDs}
+          end,
+    Case = fun({_, CDs}) ->
+                   %% Create the counter worker procs
+                   i("create counter working procs"),
+                   Pids = create_counter_working_procs(CDs, ?NUM_CNT_PROCS),
+
+                   %% Start the counter worker procs
+                   i("release the counter working procs"),
+                   start_counter_working_procs(Pids),
+
+                   %% Await the counter worker procs termination
+                   i("await the counter working procs completion"),
+                   ok = await_completion_counter_working_procs(Pids),
+
+                   %% Verify result
+                   i("verify counter result"),
+                   verify_counter_results(CDs)
+           end,
+
+    Post = fun({UserMid, CDs}) ->
+                   %% Stop test
+                   i("disconnect"),
+                   delete_connections(CDs), 
+                   i("stop user"),
+                   ok = megaco_config:stop_user(UserMid),
+                   i("stop megaco_config"),
+                   ok = megaco_config:stop()
+           end,
+    try_tc(Name, Pre, Case, Post).
 
-    %% Set counter limits
-    i("set counter max limit(s)"),
-    set_counter_max_limits(CDs, 1000),
-
-    %% Create the counter worker procs
-    i("create counter working procs"),
-    Pids = create_counter_working_procs(CDs, ?NUM_CNT_PROCS),
-
-    %% Start the counter worker procs
-    i("release the counter working procs"),
-    start_counter_working_procs(Pids),
-
-    %% Await the counter worker procs termination
-    i("await the counter working procs completion"),
-    await_completion_counter_working_procs(Pids),
-
-    %% Verify result
-    i("verify counter result"),
-    verify_counter_results(CDs),
-
-    %% Stop test
-    i("disconnect"),
-    delete_connections(CDs), 
-    i("stop user"),
-    ok = megaco_config:stop_user(UserMid),
-    i("stop megaco_config"),
-    ok = megaco_config:stop(),
-
-    i("done"),
-    ok.
 
 create_connections(RecvHandles, RemoteMids, SendHandle, ControlPid) ->
     create_connections(RecvHandles, RemoteMids, SendHandle, ControlPid, []).
@@ -1216,6 +1241,15 @@ otp_8183(Config) when is_list(Config) ->
     ok.
 
 
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+try_tc(TCName, Pre, Case, Post) ->
+    try_tc(TCName, "TEST", ?TEST_VERBOSITY, Pre, Case, Post).
+
+try_tc(TCName, Name, Verbosity, Pre, Case, Post) ->
+    ?TRY_TC(TCName, Name, Verbosity, Pre, Case, Post).
+
+
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 p(F) ->
@@ -1234,7 +1268,10 @@ i(F) ->
     i(F, []).
 
 i(F, A) ->
-    print(info, get(verbosity), get(tc), "INF", F, A).
+    print(info, get(verbosity), get(tc), "INFO", F, A).
+
+e(F, A) ->
+    print(info, get(verbosity), get(tc), "ERROR", F, A).
 
 printable(_, debug)   -> true;
 printable(info, info) -> true;
-- 
2.26.2

openSUSE Build Service is sponsored by