Skip to content

Commit e8c5c86

Browse files
committed
Merge branch 'maint'
2 parents 52c6beb + 5d9eaa9 commit e8c5c86

File tree

7 files changed

+224
-165
lines changed

7 files changed

+224
-165
lines changed

lib/ssh/test/ssh_basic_SUITE.erl

Lines changed: 38 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -190,8 +190,10 @@ init_per_group(_, Config) ->
190190
end_per_group(_, Config) ->
191191
Config.
192192
%%--------------------------------------------------------------------
193-
init_per_testcase(TC, Config) when TC==shell_no_unicode ;
194-
TC==shell_unicode_string ->
193+
init_per_testcase(TestCase, Config0)
194+
when TestCase==shell_no_unicode;
195+
TestCase==shell_unicode_string ->
196+
Config = ssh_test_lib:add_log_handler(TestCase, Config0),
195197
PrivDir = proplists:get_value(priv_dir, Config),
196198
UserDir = proplists:get_value(priv_dir, Config),
197199
SysDir = proplists:get_value(data_dir, Config),
@@ -208,31 +210,51 @@ init_per_testcase(TC, Config) when TC==shell_no_unicode ;
208210
ct:log("file:native_name_encoding() = ~p,~nio:getopts() = ~p",
209211
[file:native_name_encoding(),io:getopts()]),
210212
wait_for_erlang_first_line([{io,IO}, {shell,Shell}, {sftpd, Sftpd} | Config]);
211-
212-
init_per_testcase(inet6_option, Config) ->
213+
init_per_testcase(TestCase = inet6_option, Config0) ->
214+
Config = ssh_test_lib:add_log_handler(TestCase, Config0),
213215
case ssh_test_lib:has_inet6_address() of
214216
true ->
215217
init_per_testcase('__default__', Config);
216218
false ->
217219
{skip,"No ipv6 interface address"}
218220
end;
219-
init_per_testcase(_TestCase, Config) ->
220-
Config.
221+
init_per_testcase(TestCase, Config) ->
222+
ssh_test_lib:add_log_handler(TestCase, Config).
221223

222-
end_per_testcase(TC, Config) when TC==shell_no_unicode ;
223-
TC==shell_unicode_string ->
224+
end_per_testcase(TestCase, Config)
225+
when TestCase==shell_no_unicode;
226+
TestCase==shell_unicode_string ->
224227
case proplists:get_value(sftpd, Config) of
225228
{Pid, _, _} ->
226229
catch ssh:stop_daemon(Pid);
227230
_ ->
228231
ok
229232
end,
230-
end_per_testcase(Config);
231-
end_per_testcase(_TestCase, Config) ->
232-
end_per_testcase(Config).
233-
234-
end_per_testcase(_Config) ->
235-
ok.
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.
249+
250+
verify_events(_TestCase, 0) ->
251+
ok;
252+
verify_events(multi_daemon_opt_fd, 6) -> ok;
253+
verify_events(internal_error, 3) -> ok;
254+
verify_events(_TestCase, EventNumber) when EventNumber > 0->
255+
{fail, lists:flatten(
256+
io_lib:format("unexpected event cnt: ~s",
257+
[integer_to_list(EventNumber)]))}.
236258

237259
%%--------------------------------------------------------------------
238260
%% Test Cases --------------------------------------------------------
@@ -1051,7 +1073,7 @@ parallel_login(Config) when is_list(Config) ->
10511073
ok = ssh_connection:send(ConnectionRef, ChannelId, <<"Data">>),
10521074
ok = ssh_connection:send(ConnectionRef, ChannelId, << >>),
10531075
ssh_info:print(fun(Fmt, Args) -> io:fwrite(user, Fmt, Args) end),
1054-
{Parents, Conns, Handshakers} =
1076+
{_Parents, _Conns, _Handshakers} =
10551077
ssh_test_lib:find_handshake_parent(Port),
10561078
ssh:stop_daemon(Pid).
10571079

@@ -1539,7 +1561,7 @@ wait_for_erlang_first_line(Config) ->
15391561
{fail,no_ssh_connection};
15401562
<<"Eshell ",_/binary>> = _ErlShellStart ->
15411563
ct:log("Erlang shell start: ~p~n", [_ErlShellStart]),
1542-
Config;
1564+
Config;
15431565
Other ->
15441566
ct:log("Unexpected answer from ssh server: ~p",[Other]),
15451567
{fail,unexpected_answer}

lib/ssh/test/ssh_connection_SUITE.erl

Lines changed: 9 additions & 115 deletions
Original file line numberDiff line numberDiff line change
@@ -235,129 +235,22 @@ end_per_group(_, Config) ->
235235
Config.
236236

237237
%%--------------------------------------------------------------------
238-
init_per_testcase(_TestCase, Config) ->
238+
init_per_testcase(TestCase, Config) ->
239239
ssh:stop(),
240240
ssh:start(),
241-
{ok, TestLogHandlerRef} = ssh_test_lib:add_log_handler(),
242241
ssh_test_lib:verify_sanity_check(Config),
243-
[{log_handler_ref, TestLogHandlerRef} | Config].
242+
ssh_test_lib:add_log_handler(TestCase, Config).
244243

245244
end_per_testcase(TestCase, Config) ->
246245
{ok, Events} = ssh_test_lib:get_log_events(
247246
proplists:get_value(log_handler_ref, Config)),
248247
EventCnt = length(Events),
249-
{ok, InterestingEventCnt} = analyze_events(Events, EventCnt),
248+
{ok, InterestingEventCnt} = ssh_test_lib:analyze_events(Events, EventCnt),
250249
VerificationResult = verify_events(TestCase, InterestingEventCnt),
251-
ssh_test_lib:rm_log_handler(),
250+
ssh_test_lib:rm_log_handler(TestCase),
252251
ssh:stop(),
253252
VerificationResult.
254253

255-
analyze_events(_, 0) ->
256-
{ok, 0};
257-
analyze_events(Events, EventNumber) when EventNumber > 0 ->
258-
{ok, Cnt} = print_interesting_events(Events, 0),
259-
case Cnt > 0 of
260-
true ->
261-
ct:comment("(logger stats) interesting: ~p boring: ~p",
262-
[Cnt, EventNumber - Cnt]);
263-
_ ->
264-
ct:comment("(logger stats) boring: ~p",
265-
[length(Events)])
266-
end,
267-
AllEventsSummary = lists:flatten([process_event(E) || E <- Events]),
268-
ct:log("~nTotal logger events: ~p~nAll events:~n~s", [EventNumber, AllEventsSummary]),
269-
{ok, Cnt}.
270-
271-
process_event(#{msg := {report,
272-
#{label := Label,
273-
report := [{supervisor, Supervisor},
274-
{Status, Properties}]}},
275-
level := Level}) ->
276-
format_event1(Label, Supervisor, Status, Properties, Level);
277-
process_event(#{msg := {report,
278-
#{label := Label,
279-
report := [{supervisor, Supervisor},
280-
{errorContext, _ErrorContext},
281-
{reason, {Status, _ReasonDetails}},
282-
{offender, Properties}]}},
283-
level := Level}) ->
284-
format_event1(Label, Supervisor, Status, Properties, Level);
285-
process_event(#{msg := {report,
286-
#{label := Label,
287-
report := [{supervisor, Supervisor},
288-
{errorContext, _ErrorContext},
289-
{reason, Status},
290-
{offender, Properties}]}},
291-
level := Level}) ->
292-
format_event1(Label, Supervisor, Status, Properties, Level);
293-
process_event(#{msg := {report,
294-
#{label := Label,
295-
report := [Properties, []]}},
296-
level := Level}) ->
297-
{status, Status} = get_value(status, Properties),
298-
{pid, Pid} = get_value(pid, Properties),
299-
Id = get_value(registered_name, Properties),
300-
{initial_call, {M, F, Args}} = get_value(initial_call, Properties),
301-
io_lib:format("[~44s] ~6s ~30s ~20s ~30s ~20s:~10s(~40s)~n",
302-
[io_lib:format("~p", [E]) ||
303-
E <- [Pid, Level, Label, Status, Id, M, F, Args]]);
304-
process_event(#{msg := {report,
305-
#{label := Label,
306-
name := Pid,
307-
reason := {Reason, _Stack = [{M, F, Args, Location} | _]}}},
308-
level := Level}) ->
309-
io_lib:format("[~44s] ~6s ~30s ~20s ~30s ~20s:~10s(~40s) ~30s~n",
310-
[io_lib:format("~p", [E]) ||
311-
E <- [Pid, Level, Label, Reason, undefined, M, F, Args, Location]]);
312-
process_event(#{msg := {report,
313-
#{label := Label,
314-
format := Format,
315-
args := Args}},
316-
meta := #{pid := Pid},
317-
level := Level}) ->
318-
io_lib:format("[~44s] ~6s ~30s ~150s~n",
319-
[io_lib:format("~p", [E]) ||
320-
E <- [Pid, Level, Label]] ++ [io_lib:format(Format, Args)]);
321-
process_event(E) ->
322-
io_lib:format("~n||RAW event||~n~p~n", [E]).
323-
324-
format_event1(Label, Supervisor, Status, Properties, Level) ->
325-
{pid, Pid} = get_value(pid, Properties),
326-
Id = get_value(id, Properties),
327-
{M, F, Args} = get_mfa_value(Properties),
328-
RestartType = get_value(restart_type, Properties),
329-
Significant = get_value(significant, Properties),
330-
io_lib:format("[~30s <- ~10s] ~6s ~30s ~20s ~30s ~20s:~10s(~40s) ~20s ~25s~n",
331-
[io_lib:format("~p", [E]) ||
332-
E <- [Supervisor, Pid, Level, Label, Status, Id, M, F, Args,
333-
Significant, RestartType]]).
334-
335-
get_mfa_value(Properties) ->
336-
case get_value(mfargs, Properties) of
337-
{mfargs, MFA} ->
338-
MFA;
339-
false ->
340-
{mfa, MFA} = get_value(mfa, Properties),
341-
MFA
342-
end.
343-
344-
get_value(Key, List) ->
345-
case lists:keyfind(Key, 1, List) of
346-
R = false ->
347-
ct:log("Key ~p not found in~n~p", [Key, List]),
348-
R;
349-
R -> R
350-
end.
351-
352-
print_interesting_events([], Cnt) ->
353-
{ok, Cnt};
354-
print_interesting_events([#{level := Level} = Event | Tail], Cnt)
355-
when Level /= info, Level /= notice, Level /= debug ->
356-
ct:log("------------~nInteresting event found:~n~p~n==========~n", [Event]),
357-
print_interesting_events(Tail, Cnt + 1);
358-
print_interesting_events([_|Tail], Cnt) ->
359-
print_interesting_events(Tail, Cnt).
360-
361254
verify_events(_TestCase, 0) -> ok;
362255
verify_events(no_sensitive_leak, 1) -> ok;
363256
verify_events(max_channels_option, 3) -> ok;
@@ -1647,7 +1540,8 @@ kex_error(Config) ->
16471540
{preferred_algorithms,[{kex,[Kex1]}]}
16481541
]),
16491542
Ref = make_ref(),
1650-
ok = ssh_log_h:add_fun(kex_error,
1543+
HandlerId = kex_error2, %% avoid conflict with ssh_test_lib log handler
1544+
ok = ssh_log_h:add_fun(HandlerId,
16511545
fun(#{msg:={report,#{format:=Fmt,args:=As,label:={error_logger,_}}}}, Pid) ->
16521546
true = (erlang:process_info(Pid) =/= undefined), % remove handler if we are dead
16531547
Pid ! {Ref, lists:flatten(io_lib:format(Fmt,As))};
@@ -1657,7 +1551,7 @@ kex_error(Config) ->
16571551
end,
16581552
self()),
16591553
Cleanup = fun() ->
1660-
ok = logger:remove_handler(kex_error),
1554+
ok = logger:remove_handler(HandlerId),
16611555
ok = logger:set_primary_config(level, Level)
16621556
end,
16631557
try
@@ -1670,7 +1564,7 @@ kex_error(Config) ->
16701564
])
16711565
of
16721566
_ ->
1673-
ok = logger:remove_handler(kex_error),
1567+
ok = logger:remove_handler(HandlerId),
16741568
ct:fail("expected failure", [])
16751569
catch
16761570
error:{badmatch,{error,"Key exchange failed"}} ->
@@ -1796,7 +1690,7 @@ no_sensitive_leak(Config) ->
17961690
end,
17971691

17981692
%% Install the test handler:
1799-
Hname = no_sensitive_leak,
1693+
Hname = no_sensitive_leak2, %% avoid conflict with ssh_test_lib log handler
18001694
ok = ssh_log_h:add_fun(Hname,
18011695
fun(#{msg := {report,#{report := Rep}}}, Pid) ->
18021696
true = (erlang:process_info(Pid, status) =/= undefined), % remove handler if we are dead

lib/ssh/test/ssh_protocol_SUITE.erl

Lines changed: 13 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1084,19 +1084,20 @@ ext_info_c(Config) ->
10841084
%%%--------------------------------------------------------------------
10851085
%%%
10861086
kex_strict_negotiated(Config0) ->
1087-
{ok, TestRef} = ssh_test_lib:add_log_handler(),
1088-
Config = start_std_daemon(Config0, []),
1087+
Config =
1088+
ssh_test_lib:add_log_handler(?FUNCTION_NAME,
1089+
start_std_daemon(Config0, [])),
10891090
{Server, Host, Port} = proplists:get_value(server, Config),
10901091
Level = ssh_test_lib:get_log_level(),
10911092
ssh_test_lib:set_log_level(debug),
10921093
{ok, ConnRef} = std_connect({Host, Port}, Config, []),
10931094
{algorithms, _A} = ssh:connection_info(ConnRef, algorithms),
10941095
ssh:stop_daemon(Server),
1095-
{ok, Events} = ssh_test_lib:get_log_events(TestRef),
1096+
{ok, Events} = ssh_test_lib:get_log_events(Config),
10961097
true = ssh_test_lib:kex_strict_negotiated(client, Events),
10971098
true = ssh_test_lib:kex_strict_negotiated(server, Events),
10981099
ssh_test_lib:set_log_level(Level),
1099-
ssh_test_lib:rm_log_handler(),
1100+
ssh_test_lib:rm_log_handler(?FUNCTION_NAME),
11001101
ok.
11011102

11021103
%% Connect to an erlang server and inject unexpected SSH message
@@ -1203,9 +1204,9 @@ kex_strict_violation(Config) ->
12031204
ct:log("==== END ====="),
12041205
ok.
12051206

1206-
kex_strict_violation_2(Config) ->
1207+
kex_strict_violation_2(Config0) ->
12071208
ExpectedReason = "KEX strict violation",
1208-
{ok, TestRef} = ssh_test_lib:add_log_handler(),
1209+
Config = ssh_test_lib:add_log_handler(?FUNCTION_NAME, Config0),
12091210
Level = ssh_test_lib:get_log_level(),
12101211
ssh_test_lib:set_log_level(debug),
12111212
%% Connect and negotiate keys
@@ -1246,8 +1247,8 @@ kex_strict_violation_2(Config) ->
12461247
ct:log("2nd flow disconnect already received")
12471248
end,
12481249
ct:sleep(100),
1249-
{ok, Events} = ssh_test_lib:get_log_events(TestRef),
1250-
ssh_test_lib:rm_log_handler(),
1250+
{ok, Events} = ssh_test_lib:get_log_events(Config),
1251+
ssh_test_lib:rm_log_handler(?FUNCTION_NAME),
12511252
ct:log("Events = ~p", [Events]),
12521253
true = ssh_test_lib:kex_strict_negotiated(client, Events),
12531254
true = ssh_test_lib:kex_strict_negotiated(server, Events),
@@ -1270,8 +1271,8 @@ kex_strict_msg_unknown(Config) ->
12701271
{match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}],
12711272
kex_strict_helper(Config, TestMessages, ExpectedReason).
12721273

1273-
kex_strict_helper(Config, TestMessages, ExpectedReason) ->
1274-
{ok, TestRef} = ssh_test_lib:add_log_handler(),
1274+
kex_strict_helper(Config0, TestMessages, ExpectedReason) ->
1275+
Config = ssh_test_lib:add_log_handler(?FUNCTION_NAME, Config0),
12751276
Level = ssh_test_lib:get_log_level(),
12761277
ssh_test_lib:set_log_level(debug),
12771278
%% Connect and negotiate keys
@@ -1293,8 +1294,8 @@ kex_strict_helper(Config, TestMessages, ExpectedReason) ->
12931294
TestMessages,
12941295
InitialState),
12951296
ct:sleep(100),
1296-
{ok, Events} = ssh_test_lib:get_log_events(TestRef),
1297-
ssh_test_lib:rm_log_handler(),
1297+
{ok, Events} = ssh_test_lib:get_log_events(Config),
1298+
ssh_test_lib:rm_log_handler(?FUNCTION_NAME),
12981299
ct:log("Events = ~p", [Events]),
12991300
true = ssh_test_lib:kex_strict_negotiated(client, Events),
13001301
true = ssh_test_lib:kex_strict_negotiated(server, Events),

lib/ssh/test/ssh_test_cli.erl

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -95,7 +95,12 @@ terminate(_Why, _S) ->
9595
nop.
9696

9797
run_portprog(User, cli, TmpDir) ->
98-
Pty_bin = os:find_executable("cat"),
98+
Cmd = case os:type() of
99+
{win32, _} -> "cmd.exe";
100+
_ -> "cat"
101+
end,
102+
Pty_bin = os:find_executable(Cmd),
103+
ct:pal("Pty_bin = ~p", [Pty_bin]),
99104
ssh_test_lib:open_port({spawn_executable, Pty_bin},
100105
[stream,
101106
{cd, TmpDir},

0 commit comments

Comments
 (0)