Skip to content

Commit

Permalink
Corrected ssh option handling
Browse files Browse the repository at this point in the history
The option ip_v6_disabled and the undocumented option exec was incorrectly
handled by the option checking code.

There where two options for allowing user interaction one documented
and one undocumented, they where merge to to be the documented one.
For backwards compatibility the undocumented one is transformed to the
documented one in the option checking code.
  • Loading branch information
IngelaAndin committed Apr 24, 2012
1 parent a76628f commit b85e884
Show file tree
Hide file tree
Showing 3 changed files with 52 additions and 20 deletions.
20 changes: 12 additions & 8 deletions lib/ssh/src/ssh.erl
Expand Up @@ -346,8 +346,9 @@ handle_option([{role, _} = Opt | Rest], SocketOptions, SshOptions) ->
handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]); handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
handle_option([{compression, _} = Opt | Rest], SocketOptions, SshOptions) -> handle_option([{compression, _} = Opt | Rest], SocketOptions, SshOptions) ->
handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]); handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
handle_option([{allow_user_interaction, _} = Opt | Rest], SocketOptions, SshOptions) -> %%Backwards compatibility
handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]); handle_option([{allow_user_interaction, Value} | Rest], SocketOptions, SshOptions) ->
handle_option(Rest, SocketOptions, [handle_ssh_option({user_interaction, Value}) | SshOptions]);
handle_option([{infofun, _} = Opt | Rest],SocketOptions, SshOptions) -> handle_option([{infofun, _} = Opt | Rest],SocketOptions, SshOptions) ->
handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]); handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
handle_option([{connectfun, _} = Opt | Rest], SocketOptions, SshOptions) -> handle_option([{connectfun, _} = Opt | Rest], SocketOptions, SshOptions) ->
Expand All @@ -366,6 +367,8 @@ handle_option([{ssh_cli, _} = Opt | Rest], SocketOptions, SshOptions) ->
handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]); handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
handle_option([{shell, _} = Opt | Rest], SocketOptions, SshOptions) -> handle_option([{shell, _} = Opt | Rest], SocketOptions, SshOptions) ->
handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]); handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
handle_option([{exec, _} = Opt | Rest], SocketOptions, SshOptions) ->
handle_option(Rest, SocketOptions, [handle_ssh_option(Opt) | SshOptions]);
handle_option([Opt | Rest], SocketOptions, SshOptions) -> handle_option([Opt | Rest], SocketOptions, SshOptions) ->
handle_option(Rest, [handle_inet_option(Opt) | SocketOptions], SshOptions). handle_option(Rest, [handle_inet_option(Opt) | SocketOptions], SshOptions).


Expand Down Expand Up @@ -401,8 +404,9 @@ handle_ssh_option({key_cb, Value} = Opt) when is_atom(Value) ->
Opt; Opt;
handle_ssh_option({compression, Value} = Opt) when is_atom(Value) -> handle_ssh_option({compression, Value} = Opt) when is_atom(Value) ->
Opt; Opt;
handle_ssh_option({allow_user_interaction, Value} = Opt) when Value == true; handle_ssh_option({exec, {Module, Function, _}} = Opt) when is_atom(Module),
Value == false -> is_atom(Function) ->

Opt; Opt;
handle_ssh_option({infofun, Value} = Opt) when is_function(Value) -> handle_ssh_option({infofun, Value} = Opt) when is_function(Value) ->
Opt; Opt;
Expand All @@ -412,11 +416,12 @@ handle_ssh_option({disconnectfun , Value} = Opt) when is_function(Value) ->
Opt; Opt;
handle_ssh_option({failfun, Value} = Opt) when is_function(Value) -> handle_ssh_option({failfun, Value} = Opt) when is_function(Value) ->
Opt; Opt;
handle_ssh_option({ip_v6_disabled, Value} = Opt) when is_function(Value) -> handle_ssh_option({ip_v6_disabled, Value} = Opt) when Value == true;
Value == false ->
Opt; Opt;
handle_ssh_option({transport, {Protocol, Cb, ClosTag}} = Opt) when is_atom(Protocol), handle_ssh_option({transport, {Protocol, Cb, ClosTag}} = Opt) when is_atom(Protocol),
is_atom(Cb), is_atom(Cb),
is_atom(ClosTag) -> is_atom(ClosTag) ->
Opt; Opt;
handle_ssh_option({subsystems, Value} = Opt) when is_list(Value) -> handle_ssh_option({subsystems, Value} = Opt) when is_list(Value) ->
Opt; Opt;
Expand Down Expand Up @@ -495,4 +500,3 @@ verify_data(Data, Signature, Algorithm) when is_binary(Data), is_binary(Signatur
Error -> Error ->
Error Error
end. end.

16 changes: 6 additions & 10 deletions lib/ssh/src/ssh_auth.erl
Expand Up @@ -71,7 +71,7 @@ password_msg([#ssh{opts = Opts, io_cb = IoCb,
ssh_bits:install_messages(userauth_passwd_messages()), ssh_bits:install_messages(userauth_passwd_messages()),
Password = case proplists:get_value(password, Opts) of Password = case proplists:get_value(password, Opts) of
undefined -> undefined ->
user_interaction(Opts, IoCb); user_interaction(IoCb);
PW -> PW ->
PW PW
end, end,
Expand All @@ -89,13 +89,10 @@ password_msg([#ssh{opts = Opts, io_cb = IoCb,
Ssh) Ssh)
end. end.


user_interaction(Opts, IoCb) -> user_interaction(ssh_no_io) ->
case proplists:get_value(allow_user_interaction, Opts, true) of not_ok;
true -> user_interaction(IoCb) ->
IoCb:read_password("ssh password: "); IoCb:read_password("ssh password: ").
false ->
not_ok
end.




%% See RFC 4256 for info on keyboard-interactive %% See RFC 4256 for info on keyboard-interactive
Expand Down Expand Up @@ -124,8 +121,7 @@ init_userauth_request_msg(#ssh{opts = Opts} = Ssh) ->
FirstAlg = algorithm(proplists:get_value(public_key_alg, Opts, FirstAlg = algorithm(proplists:get_value(public_key_alg, Opts,
?PREFERRED_PK_ALG)), ?PREFERRED_PK_ALG)),
SecondAlg = other_alg(FirstAlg), SecondAlg = other_alg(FirstAlg),
AllowUserInt = proplists:get_value(allow_user_interaction, Opts, AllowUserInt = proplists:get_value(user_interaction, Opts, true),
true),
Prefs = method_preference(FirstAlg, SecondAlg, AllowUserInt), Prefs = method_preference(FirstAlg, SecondAlg, AllowUserInt),
ssh_transport:ssh_packet(Msg, Ssh#ssh{user = User, ssh_transport:ssh_packet(Msg, Ssh#ssh{user = User,
userauth_preference = Prefs, userauth_preference = Prefs,
Expand Down
36 changes: 34 additions & 2 deletions lib/ssh/test/ssh_basic_SUITE.erl
Expand Up @@ -183,7 +183,29 @@ app_test(doc) ->
app_test(Config) when is_list(Config) -> app_test(Config) when is_list(Config) ->
?t:app_test(ssh), ?t:app_test(ssh),
ok. ok.
%%--------------------------------------------------------------------
misc_ssh_options(doc) ->
["Test that we can set some misc options not tested elsewhere, "
"some options not yet present are not decided if we should support or "
"if they need thier own test case."];
misc_ssh_options(suite) ->
[];
misc_ssh_options(Config) when is_list(Config) ->
SystemDir = filename:join(?config(priv_dir, Config), system),
UserDir = ?config(priv_dir, Config),

CMiscOpt0 = [{connecect_timeout, 1000}, {ip_v6_disable, false}, {user_dir, UserDir}],
CMiscOpt1 = [{connecect_timeout, infinity}, {ip_v6_disable, true}, {user_dir, UserDir}],
SMiscOpt0 = [{ip_v6_disable, false}, {user_dir, UserDir}, {system_dir, SystemDir}],
SMiscOpt1 = [{ip_v6_disable, true}, {user_dir, UserDir}, {system_dir, SystemDir}],

ClientOpts = ?config(client_opts, Config),
ServerOpts = ?config(server_opts, Config),

basic_test([{client_opts, CMiscOpt0 ++ ClientOpts}, {server_opts, SMiscOpt0 ++ ServerOpts}]),
basic_test([{client_opts, CMiscOpt1 ++ ClientOpts}, {server_opts, SMiscOpt1 ++ ServerOpts}]).


%%--------------------------------------------------------------------
exec(doc) -> exec(doc) ->
["Test api function ssh_connection:exec"]; ["Test api function ssh_connection:exec"];


Expand Down Expand Up @@ -500,13 +522,14 @@ internal_error(Config) when is_list(Config) ->
SystemDir = filename:join(?config(priv_dir, Config), system), SystemDir = filename:join(?config(priv_dir, Config), system),
UserDir = ?config(priv_dir, Config), UserDir = ?config(priv_dir, Config),


{_Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, SystemDir}, {Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, SystemDir},
{user_dir, UserDir}, {user_dir, UserDir},
{failfun, fun ssh_test_lib:failfun/2}]), {failfun, fun ssh_test_lib:failfun/2}]),
{error,"Internal error"} = {error,"Internal error"} =
ssh:connect(Host, Port, [{silently_accept_hosts, true}, ssh:connect(Host, Port, [{silently_accept_hosts, true},
{user_dir, UserDir}, {user_dir, UserDir},
{user_interaction, false}]). {user_interaction, false}]),
ssh:stop_daemon(Pid).


%%-------------------------------------------------------------------- %%--------------------------------------------------------------------
close(doc) -> close(doc) ->
Expand Down Expand Up @@ -539,3 +562,12 @@ close(Config) when is_list(Config) ->
%%-------------------------------------------------------------------- %%--------------------------------------------------------------------
%% Internal functions %% Internal functions
%%-------------------------------------------------------------------- %%--------------------------------------------------------------------

basic_test(Config) ->
ClientOpts = ?config(client_opts, Config),
ServerOpts = ?config(server_opts, Config),

{Pid, Host, Port} = ssh_test_lib:daemon(ServerOpts),
{ok, CM} = ssh:connect(Host, Port, ClientOpts),
ok = ssh:close(CM),
ssh:stop_daemon(Pid).

0 comments on commit b85e884

Please sign in to comment.