Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
56 changes: 39 additions & 17 deletions lib/ssh/test/ssh_basic_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -190,8 +190,10 @@ init_per_group(_, Config) ->
end_per_group(_, Config) ->
Config.
%%--------------------------------------------------------------------
init_per_testcase(TC, Config) when TC==shell_no_unicode ;
TC==shell_unicode_string ->
init_per_testcase(TestCase, Config0)
when TestCase==shell_no_unicode;
TestCase==shell_unicode_string ->
Config = ssh_test_lib:add_log_handler(TestCase, Config0),
PrivDir = proplists:get_value(priv_dir, Config),
UserDir = proplists:get_value(priv_dir, Config),
SysDir = proplists:get_value(data_dir, Config),
Expand All @@ -208,31 +210,51 @@ init_per_testcase(TC, Config) when TC==shell_no_unicode ;
ct:log("file:native_name_encoding() = ~p,~nio:getopts() = ~p",
[file:native_name_encoding(),io:getopts()]),
wait_for_erlang_first_line([{io,IO}, {shell,Shell}, {sftpd, Sftpd} | Config]);

init_per_testcase(inet6_option, Config) ->
init_per_testcase(TestCase = inet6_option, Config0) ->
Config = ssh_test_lib:add_log_handler(TestCase, Config0),
case ssh_test_lib:has_inet6_address() of
true ->
init_per_testcase('__default__', Config);
false ->
{skip,"No ipv6 interface address"}
end;
init_per_testcase(_TestCase, Config) ->
Config.
init_per_testcase(TestCase, Config) ->
ssh_test_lib:add_log_handler(TestCase, Config).

end_per_testcase(TC, Config) when TC==shell_no_unicode ;
TC==shell_unicode_string ->
end_per_testcase(TestCase, Config)
when TestCase==shell_no_unicode;
TestCase==shell_unicode_string ->
case proplists:get_value(sftpd, Config) of
{Pid, _, _} ->
catch ssh:stop_daemon(Pid);
_ ->
ok
end,
end_per_testcase(Config);
end_per_testcase(_TestCase, Config) ->
end_per_testcase(Config).

end_per_testcase(_Config) ->
ok.
process_events(TestCase, Config);
end_per_testcase(TestCase, Config) ->
process_events(TestCase, Config).

%% FIXME in parallel executions (p_basic group) this setup does not
%% work log handlers are uniq per testcase, but they all receive same
%% logger events; so if one testcase fails due to logger events, rest
%% of group might fail as well
process_events(TestCase, Config) ->
{ok, Events} = ssh_test_lib:get_log_events(
proplists:get_value(log_handler_ref, Config)),
EventCnt = length(Events),
{ok, InterestingEventCnt} = ssh_test_lib:analyze_events(Events, EventCnt),
VerificationResult = verify_events(TestCase, InterestingEventCnt),
ssh_test_lib:rm_log_handler(TestCase),
VerificationResult.

verify_events(_TestCase, 0) ->
ok;
verify_events(multi_daemon_opt_fd, 6) -> ok;
verify_events(internal_error, 3) -> ok;
verify_events(_TestCase, EventNumber) when EventNumber > 0->
{fail, lists:flatten(
io_lib:format("unexpected event cnt: ~s",
[integer_to_list(EventNumber)]))}.

%%--------------------------------------------------------------------
%% Test Cases --------------------------------------------------------
Expand Down Expand Up @@ -1051,7 +1073,7 @@ parallel_login(Config) when is_list(Config) ->
ok = ssh_connection:send(ConnectionRef, ChannelId, <<"Data">>),
ok = ssh_connection:send(ConnectionRef, ChannelId, << >>),
ssh_info:print(fun(Fmt, Args) -> io:fwrite(user, Fmt, Args) end),
{Parents, Conns, Handshakers} =
{_Parents, _Conns, _Handshakers} =
ssh_test_lib:find_handshake_parent(Port),
ssh:stop_daemon(Pid).

Expand Down Expand Up @@ -1238,7 +1260,7 @@ packet_size(Config) ->
ok = ssh_connection:shell(Conn, Ch),
rec(Server, Conn, Ch, MaxPacketSize),
ssh_connection:close(Conn, Ch)
end, [0, 1, 10, 25]),
end, [1, 10, 25]),

ssh:close(Conn),
ssh:stop_daemon(Server),
Expand Down Expand Up @@ -1539,7 +1561,7 @@ wait_for_erlang_first_line(Config) ->
{fail,no_ssh_connection};
<<"Eshell ",_/binary>> = _ErlShellStart ->
ct:log("Erlang shell start: ~p~n", [_ErlShellStart]),
Config;
Config;
Other ->
ct:log("Unexpected answer from ssh server: ~p",[Other]),
{fail,unexpected_answer}
Expand Down
124 changes: 9 additions & 115 deletions lib/ssh/test/ssh_connection_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -235,129 +235,22 @@ end_per_group(_, Config) ->
Config.

%%--------------------------------------------------------------------
init_per_testcase(_TestCase, Config) ->
init_per_testcase(TestCase, Config) ->
ssh:stop(),
ssh:start(),
{ok, TestLogHandlerRef} = ssh_test_lib:add_log_handler(),
ssh_test_lib:verify_sanity_check(Config),
[{log_handler_ref, TestLogHandlerRef} | Config].
ssh_test_lib:add_log_handler(TestCase, Config).

end_per_testcase(TestCase, Config) ->
{ok, Events} = ssh_test_lib:get_log_events(
proplists:get_value(log_handler_ref, Config)),
EventCnt = length(Events),
{ok, InterestingEventCnt} = analyze_events(Events, EventCnt),
{ok, InterestingEventCnt} = ssh_test_lib:analyze_events(Events, EventCnt),
VerificationResult = verify_events(TestCase, InterestingEventCnt),
ssh_test_lib:rm_log_handler(),
ssh_test_lib:rm_log_handler(TestCase),
ssh:stop(),
VerificationResult.

analyze_events(_, 0) ->
{ok, 0};
analyze_events(Events, EventNumber) when EventNumber > 0 ->
{ok, Cnt} = print_interesting_events(Events, 0),
case Cnt > 0 of
true ->
ct:comment("(logger stats) interesting: ~p boring: ~p",
[Cnt, EventNumber - Cnt]);
_ ->
ct:comment("(logger stats) boring: ~p",
[length(Events)])
end,
AllEventsSummary = lists:flatten([process_event(E) || E <- Events]),
ct:log("~nTotal logger events: ~p~nAll events:~n~s", [EventNumber, AllEventsSummary]),
{ok, Cnt}.

process_event(#{msg := {report,
#{label := Label,
report := [{supervisor, Supervisor},
{Status, Properties}]}},
level := Level}) ->
format_event1(Label, Supervisor, Status, Properties, Level);
process_event(#{msg := {report,
#{label := Label,
report := [{supervisor, Supervisor},
{errorContext, _ErrorContext},
{reason, {Status, _ReasonDetails}},
{offender, Properties}]}},
level := Level}) ->
format_event1(Label, Supervisor, Status, Properties, Level);
process_event(#{msg := {report,
#{label := Label,
report := [{supervisor, Supervisor},
{errorContext, _ErrorContext},
{reason, Status},
{offender, Properties}]}},
level := Level}) ->
format_event1(Label, Supervisor, Status, Properties, Level);
process_event(#{msg := {report,
#{label := Label,
report := [Properties, []]}},
level := Level}) ->
{status, Status} = get_value(status, Properties),
{pid, Pid} = get_value(pid, Properties),
Id = get_value(registered_name, Properties),
{initial_call, {M, F, Args}} = get_value(initial_call, Properties),
io_lib:format("[~44s] ~6s ~30s ~20s ~30s ~20s:~10s(~40s)~n",
[io_lib:format("~p", [E]) ||
E <- [Pid, Level, Label, Status, Id, M, F, Args]]);
process_event(#{msg := {report,
#{label := Label,
name := Pid,
reason := {Reason, _Stack = [{M, F, Args, Location} | _]}}},
level := Level}) ->
io_lib:format("[~44s] ~6s ~30s ~20s ~30s ~20s:~10s(~40s) ~30s~n",
[io_lib:format("~p", [E]) ||
E <- [Pid, Level, Label, Reason, undefined, M, F, Args, Location]]);
process_event(#{msg := {report,
#{label := Label,
format := Format,
args := Args}},
meta := #{pid := Pid},
level := Level}) ->
io_lib:format("[~44s] ~6s ~30s ~150s~n",
[io_lib:format("~p", [E]) ||
E <- [Pid, Level, Label]] ++ [io_lib:format(Format, Args)]);
process_event(E) ->
io_lib:format("~n||RAW event||~n~p~n", [E]).

format_event1(Label, Supervisor, Status, Properties, Level) ->
{pid, Pid} = get_value(pid, Properties),
Id = get_value(id, Properties),
{M, F, Args} = get_mfa_value(Properties),
RestartType = get_value(restart_type, Properties),
Significant = get_value(significant, Properties),
io_lib:format("[~30s <- ~10s] ~6s ~30s ~20s ~30s ~20s:~10s(~40s) ~20s ~25s~n",
[io_lib:format("~p", [E]) ||
E <- [Supervisor, Pid, Level, Label, Status, Id, M, F, Args,
Significant, RestartType]]).

get_mfa_value(Properties) ->
case get_value(mfargs, Properties) of
{mfargs, MFA} ->
MFA;
false ->
{mfa, MFA} = get_value(mfa, Properties),
MFA
end.

get_value(Key, List) ->
case lists:keyfind(Key, 1, List) of
R = false ->
ct:log("Key ~p not found in~n~p", [Key, List]),
R;
R -> R
end.

print_interesting_events([], Cnt) ->
{ok, Cnt};
print_interesting_events([#{level := Level} = Event | Tail], Cnt)
when Level /= info, Level /= notice, Level /= debug ->
ct:log("------------~nInteresting event found:~n~p~n==========~n", [Event]),
print_interesting_events(Tail, Cnt + 1);
print_interesting_events([_|Tail], Cnt) ->
print_interesting_events(Tail, Cnt).

verify_events(_TestCase, 0) -> ok;
verify_events(no_sensitive_leak, 1) -> ok;
verify_events(max_channels_option, 3) -> ok;
Expand Down Expand Up @@ -1647,7 +1540,8 @@ kex_error(Config) ->
{preferred_algorithms,[{kex,[Kex1]}]}
]),
Ref = make_ref(),
ok = ssh_log_h:add_fun(kex_error,
HandlerId = kex_error2, %% avoid conflict with ssh_test_lib log handler
ok = ssh_log_h:add_fun(HandlerId,
fun(#{msg:={report,#{format:=Fmt,args:=As,label:={error_logger,_}}}}, Pid) ->
true = (erlang:process_info(Pid) =/= undefined), % remove handler if we are dead
Pid ! {Ref, lists:flatten(io_lib:format(Fmt,As))};
Expand All @@ -1657,7 +1551,7 @@ kex_error(Config) ->
end,
self()),
Cleanup = fun() ->
ok = logger:remove_handler(kex_error),
ok = logger:remove_handler(HandlerId),
ok = logger:set_primary_config(level, Level)
end,
try
Expand All @@ -1670,7 +1564,7 @@ kex_error(Config) ->
])
of
_ ->
ok = logger:remove_handler(kex_error),
ok = logger:remove_handler(HandlerId),
ct:fail("expected failure", [])
catch
error:{badmatch,{error,"Key exchange failed"}} ->
Expand Down Expand Up @@ -1796,7 +1690,7 @@ no_sensitive_leak(Config) ->
end,

%% Install the test handler:
Hname = no_sensitive_leak,
Hname = no_sensitive_leak2, %% avoid conflict with ssh_test_lib log handler
ok = ssh_log_h:add_fun(Hname,
fun(#{msg := {report,#{report := Rep}}}, Pid) ->
true = (erlang:process_info(Pid, status) =/= undefined), % remove handler if we are dead
Expand Down
25 changes: 13 additions & 12 deletions lib/ssh/test/ssh_protocol_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1083,19 +1083,20 @@ ext_info_c(Config) ->
%%%--------------------------------------------------------------------
%%%
kex_strict_negotiated(Config0) ->
{ok, TestRef} = ssh_test_lib:add_log_handler(),
Config = start_std_daemon(Config0, []),
Config =
ssh_test_lib:add_log_handler(?FUNCTION_NAME,
start_std_daemon(Config0, [])),
{Server, Host, Port} = proplists:get_value(server, Config),
Level = ssh_test_lib:get_log_level(),
ssh_test_lib:set_log_level(debug),
{ok, ConnRef} = std_connect({Host, Port}, Config, []),
{algorithms, _A} = ssh:connection_info(ConnRef, algorithms),
ssh:stop_daemon(Server),
{ok, Events} = ssh_test_lib:get_log_events(TestRef),
{ok, Events} = ssh_test_lib:get_log_events(Config),
true = ssh_test_lib:kex_strict_negotiated(client, Events),
true = ssh_test_lib:kex_strict_negotiated(server, Events),
ssh_test_lib:set_log_level(Level),
ssh_test_lib:rm_log_handler(),
ssh_test_lib:rm_log_handler(?FUNCTION_NAME),
ok.

%% Connect to an erlang server and inject unexpected SSH message
Expand Down Expand Up @@ -1202,9 +1203,9 @@ kex_strict_violation(Config) ->
ct:log("==== END ====="),
ok.

kex_strict_violation_2(Config) ->
kex_strict_violation_2(Config0) ->
ExpectedReason = "KEX strict violation",
{ok, TestRef} = ssh_test_lib:add_log_handler(),
Config = ssh_test_lib:add_log_handler(?FUNCTION_NAME, Config0),
Level = ssh_test_lib:get_log_level(),
ssh_test_lib:set_log_level(debug),
%% Connect and negotiate keys
Expand Down Expand Up @@ -1245,8 +1246,8 @@ kex_strict_violation_2(Config) ->
ct:log("2nd flow disconnect already received")
end,
ct:sleep(100),
{ok, Events} = ssh_test_lib:get_log_events(TestRef),
ssh_test_lib:rm_log_handler(),
{ok, Events} = ssh_test_lib:get_log_events(Config),
ssh_test_lib:rm_log_handler(?FUNCTION_NAME),
ct:log("Events = ~p", [Events]),
true = ssh_test_lib:kex_strict_negotiated(client, Events),
true = ssh_test_lib:kex_strict_negotiated(server, Events),
Expand All @@ -1269,8 +1270,8 @@ kex_strict_msg_unknown(Config) ->
{match, disconnect(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED), receive_msg}],
kex_strict_helper(Config, TestMessages, ExpectedReason).

kex_strict_helper(Config, TestMessages, ExpectedReason) ->
{ok, TestRef} = ssh_test_lib:add_log_handler(),
kex_strict_helper(Config0, TestMessages, ExpectedReason) ->
Config = ssh_test_lib:add_log_handler(?FUNCTION_NAME, Config0),
Level = ssh_test_lib:get_log_level(),
ssh_test_lib:set_log_level(debug),
%% Connect and negotiate keys
Expand All @@ -1292,8 +1293,8 @@ kex_strict_helper(Config, TestMessages, ExpectedReason) ->
TestMessages,
InitialState),
ct:sleep(100),
{ok, Events} = ssh_test_lib:get_log_events(TestRef),
ssh_test_lib:rm_log_handler(),
{ok, Events} = ssh_test_lib:get_log_events(Config),
ssh_test_lib:rm_log_handler(?FUNCTION_NAME),
ct:log("Events = ~p", [Events]),
true = ssh_test_lib:kex_strict_negotiated(client, Events),
true = ssh_test_lib:kex_strict_negotiated(server, Events),
Expand Down
7 changes: 6 additions & 1 deletion lib/ssh/test/ssh_test_cli.erl
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,12 @@ terminate(_Why, _S) ->
nop.

run_portprog(User, cli, TmpDir) ->
Pty_bin = os:find_executable("cat"),
Cmd = case os:type() of
{win32, _} -> "cmd.exe";
_ -> "cat"
end,
Pty_bin = os:find_executable(Cmd),
ct:pal("Pty_bin = ~p", [Pty_bin]),
ssh_test_lib:open_port({spawn_executable, Pty_bin},
[stream,
{cd, TmpDir},
Expand Down
Loading
Loading