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
4 changes: 1 addition & 3 deletions lib/ssh/src/ssh_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -45,8 +45,6 @@ these messages are handled by
[handle_ssh_msg/2](`c:ssh_client_channel:handle_ssh_msg/2`).
""".

-compile(nowarn_obsolete_bool_op).

-include_lib("kernel/include/logger.hrl").

-include("ssh.hrl").
Expand Down Expand Up @@ -1925,7 +1923,7 @@ request_reply_or_data(#channel{local_id = ChannelId, user = ChannelPid},
{[{channel_request_reply, From, Reply}],
Connection#connection{requests =
lists:keydelete(ChannelId, 1, Requests)}};
false when (Reply == success) or (Reply == failure) ->
false when Reply == success; Reply == failure ->
{[], Connection};
false ->
{[{channel_data, ChannelPid, Reply}], Connection}
Expand Down
8 changes: 3 additions & 5 deletions lib/ssh/src/ssh_connection_handler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -31,8 +31,6 @@
-module(ssh_connection_handler).
-moduledoc false.

-compile(nowarn_obsolete_bool_op).

-behaviour(gen_statem).

-include("ssh.hrl").
Expand Down Expand Up @@ -762,13 +760,13 @@ handle_event(internal, #ssh_msg_debug{} = Msg, _StateName, D) ->
handle_event(internal, {conn_msg, Msg}, StateName, #data{connection_state = Connection0,
event_queue = Qev0} = D0) ->
Role = ?role(StateName),
Rengotation = renegotiation(StateName),
Renegotiation = renegotiation(StateName),
try ssh_connection:handle_msg(Msg, Connection0, Role, D0#data.ssh_params) of
{disconnect, Reason0, RepliesConn} ->
{Repls, D} = send_replies(RepliesConn, D0),
case {Reason0,Role} of
{{_, Reason}, client} when ((StateName =/= {connected,client})
and (not Rengotation)) ->
{{_, Reason}, client} when StateName =/= {connected,client},
not Renegotiation ->
handshake({not_connected,Reason}, D);
_ ->
ok
Expand Down
39 changes: 19 additions & 20 deletions lib/ssh/src/ssh_lib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -27,8 +27,6 @@
-module(ssh_lib).
-moduledoc false.

-compile(nowarn_obsolete_bool_op).

-export([
format_address_port/2, format_address_port/1,
format_address/1,
Expand Down Expand Up @@ -75,25 +73,26 @@ format_time_ms(T) when is_integer(T) ->

%%%----------------------------------------------------------------

%% Compares X1 and X2 such that X1 (but not X2) is always iterated fully,
%% ie without returning early on the first difference.
comp(X1, X2) ->
comp(X1, X2, true).

%%% yes - very far from best implementation
comp(<<B1,R1/binary>>, <<B2,R2/binary>>, Truth) ->
comp(R1, R2, Truth and (B1 == B2));
comp(<<_,R1/binary>>, <<>>, Truth) ->
comp(R1, <<>>, Truth and false);
comp(<<>>, <<>>, Truth) ->
Truth;

comp([H1|T1], [H2|T2], Truth) ->
comp(T1, T2, Truth and (H1 == H2));
comp([_|T1], [], Truth) ->
comp(T1, [], Truth and false);
comp([], [], Truth) ->
Truth;

comp(_, _, _) ->
comp(X1, X2, 0).

comp(<<B1, R1/binary>>, <<B2, R2/binary>>, Diff) ->
comp(R1, R2, Diff bor (B1 bxor B2));
comp(<<B1, R1/binary>>, <<>>, _Diff) ->
comp(R1, <<>>, 1 bor (B1 bxor 0));
comp(<<>>, <<>>, Diff) ->
Diff =:= 0;

comp([H1|T1], [H2|T2], Diff) ->
comp(T1, T2, Diff bor (H1 bxor H2));
comp([H1|T1], [], _Diff) ->
comp(T1, [], 1 bor (H1 bxor 0));
comp([], [], Diff) ->
Diff =:= 0;

comp(_X1, _X2, _Diff) ->
false.

set_label(Details) ->
Expand Down
4 changes: 1 addition & 3 deletions lib/ssh/test/ssh_options_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -26,8 +26,6 @@

%%% This test suite tests different options for the ssh functions

-compile(nowarn_obsolete_bool_op).

-include_lib("common_test/include/ct.hrl").
-include_lib("kernel/include/file.hrl").
-include("ssh_test_lib.hrl").
Expand Down Expand Up @@ -1125,7 +1123,7 @@ really_do_hostkey_fingerprint_check(Config, HashAlg) ->
end,
ct:log("check ~p == ~p (~p) and ~n~p~n in ~p (~p)~n",
[PeerName,Host,HostCheck,FP,FPs,FPCheck]),
HostCheck and FPCheck
HostCheck andalso FPCheck
end,

ssh_test_lib:connect(Host, Port, [{silently_accept_hosts,
Expand Down
21 changes: 9 additions & 12 deletions lib/ssh/test/ssh_pubkey_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -22,8 +22,6 @@
%%
-module(ssh_pubkey_SUITE).

-compile(nowarn_obsolete_bool_op).

%% Note: This directive should only be used in test suites.
-export([
suite/0,
Expand Down Expand Up @@ -577,13 +575,12 @@ ssh_list_public_key(Config) when is_list(Config) ->
["openssh_rsa_pub", "openssh_dsa_pub", "openssh_ecdsa_pub"]),

true =
(chk_decode(Data_openssh, Expect_openssh, openssh_key) and
chk_decode(Data_ssh2, Expect_ssh2, rfc4716_key) and
chk_decode(Data_openssh, Expect_openssh, public_key) and
chk_decode(Data_ssh2, Expect_ssh2, public_key) and
chk_encode(Expect_openssh, openssh_key) and
chk_encode(Expect_ssh2, rfc4716_key)
).
chk_decode(Data_openssh, Expect_openssh, openssh_key) andalso
chk_decode(Data_ssh2, Expect_ssh2, rfc4716_key) andalso
chk_decode(Data_openssh, Expect_openssh, public_key) andalso
chk_decode(Data_ssh2, Expect_ssh2, public_key) andalso
chk_encode(Expect_openssh, openssh_key) andalso
chk_encode(Expect_ssh2, rfc4716_key).

chk_encode(Data, Type) ->
case ssh_file:decode(ssh_file:encode(Data,Type), Type) of
Expand Down Expand Up @@ -708,7 +705,7 @@ ssh_known_hosts(Config) when is_list(Config) ->

Value1 = proplists:get_value(hostnames, Attributes1, undefined),
Value2 = proplists:get_value(hostnames, Attributes2, undefined),
true = (Value1 =/= undefined) and (Value2 =/= undefined),
true = Value1 =/= undefined andalso Value2 =/= undefined,

Encoded = ssh_file:encode(Decoded, known_hosts),
Decoded = ssh_file:decode(Encoded, known_hosts).
Expand All @@ -723,7 +720,7 @@ ssh1_known_hosts(Config) when is_list(Config) ->

Value1 = proplists:get_value(hostnames, Attributes1, undefined),
Value2 = proplists:get_value(hostnames, Attributes2, undefined),
true = (Value1 =/= undefined) and (Value2 =/= undefined),
true = Value1 =/= undefined andalso Value2 =/= undefined,

Comment ="dhopson@VMUbuntu-DSH comment with whitespaces",
Comment = proplists:get_value(comment, Attributes3),
Expand Down Expand Up @@ -767,7 +764,7 @@ ssh1_auth_keys(Config) when is_list(Config) ->

Value1 = proplists:get_value(bits, Attributes2, undefined),
Value2 = proplists:get_value(bits, Attributes3, undefined),
true = (Value1 =/= undefined) and (Value2 =/= undefined),
true = Value1 =/= undefined andalso Value2 =/= undefined,

Comment2 = Comment3 = "dhopson@VMUbuntu-DSH",
Comment4 = Comment5 ="dhopson@VMUbuntu-DSH comment with whitespaces",
Expand Down
Loading