Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
  • Loading branch information
bmk committed Nov 28, 2023
2 parents e2d7e2b + f2db25f commit df76879
Show file tree
Hide file tree
Showing 2 changed files with 21 additions and 4 deletions.
23 changes: 20 additions & 3 deletions lib/megaco/test/megaco_mib_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,7 @@
handle_trans_ack/5
]).

-include_lib("common_test/include/ct.hrl").
-include_lib("megaco/include/megaco.hrl").
-include_lib("megaco/include/megaco_message_v1.hrl").
-include("megaco_test_lib.hrl").
Expand Down Expand Up @@ -190,6 +191,7 @@ plain(suite) ->
plain(doc) ->
["Test case for the basic statistics counter handling. "];
plain(Config) when is_list(Config) ->
ct:timetrap(?SECS(10)),
io:format("create test table 1~n", []),
Tab1 = megaco_test_cnt1,
megaco_stats:init(Tab1),
Expand Down Expand Up @@ -292,6 +294,8 @@ connect(suite) ->
connect(doc) ->
[];
connect(Config) when is_list(Config) ->
Factor = ?config(megaco_factor, Config),
ct:timetrap(?SECS(10) + Factor * ?SECS(1)),
Pre = fun() ->
progress("start nodes"),
MgcNode = make_node_name(mgc),
Expand Down Expand Up @@ -408,6 +412,8 @@ traffic(suite) ->
traffic(doc) ->
[];
traffic(Config) when is_list(Config) ->
Factor = ?config(megaco_factor, Config),
ct:timetrap(?MINS(1) + Factor * ?SECS(10)),
Pre = fun() ->
progress("start nodes"),
MgcNode = make_node_name(mgc),
Expand Down Expand Up @@ -1112,7 +1118,9 @@ mgc_handle_request({handle_disconnect, CH, _PV, R}) ->
megaco:cancel(CH, R), % Cancel the outstanding messages
ok;
mgc_handle_request({handle_syntax_error, _RH, _PV, _ED}) ->
reply;
%% There is no point in this test where this is expected.
%% There if it *does* happen; stop
no_reply;
mgc_handle_request({handle_message_error, _CH, _PV, _ED}) ->
no_reply;
mgc_handle_request({handle_trans_request, CH, PV, ARs}) ->
Expand Down Expand Up @@ -1509,8 +1517,17 @@ mg_handle_request({handle_connect, CH, _PV},
mg_handle_request({handle_disconnect, CH, _PV, _R}, S) ->
{ok, S#mg{conn_handle = CH}};

mg_handle_request({handle_syntax_error, _RH, _PV, _ED}, S) ->
{reply, S};
mg_handle_request({handle_syntax_error, RH, PV, ED}, S) ->
%% There is no point in this test where this is expected.
%% But if it *does* happen; stop
%% But can we do that from here? Spawn?
p("Received unexpected syntax error: cancel connection"
"~n RH: ~p"
"~n PV: ~p"
"~n ED: ~p", [RH, PV, ED]),
megaco:cancel(S#mg.conn_handle, ED),
megaco:disconnect(S#mg.conn_handle, {syntax_error, ED}),
{no_reply, S};

mg_handle_request({handle_message_error, CH, _PV, _ED}, S) ->
{no_reply, S#mg{conn_handle = CH}};
Expand Down
2 changes: 1 addition & 1 deletion lib/megaco/test/megaco_mreq_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -255,7 +255,7 @@ req_and_rep(Config) when is_list(Config) ->
"~n Mg4Node: ~p",
[MgcNode, Mg1Node, Mg2Node, Mg3Node, Mg4Node]),
Nodes = [MgcNode, Mg1Node, Mg2Node, Mg3Node, Mg4Node],
ok = ?START_NODES(Nodes),
ok = ?START_NODES(Nodes, true),
Nodes
end,
Case = fun(X) ->
Expand Down

0 comments on commit df76879

Please sign in to comment.