Skip to content

Commit 98fdca2

Browse files
committed
ssh: add cth_events and event verification for ssh_protocol_SUITE
- add ssh/test/cth_events - hook module for verifying logger events - verify logger events for ssh_protocol_SUITE - use cth_events in other test suites
1 parent 9efd029 commit 98fdca2

File tree

6 files changed

+151
-38
lines changed

6 files changed

+151
-38
lines changed

lib/ssh/test/Makefile

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ include $(ERL_TOP)/make/$(TARGET)/otp.mk
2828
# ----------------------------------------------------
2929

3030
MODULES= \
31+
cth_events \
3132
ssh_cth \
3233
ssh_algorithms_SUITE \
3334
ssh_options_SUITE \

lib/ssh/test/cth_events.erl

Lines changed: 97 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,97 @@
1+
%%
2+
%% %CopyrightBegin%
3+
%%
4+
%% SPDX-License-Identifier: Apache-2.0
5+
%%
6+
%% Copyright Ericsson AB 2011-2025. All Rights Reserved.
7+
%%
8+
%% Licensed under the Apache License, Version 2.0 (the "License");
9+
%% you may not use this file except in compliance with the License.
10+
%% You may obtain a copy of the License at
11+
%%
12+
%% http://www.apache.org/licenses/LICENSE-2.0
13+
%%
14+
%% Unless required by applicable law or agreed to in writing, software
15+
%% distributed under the License is distributed on an "AS IS" BASIS,
16+
%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
17+
%% See the License for the specific language governing permissions and
18+
%% limitations under the License.
19+
%%
20+
%% %CopyrightEnd%
21+
%%
22+
-module(cth_events).
23+
-moduledoc false.
24+
25+
%%% This module verifies logger events.
26+
27+
%% CTH Callbacks
28+
-export([id/1, init/2,
29+
%% pre_init_per_suite/3, pre_end_per_suite/3, post_end_per_suite/4,
30+
%% pre_init_per_group/4, post_init_per_group/5,
31+
%% pre_end_per_group/4, post_end_per_group/5,
32+
pre_init_per_testcase/4, %post_init_per_testcase/5,
33+
%% pre_end_per_testcase/4,
34+
post_end_per_testcase/5]).
35+
36+
-behaviour(ct_hooks).
37+
38+
id(_Opts) ->
39+
?MODULE.
40+
41+
init(?MODULE, Opts) ->
42+
GetValue =
43+
fun(Property, PropList, Default) ->
44+
case proplists:get_value(Property, PropList) of
45+
undefined -> Default;
46+
V -> V
47+
end
48+
end,
49+
50+
DefaultVerifyFun =
51+
fun(_, 0) ->
52+
ok;
53+
(_, EventNumber) when EventNumber > 0 ->
54+
{fail, lists:flatten(
55+
io_lib:format("unexpected event cnt: ~s",
56+
[integer_to_list(EventNumber)]))}
57+
end,
58+
VerifyFun = GetValue(verify_fun, Opts, DefaultVerifyFun),
59+
SkipTc = GetValue(skip_tc, Opts, []),
60+
ct_util:mark_process(), % ??
61+
{ok, #{verify_fun => VerifyFun, skip_tc => SkipTc}}.
62+
63+
%% FIXME in parallel executions (e.g. ssh_basic_SUITE:p_basic group) this setup does not
64+
%% work log handlers are uniq per testcase, but they all receive same
65+
%% logger events; so if one testcase fails due to logger events, rest
66+
%% of group might fail as well
67+
pre_init_per_testcase(_Suite, TestCase, Config0, State = #{skip_tc := SkipTc}) ->
68+
case lists:member(TestCase, SkipTc) of
69+
false ->
70+
Config = ssh_test_lib:add_log_handler(TestCase, Config0),
71+
{Config, State};
72+
true ->
73+
{Config0, State}
74+
end.
75+
76+
post_end_per_testcase(_Suite, TestCase, Config, Result,
77+
State = #{skip_tc := SkipTc,
78+
verify_fun := VerifyFun}) ->
79+
case lists:member(TestCase, SkipTc) of
80+
false ->
81+
{ok, Events} = ssh_test_lib:get_log_events(
82+
proplists:get_value(log_handler_ref, Config)),
83+
EventCnt = length(Events),
84+
{ok, InterestingEventCnt} = ssh_test_lib:analyze_events(Events, EventCnt),
85+
VerificationResult = VerifyFun(TestCase, InterestingEventCnt),
86+
ssh_test_lib:rm_log_handler(TestCase),
87+
case VerificationResult of
88+
ok ->
89+
{Result, State};
90+
_ ->
91+
{VerificationResult, State}
92+
end;
93+
true ->
94+
{Result, State}
95+
end.
96+
97+

lib/ssh/test/ssh_basic_SUITE.erl

Lines changed: 10 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -109,7 +109,9 @@
109109
%%--------------------------------------------------------------------
110110

111111
suite() ->
112-
[{ct_hooks,[ts_install_cth]},
112+
[{ct_hooks,[ts_install_cth,
113+
{cth_events,
114+
[{verify_fun, fun verify_events/2}]}]},
113115
{timetrap,{seconds,90}}].
114116

115117
all() ->
@@ -190,10 +192,9 @@ init_per_group(_, Config) ->
190192
end_per_group(_, Config) ->
191193
Config.
192194
%%--------------------------------------------------------------------
193-
init_per_testcase(TestCase, Config0)
195+
init_per_testcase(TestCase, Config)
194196
when TestCase==shell_no_unicode;
195197
TestCase==shell_unicode_string ->
196-
Config = ssh_test_lib:add_log_handler(TestCase, Config0),
197198
PrivDir = proplists:get_value(priv_dir, Config),
198199
UserDir = proplists:get_value(priv_dir, Config),
199200
SysDir = proplists:get_value(data_dir, Config),
@@ -210,8 +211,7 @@ init_per_testcase(TestCase, Config0)
210211
ct:log("file:native_name_encoding() = ~p,~nio:getopts() = ~p",
211212
[file:native_name_encoding(),io:getopts()]),
212213
wait_for_erlang_first_line([{io,IO}, {shell,Shell}, {sftpd, Sftpd} | Config]);
213-
init_per_testcase(TestCase = inet6_option, Config0) ->
214-
Config = ssh_test_lib:add_log_handler(TestCase, Config0),
214+
init_per_testcase(inet6_option, Config) ->
215215
case ssh_test_lib:has_inet6_address() of
216216
true ->
217217
init_per_testcase('__default__', Config);
@@ -226,26 +226,13 @@ end_per_testcase(TestCase, Config)
226226
TestCase==shell_unicode_string ->
227227
case proplists:get_value(sftpd, Config) of
228228
{Pid, _, _} ->
229-
catch ssh:stop_daemon(Pid);
229+
catch ssh:stop_daemon(Pid),
230+
ok;
230231
_ ->
231232
ok
232-
end,
233-
process_events(TestCase, Config);
234-
end_per_testcase(TestCase, Config) ->
235-
process_events(TestCase, Config).
236-
237-
%% FIXME in parallel executions (p_basic group) this setup does not
238-
%% work log handlers are uniq per testcase, but they all receive same
239-
%% logger events; so if one testcase fails due to logger events, rest
240-
%% of group might fail as well
241-
process_events(TestCase, Config) ->
242-
{ok, Events} = ssh_test_lib:get_log_events(
243-
proplists:get_value(log_handler_ref, Config)),
244-
EventCnt = length(Events),
245-
{ok, InterestingEventCnt} = ssh_test_lib:analyze_events(Events, EventCnt),
246-
VerificationResult = verify_events(TestCase, InterestingEventCnt),
247-
ssh_test_lib:rm_log_handler(TestCase),
248-
VerificationResult.
233+
end;
234+
end_per_testcase(_TestCase, _Config) ->
235+
ok.
249236

250237
verify_events(_TestCase, 0) ->
251238
ok;

lib/ssh/test/ssh_connection_SUITE.erl

Lines changed: 9 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -125,7 +125,10 @@
125125
%% [{ct_hooks,[ts_install_cth]}].
126126

127127
suite() ->
128-
[{timetrap,{seconds,40}}].
128+
[{ct_hooks,[ts_install_cth,
129+
{cth_events,
130+
[{verify_fun, fun verify_events/2}]}]},
131+
{timetrap,{seconds,40}}].
129132

130133
all() ->
131134
[
@@ -235,21 +238,14 @@ end_per_group(_, Config) ->
235238
Config.
236239

237240
%%--------------------------------------------------------------------
238-
init_per_testcase(TestCase, Config) ->
241+
init_per_testcase(_TestCase, Config) ->
239242
ssh:stop(),
240243
ssh:start(),
241244
ssh_test_lib:verify_sanity_check(Config),
242-
ssh_test_lib:add_log_handler(TestCase, Config).
243-
244-
end_per_testcase(TestCase, Config) ->
245-
{ok, Events} = ssh_test_lib:get_log_events(
246-
proplists:get_value(log_handler_ref, Config)),
247-
EventCnt = length(Events),
248-
{ok, InterestingEventCnt} = ssh_test_lib:analyze_events(Events, EventCnt),
249-
VerificationResult = verify_events(TestCase, InterestingEventCnt),
250-
ssh_test_lib:rm_log_handler(TestCase),
251-
ssh:stop(),
252-
VerificationResult.
245+
Config.
246+
247+
end_per_testcase(_TestCase, _Config) ->
248+
ssh:stop().
253249

254250
verify_events(_TestCase, 0) -> ok;
255251
verify_events(no_sensitive_leak, 1) -> ok;

lib/ssh/test/ssh_protocol_SUITE.erl

Lines changed: 20 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -123,7 +123,25 @@
123123
%% Common Test interface functions -----------------------------------
124124
%%--------------------------------------------------------------------
125125
suite() ->
126-
[{ct_hooks,[ts_install_cth]},
126+
VerifyFun =
127+
fun(_, 0) ->
128+
ok;
129+
(client_close_after_hello, 1) ->
130+
ok;
131+
(extra_ssh_msg_service_request, 1) ->
132+
ok;
133+
(_, EventNumber) ->
134+
{fail, lists:flatten(
135+
io_lib:format("unexpected event cnt: ~s",
136+
[integer_to_list(EventNumber)]))}
137+
end,
138+
SkipTc = [kex_strict_negotiated,
139+
kex_strict_violation,
140+
kex_strict_violation_2],
141+
[{ct_hooks,[ts_install_cth,
142+
{cth_events,
143+
[{verify_fun, VerifyFun},
144+
{skip_tc, SkipTc}]}]},
127145
{timetrap,{seconds,40}}].
128146

129147
all() ->
@@ -550,7 +568,7 @@ no_common_alg_client_disconnects(Config) ->
550568
ct:log("ERROR!~nOp = ~p~nExecResult = ~p~nState =~n~s",
551569
[Op,ExecResult,ssh_trpt_test_lib:format_msg(S)]),
552570
{fail, ExecResult};
553-
X ->
571+
{result, Pid, X} ->
554572
ct:log("¤¤¤¤¤"),
555573
ct:fail(X)
556574
after

lib/ssh/test/ssh_test_lib.erl

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1426,6 +1426,14 @@ process_event(#{msg := {report,
14261426
io_lib:format("[~44s] ~6s ~30s ~20s ~30s ~20s:~10s(~40s)~n",
14271427
[io_lib:format("~p", [E]) ||
14281428
E <- [Pid, Level, Label, Status, Id, M, F, Args]]);
1429+
process_event(#{msg := {report,
1430+
#{label := Label,
1431+
report := [MsgString]}},
1432+
meta := #{pid := Pid},
1433+
level := Level}) ->
1434+
io_lib:format("[~44s] ~6s ~20s ~s~n",
1435+
[io_lib:format("~p", [E]) ||
1436+
E <- [Pid, Level, Label]] ++ [MsgString]);
14291437
process_event(#{msg := {report,
14301438
#{label := Label,
14311439
name := Pid,
@@ -1449,6 +1457,12 @@ process_event(#{msg := {Format, Args},
14491457
io_lib:format("[~44s] ~6s~n~s~n",
14501458
[io_lib:format("~p", [E]) ||
14511459
E <- [Pid, Level]] ++ [io_lib:format(Format, Args)]);
1460+
process_event(#{msg := {string, MsgString},
1461+
meta := #{pid := Pid},
1462+
level := Level}) when is_list(MsgString) ->
1463+
io_lib:format("[~44s] ~6s ~s~n",
1464+
[io_lib:format("~p", [E]) ||
1465+
E <- [Pid, Level]] ++ [MsgString]);
14521466
process_event(#{msg := {report,
14531467
#{label := Label,
14541468
reason := Reason,

0 commit comments

Comments
 (0)