File 3832-ssh-Make-and-adjust-tests.patch of Package erlang
From 230b64a71b2638a3552a72bd65af5a19b20cf20f Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Tue, 9 Mar 2021 16:54:07 +0100
Subject: [PATCH 2/3] ssh: Make and adjust tests
---
lib/ssh/test/ssh_compat_SUITE.erl | 6 +-
lib/ssh/test/ssh_options_SUITE.erl | 14 +-
lib/ssh/test/ssh_pubkey_SUITE.erl | 306 +++++++++++++++++++----------
3 files changed, 215 insertions(+), 111 deletions(-)
diff --git a/lib/ssh/test/ssh_compat_SUITE.erl b/lib/ssh/test/ssh_compat_SUITE.erl
index 6df42660ed..bb46653657 100644
--- a/lib/ssh/test/ssh_compat_SUITE.erl
+++ b/lib/ssh/test/ssh_compat_SUITE.erl
@@ -310,6 +310,7 @@ all_algorithms_sftp_exec_reneg_otp_is_client(Config) ->
%%--------------------------------------------------------------------
renegotiation_otp_is_server(Config) ->
PublicKeyAlgs = [A || {public_key,A} <- proplists:get_value(common_remote_client_algs, Config, [])],
+ ct:log("PublicKeyAlgs = ~p", [PublicKeyAlgs]),
UserDir = setup_remote_priv_and_local_auth_keys(hd(PublicKeyAlgs), Config),
SftpRootDir = new_dir(Config),
ct:log("Rootdir = ~p",[SftpRootDir]),
@@ -321,6 +322,7 @@ renegotiation_otp_is_server(Config) ->
{user_dir, UserDir},
{user_passwords, [{?USER,?PASSWD}]},
{failfun, fun ssh_test_lib:failfun/2},
+ {modify_algorithms, [{append, [{public_key,PublicKeyAlgs}]}]},
{connectfun,
fun(_,_,_) ->
HostConnRef = self(),
@@ -1237,13 +1239,13 @@ call_sftp_in_docker(Config, ServerIP, ServerPort, Cmnds, UserDir, Ref) ->
recv_log_msgs(C, Ch) ->
receive
{ssh_cm,C,{closed,Ch}} ->
- %% ct:log("Channel closed ~p",[{closed,1}]),
+ ct:log("Channel closed ~p",[{closed,1}]),
ok;
{ssh_cm,C,{data,Ch,1,Msg}} ->
ct:log("*** ERROR from docker:~n~s",[Msg]),
recv_log_msgs(C, Ch);
{ssh_cm,C,_Msg} ->
- %% ct:log("Got ~p",[_Msg]),
+ ct:log("Got ~p",[_Msg]),
recv_log_msgs(C, Ch)
after
30000 ->
diff --git a/lib/ssh/test/ssh_options_SUITE.erl b/lib/ssh/test/ssh_options_SUITE.erl
index 5125710471..36d3e16a18 100644
--- a/lib/ssh/test/ssh_options_SUITE.erl
+++ b/lib/ssh/test/ssh_options_SUITE.erl
@@ -1569,6 +1569,18 @@ config_file(Config) ->
ct:log("ServerAlgs =~n~p~n~nOurAlgs =~n~p~n~nCommonAlgs =~n~p",[ServerAlgs,OurAlgs,CommonAlgs]),
Nkex = length(proplists:get_value(kex, CommonAlgs, [])),
+ %% Adjust for very old ssh daemons that only supports ssh-rsa and ssh-dss:
+ AdjustClient =
+ case proplists:get_value(public_key,ServerAlgs,[]) -- ['ssh-rsa','ssh-dss'] of
+ [] ->
+ %% Old, let the client support them also:
+ ct:log("Adjust the client's public_key set", []),
+ [{public_key, ['ssh-rsa','ssh-dss']}];
+ [_|_] ->
+ %% Ok, let the client be un-modified:
+ []
+ end,
+
case {ServerAlgs, ssh_test_lib:some_empty(CommonAlgs)} of
{[],_} ->
{skip, "No server algorithms found"};
@@ -1586,7 +1598,7 @@ config_file(Config) ->
[{ssh, [{preferred_algorithms,
[{cipher, [Ch1]},
{kex, [K1a]}
- ]},
+ ] ++ AdjustClient},
{client_options,
[{modify_algorithms,
[{rm, [{kex, [K1a]}]},
diff --git a/lib/ssh/test/ssh_pubkey_SUITE.erl b/lib/ssh/test/ssh_pubkey_SUITE.erl
index 481666d25e..885c9914a0 100644
--- a/lib/ssh/test/ssh_pubkey_SUITE.erl
+++ b/lib/ssh/test/ssh_pubkey_SUITE.erl
@@ -34,31 +34,34 @@
]).
-export([
+ check_dsa_disabled/1,
+ check_rsa_sha1_disabled/1,
connect_dsa_to_dsa/1,
connect_dsa_to_ecdsa/1,
connect_dsa_to_ed25519/1,
connect_dsa_to_ed448/1,
- connect_dsa_to_rsa/1,
+ connect_dsa_to_rsa_sha2/1,
connect_ecdsa_to_dsa/1,
connect_ecdsa_to_ecdsa/1,
connect_ecdsa_to_ed25519/1,
connect_ecdsa_to_ed448/1,
- connect_ecdsa_to_rsa/1,
+ connect_ecdsa_to_rsa_sha2/1,
connect_ed25519_to_dsa/1,
connect_ed25519_to_ecdsa/1,
connect_ed25519_to_ed25519/1,
connect_ed25519_to_ed448/1,
- connect_ed25519_to_rsa/1,
+ connect_ed25519_to_rsa_sha2/1,
connect_ed448_to_dsa/1,
connect_ed448_to_ecdsa/1,
connect_ed448_to_ed25519/1,
connect_ed448_to_ed448/1,
- connect_ed448_to_rsa/1,
- connect_rsa_to_dsa/1,
- connect_rsa_to_ecdsa/1,
- connect_rsa_to_ed25519/1,
- connect_rsa_to_ed448/1,
- connect_rsa_to_rsa/1,
+ connect_ed448_to_rsa_sha2/1,
+ connect_rsa_sha1_to_dsa/1,
+ connect_rsa_sha2_to_dsa/1,
+ connect_rsa_sha2_to_ecdsa/1,
+ connect_rsa_sha2_to_ed25519/1,
+ connect_rsa_sha2_to_ed448/1,
+ connect_rsa_sha2_to_rsa_sha2/1,
chk_known_hosts/1
]).
@@ -82,19 +85,19 @@ all() ->
].
--define(tests_old, [connect_rsa_to_rsa,
- connect_rsa_to_dsa,
- connect_rsa_to_ecdsa,
- connect_dsa_to_rsa,
+-define(tests_old, [connect_rsa_sha2_to_rsa_sha2,
+ connect_rsa_sha1_to_dsa,
+ connect_rsa_sha2_to_dsa,
+ connect_rsa_sha2_to_ecdsa,
+ connect_dsa_to_rsa_sha2,
connect_dsa_to_dsa,
connect_dsa_to_ecdsa,
- connect_ecdsa_to_rsa,
+ connect_ecdsa_to_rsa_sha2,
connect_ecdsa_to_dsa,
connect_ecdsa_to_ecdsa
]).
--define(tests_new, [
- connect_dsa_to_ed25519,
+-define(tests_new, [connect_dsa_to_ed25519,
connect_dsa_to_ed448,
connect_ecdsa_to_ed25519,
connect_ecdsa_to_ed448,
@@ -102,20 +105,20 @@ all() ->
connect_ed25519_to_ecdsa,
connect_ed25519_to_ed448,
connect_ed25519_to_ed25519,
- connect_ed25519_to_rsa,
+ connect_ed25519_to_rsa_sha2,
connect_ed448_to_dsa,
connect_ed448_to_ecdsa,
connect_ed448_to_ed25519,
connect_ed448_to_ed448,
- connect_ed448_to_rsa,
- connect_rsa_to_ed25519,
- connect_rsa_to_ed448
+ connect_ed448_to_rsa_sha2,
+ connect_rsa_sha2_to_ed25519,
+ connect_rsa_sha2_to_ed448
| ?tests_old % but taken from the new format directory
]).
groups() ->
[{new_format, [], ?tests_new},
- {old_format, [], ?tests_old++[{group,passphrase}]},
+ {old_format, [], [check_dsa_disabled, check_rsa_sha1_disabled | ?tests_old++[{group,passphrase}] ]},
{passphrase, [], ?tests_old},
{option_space,[], [{group,new_format}]}
].
@@ -183,18 +186,20 @@ end_per_group(_, Config) ->
Config.
%%%----------------------------------------------------------------
-init_per_testcase(connect_rsa_to_rsa, Config0) ->
- setup_user_system_dir(rsa, rsa, Config0);
-init_per_testcase(connect_rsa_to_dsa, Config0) ->
- setup_user_system_dir(rsa, dsa, Config0);
-init_per_testcase(connect_rsa_to_ecdsa, Config0) ->
- setup_user_system_dir(rsa, ecdsa, Config0);
-init_per_testcase(connect_rsa_to_ed25519, Config0) ->
- setup_user_system_dir(rsa, ed25519, Config0);
-init_per_testcase(connect_rsa_to_ed448, Config0) ->
- setup_user_system_dir(rsa, ed448, Config0);
-init_per_testcase(connect_dsa_to_rsa, Config0) ->
- setup_user_system_dir(dsa, rsa, Config0);
+init_per_testcase(connect_rsa_sha2_to_rsa_sha2, Config0) ->
+ setup_user_system_dir(rsa_sha2, rsa_sha2, Config0);
+init_per_testcase(connect_rsa_sha1_to_dsa, Config0) ->
+ setup_user_system_dir(rsa_sha1, dsa, Config0);
+init_per_testcase(connect_rsa_sha2_to_dsa, Config0) ->
+ setup_user_system_dir(rsa_sha2, dsa, Config0);
+init_per_testcase(connect_rsa_sha2_to_ecdsa, Config0) ->
+ setup_user_system_dir(rsa_sha2, ecdsa, Config0);
+init_per_testcase(connect_rsa_sha2_to_ed25519, Config0) ->
+ setup_user_system_dir(rsa_sha2, ed25519, Config0);
+init_per_testcase(connect_rsa_sha2_to_ed448, Config0) ->
+ setup_user_system_dir(rsa_sha2, ed448, Config0);
+init_per_testcase(connect_dsa_to_rsa_sha2, Config0) ->
+ setup_user_system_dir(dsa, rsa_sha2, Config0);
init_per_testcase(connect_dsa_to_dsa, Config0) ->
setup_user_system_dir(dsa, dsa, Config0);
init_per_testcase(connect_dsa_to_ecdsa, Config0) ->
@@ -203,8 +208,8 @@ init_per_testcase(connect_dsa_to_ed25519
setup_user_system_dir(dsa, ed25519, Config0);
init_per_testcase(connect_dsa_to_ed448, Config0) ->
setup_user_system_dir(dsa, ed448, Config0);
-init_per_testcase(connect_ecdsa_to_rsa, Config0) ->
- setup_user_system_dir(ecdsa, rsa, Config0);
+init_per_testcase(connect_ecdsa_to_rsa_sha2, Config0) ->
+ setup_user_system_dir(ecdsa, rsa_sha2, Config0);
init_per_testcase(connect_ecdsa_to_dsa, Config0) ->
setup_user_system_dir(ecdsa, dsa, Config0);
init_per_testcase(connect_ecdsa_to_ecdsa, Config0) ->
@@ -213,8 +218,8 @@ init_per_testcase(connect_ecdsa_to_ed255
setup_user_system_dir(ecdsa, ed25519, Config0);
init_per_testcase(connect_ecdsa_to_ed448, Config0) ->
setup_user_system_dir(ecdsa, ed448, Config0);
-init_per_testcase(connect_ed25519_to_rsa, Config0) ->
- setup_user_system_dir(ed25519, rsa, Config0);
+init_per_testcase(connect_ed25519_to_rsa_sha2, Config0) ->
+ setup_user_system_dir(ed25519, rsa_sha2, Config0);
init_per_testcase(connect_ed25519_to_dsa, Config0) ->
setup_user_system_dir(ed25519, dsa, Config0);
init_per_testcase(connect_ed25519_to_ecdsa, Config0) ->
@@ -223,8 +228,8 @@ init_per_testcase(connect_ed25519_to_ed2
setup_user_system_dir(ed25519, ed25519, Config0);
init_per_testcase(connect_ed25519_to_ed448, Config0) ->
setup_user_system_dir(ed25519, ed448, Config0);
-init_per_testcase(connect_ed448_to_rsa, Config0) ->
- setup_user_system_dir(ed448, rsa, Config0);
+init_per_testcase(connect_ed448_to_rsa_sha2, Config0) ->
+ setup_user_system_dir(ed448, rsa_sha2, Config0);
init_per_testcase(connect_ed448_to_dsa, Config0) ->
setup_user_system_dir(ed448, dsa, Config0);
init_per_testcase(connect_ed448_to_ecdsa, Config0) ->
@@ -233,31 +238,41 @@ init_per_testcase(connect_ed448_to_ed255
setup_user_system_dir(ed448, ed25519, Config0);
init_per_testcase(connect_ed448_to_ed448, Config0) ->
setup_user_system_dir(ed448, ed448, Config0);
+
+init_per_testcase(check_dsa_disabled, Config0) ->
+ setup_default_user_system_dir(dsa, Config0);
+init_per_testcase(check_rsa_sha1_disabled, Config0) ->
+ setup_default_user_system_dir(rsa_sha1, Config0);
+
init_per_testcase(_, Config) ->
Config.
+
end_per_testcase(_, Config) ->
Config.
%%%----------------------------------------------------------------
%%% Test Cases ----------------------------------------------------
%%%----------------------------------------------------------------
-connect_rsa_to_rsa(Config) ->
+connect_rsa_sha2_to_rsa_sha2(Config) ->
try_connect(Config).
-connect_rsa_to_dsa(Config) ->
+connect_rsa_sha1_to_dsa(Config) ->
try_connect(Config).
-connect_rsa_to_ecdsa(Config) ->
+connect_rsa_sha2_to_dsa(Config) ->
+ try_connect(Config).
+
+connect_rsa_sha2_to_ecdsa(Config) ->
try_connect(Config).
-connect_rsa_to_ed25519(Config) ->
+connect_rsa_sha2_to_ed25519(Config) ->
try_connect(Config).
-connect_rsa_to_ed448(Config) ->
+connect_rsa_sha2_to_ed448(Config) ->
try_connect(Config).
-connect_dsa_to_rsa(Config) ->
+connect_dsa_to_rsa_sha2(Config) ->
try_connect(Config).
connect_dsa_to_dsa(Config) ->
@@ -272,7 +287,7 @@ connect_dsa_to_ed25519(Config) ->
connect_dsa_to_ed448(Config) ->
try_connect(Config).
-connect_ecdsa_to_rsa(Config) ->
+connect_ecdsa_to_rsa_sha2(Config) ->
try_connect(Config).
connect_ecdsa_to_dsa(Config) ->
@@ -287,7 +302,7 @@ connect_ecdsa_to_ed25519(Config) ->
connect_ecdsa_to_ed448(Config) ->
try_connect(Config).
-connect_ed25519_to_rsa(Config) ->
+connect_ed25519_to_rsa_sha2(Config) ->
try_connect(Config).
connect_ed25519_to_dsa(Config) ->
@@ -302,7 +317,7 @@ connect_ed25519_to_ed25519(Config) ->
connect_ed25519_to_ed448(Config) ->
try_connect(Config).
-connect_ed448_to_rsa(Config) ->
+connect_ed448_to_rsa_sha2(Config) ->
try_connect(Config).
connect_ed448_to_dsa(Config) ->
@@ -317,6 +332,13 @@ connect_ed448_to_ed25519(Config) ->
connect_ed448_to_ed448(Config) ->
try_connect(Config).
+%%%----------------------------------------------------------------
+check_dsa_disabled(Config) ->
+ try_connect_disabled(Config).
+
+check_rsa_sha1_disabled(Config) ->
+ try_connect_disabled(Config).
+
%%%----------------------------------------------------------------
chk_known_hosts(Config) ->
@@ -370,11 +392,13 @@ chk_known_hosts(Config) ->
try_connect({skip,Reason}) ->
{skip,Reason};
try_connect(Config) ->
+%ssh_dbg:start(fun ct:pal/2), dbg:tp(ssh_transport,sign,3,x), dbg:tp(ssh_transport,verify,5,x),
SystemDir = proplists:get_value(system_dir, Config),
UserDir = proplists:get_value(user_dir, Config),
ClientOpts = proplists:get_value(client_opts, Config, []),
DaemonOpts = proplists:get_value(daemon_opts, Config, []),
+ ssh_dbg:start(fun ct:log/2), ssh_dbg:on([alg]),
{Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, SystemDir},
{user_dir, UserDir}
| DaemonOpts]),
@@ -384,46 +408,29 @@ try_connect(Config) ->
{user_interaction, false}
| ClientOpts]),
ssh:close(C),
+ ssh_dbg:stop(),
ssh:stop_daemon(Pid).
+
+try_connect_disabled(Config) ->
+ try try_connect(Config)
+ of _ -> {fail, "non-default algorithm accepted"}
+ catch error:{badmatch,{error,"Service not available"}} -> ok
+ end.
+
%%%----------------------------------------------------------------
%%% Local ---------------------------------------------------------
%%%----------------------------------------------------------------
setup_user_system_dir(ClientAlg, ServerAlg, Config) ->
- case supported(public_keys, ClientAlg) andalso supported(public_keys, ServerAlg) of
+ case supported(public_key, ClientAlg) andalso supported(public_key, ServerAlg) of
true ->
- PrivDir = proplists:get_value(priv_dir, Config),
- KeySrcDir = proplists:get_value(key_src_dir, Config),
- Fmt = proplists:get_value(fmt, Config),
-
- System = lists:concat(["system_", ClientAlg, "_", ServerAlg, "_", Fmt]),
- SystemDir = filename:join(PrivDir, System),
- file:make_dir(SystemDir),
-
- User = lists:concat(["user_", ClientAlg, "_", ServerAlg, "_", Fmt]),
- UserDir = filename:join(PrivDir, User),
- file:make_dir(UserDir),
-
- HostSrcFile = filename:join(KeySrcDir, file(host,ServerAlg)),
- HostDstFile = filename:join(SystemDir, file(host,ServerAlg)),
-
- UserSrcFile = filename:join(KeySrcDir, file(user,ClientAlg)),
- UserDstFile = filename:join(UserDir, file(user,ClientAlg)),
-
- UserPubSrcFile = filename:join(KeySrcDir, file(user,ClientAlg)++".pub"),
- AuthorizedKeys = filename:join(UserDir, "authorized_keys"),
-
try
- {ok,_} = file:copy(UserSrcFile, UserDstFile),
- {ok,_} = file:copy(UserPubSrcFile, AuthorizedKeys),
- {ok,_} = file:copy(HostSrcFile, HostDstFile)
+ setup_dirs(ClientAlg, ServerAlg, Config)
of
- _ ->
- ModAlgs = [{modify_algorithms,
- [{append,[{public_key,
- lists:usort([alg(ClientAlg),
- alg(ServerAlg)])}]}]}
- ],
+ {ok, {SystemDir,UserDir}} ->
+ ModAlgs = [{preferred_algorithms,
+ [{public_key, lists:usort([alg(ClientAlg), alg(ServerAlg)])}]
+ }],
[{system_dir,SystemDir},
{user_dir,UserDir}
| extend_optsL([daemon_opts,client_opts], ModAlgs, Config)]
@@ -437,38 +444,120 @@ setup_user_system_dir(ClientAlg, ServerA
{skip, unsupported_algorithm}
end.
+
+setup_default_user_system_dir(ClientAlg, Config) ->
+ ServerAlg = ecdsa,
+ case default(public_key, ClientAlg) of
+ false ->
+ case supported(public_key, ClientAlg) of
+ true ->
+ case supported(public_key, ServerAlg) of
+ true ->
+ try
+ setup_dirs(ClientAlg, ServerAlg, Config)
+ of
+ {ok, {SystemDir,UserDir}} ->
+ ModAlgs = [{modify_algorithms,
+ [{append,[{public_key,[alg(ServerAlg)]}]},
+ {rm, [{public_key,[alg(ClientAlg)|inv_algs(ClientAlg)]}]}
+ ]}],
+ [{system_dir,SystemDir},
+ {user_dir,UserDir}
+ | extend_optsL([daemon_opts,client_opts], ModAlgs, Config)]
+ catch
+ error:{badmatch,{error,enoent}}:S ->
+ ct:log("~p:~p Stack:~n~p", [?MODULE,?LINE,S]),
+ {skip, no_key_file_found}
+ end;
+ false ->
+ {skip, unsupported_server_algorithm}
+ end;
+ false ->
+ {skip, unsupported_client_algorithm}
+ end;
+ true ->
+ {fail, disabled_algorithm_present}
+ end.
+
+
+setup_dirs(ClientAlg, ServerAlg, Config) ->
+ PrivDir = proplists:get_value(priv_dir, Config),
+ KeySrcDir = proplists:get_value(key_src_dir, Config),
+ Fmt = proplists:get_value(fmt, Config),
+
+ System = lists:concat(["system_", ClientAlg, "_", ServerAlg, "_", Fmt]),
+ SystemDir = filename:join(PrivDir, System),
+ file:make_dir(SystemDir),
+
+ User = lists:concat(["user_", ClientAlg, "_", ServerAlg, "_", Fmt]),
+ UserDir = filename:join(PrivDir, User),
+ file:make_dir(UserDir),
+
+ HostSrcFile = filename:join(KeySrcDir, file(src,host,ServerAlg)),
+ HostDstFile = filename:join(SystemDir, file(dst,host,ServerAlg)),
+
+ UserSrcFile = filename:join(KeySrcDir, file(src,user,ClientAlg)),
+ UserDstFile = filename:join(UserDir, file(dst,user,ClientAlg)),
+
+ UserPubSrcFile = filename:join(KeySrcDir, file(src,user,ClientAlg)++".pub"),
+ AuthorizedKeys = filename:join(UserDir, "authorized_keys"),
+
+ ct:log("UserSrcFile = ~p~nUserDstFile = ~p", [UserSrcFile, UserDstFile]),
+ {ok,_} = file:copy(UserSrcFile, UserDstFile),
+ ct:log("UserPubSrcFile = ~p~nAuthorizedKeys = ~p", [UserPubSrcFile, AuthorizedKeys]),
+ {ok,_} = file:copy(UserPubSrcFile, AuthorizedKeys),
+ ct:log("HostSrcFile = ~p~nHostDstFile = ~p", [HostSrcFile, HostDstFile]),
+ {ok,_} = file:copy(HostSrcFile, HostDstFile),
+
+ ct:log("SystemDir = ~p~nUserDir = ~p", [SystemDir,UserDir]),
+ {ok, {SystemDir,UserDir}}.
+
%%%----------------------------------------------------------------
-file(host, dsa) -> "ssh_host_dsa_key";
-file(host, ecdsa) -> "ssh_host_ecdsa_key";
-file(host, ed25519) -> "ssh_host_ed25519_key";
-file(host, ed448) -> "ssh_host_ed448_key";
-file(host, rsa) -> "ssh_host_rsa_key";
-file(user, dsa) -> "id_dsa";
-file(user, ecdsa) -> "id_ecdsa";
-file(user, ed25519) -> "id_ed25519";
-file(user, ed448) -> "id_ed448";
-file(user, rsa) -> "id_rsa".
+file( _, host, dsa) -> "ssh_host_dsa_key";
+file( _, host, ecdsa) -> "ssh_host_ecdsa_key";
+file( _, host, ed25519) -> "ssh_host_ed25519_key";
+file( _, host, ed448) -> "ssh_host_ed448_key";
+file( _, host, rsa_sha2)-> "ssh_host_rsa_key";
+file(src, host, rsa_sha1)-> "ssh_host_rsa_key";
+file(dst, host, rsa_sha1)-> "ssh_host_rsa_key";
+file( _, user, dsa) -> "id_dsa";
+file( _, user, ecdsa) -> "id_ecdsa";
+file( _, user, ed25519) -> "id_ed25519";
+file( _, user, ed448) -> "id_ed448";
+file( _, user, rsa_sha2)-> "id_rsa";
+file(src, user, rsa_sha1)-> "id_rsa";
+file(dst, user, rsa_sha1)-> "id_rsa".
alg(dsa) -> 'ssh-dss';
alg(ecdsa) -> 'ecdsa-sha2-nistp256';
alg(ed25519) -> 'ssh-ed25519';
alg(ed448) -> 'ssh-ed448';
-alg(rsa) -> 'ssh-rsa'.
+alg(rsa_sha2)-> 'rsa-sha2-256';
+alg(rsa_sha1)-> 'ssh-rsa'.
+inv_algs(rsa_sha1) -> algs(rsa_sha2);
+inv_algs(_) -> [].
-supported(public_keys, rsa) -> supported(public_key, 'ssh-rsa') orelse
- supported(public_key, 'rsa-sha2-256') orelse
- supported(public_key, 'rsa-sha2-521');
-supported(public_keys, dsa) -> supported(public_key, 'ssh-dss');
-supported(public_keys, ecdsa) -> supported(public_key, 'ecdsa-sha2-nistp256') orelse
- supported(public_key, 'ecdsa-sha2-nistp384') orelse
- supported(public_key, 'ecdsa-sha2-nistp521');
-supported(public_keys, ed448) -> supported(public_key, 'ssh-ed448');
-supported(public_keys, ed25519) -> supported(public_key, 'ssh-ed25519');
-supported(Type, Alg) ->
- case proplists:get_value(Type,ssh_transport:supported_algorithms()) of
- undefined ->
- lists:member(Alg, crypto:supports(Type));
- L ->
- lists:member(Alg, L)
- end.
+algs(dsa) -> ['ssh-dss'];
+algs(ecdsa) -> ['ecdsa-sha2-nistp256', 'ecdsa-sha2-nistp384', 'ecdsa-sha2-521'];
+algs(ed25519) -> ['ssh-ed25519'];
+algs(ed448) -> ['ssh-ed448'];
+algs(rsa_sha2)-> ['rsa-sha2-256', 'rsa-sha2-384', 'rsa-sha2-512'];
+algs(rsa_sha1)-> ['ssh-rsa'];
+algs(A) -> [A].
+
+
+
+default(Type, Alg) -> listed(algs(Alg), ssh_transport:default_algorithms(Type)).
+
+supported(Type, Alg) -> listed(algs(Alg),
+ try
+ ssh_transport:supported_algorithms(Type)
+ catch
+ error:function_clause -> crypto:supports(Type)
+ end).
+
+listed(As, L) -> lists:any(fun(A) -> lists:member(A,L) end,
+ As).
+
+
--
2.26.2