File 3041-ssh-Refactor-ssh_file.patch of Package erlang
From 552353ce0636f762ed8cb4037ef5328eaf38b4ec Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Wed, 5 Feb 2020 21:16:07 +0100
Subject: [PATCH 01/10] ssh: Refactor ssh_file
---
lib/ssh/src/ssh_auth.erl | 2 +-
lib/ssh/src/ssh_file.erl | 491 +++++++++++++++++++-----------------------
lib/ssh/src/ssh_transport.erl | 40 ++--
3 files changed, 241 insertions(+), 292 deletions(-)
diff --git a/lib/ssh/src/ssh_auth.erl b/lib/ssh/src/ssh_auth.erl
index b9813b6b5c..ded9ceb1bc 100644
--- a/lib/ssh/src/ssh_auth.erl
+++ b/lib/ssh/src/ssh_auth.erl
@@ -143,7 +143,7 @@ get_public_key(SigAlg, #ssh{opts = Opts}) ->
{ok, PrivKey} ->
try
%% Check the key - the KeyCb may be a buggy plugin
- true = ssh_transport:valid_key_sha_alg(PrivKey, KeyAlg),
+ true = ssh_transport:valid_key_sha_alg(private, PrivKey, KeyAlg),
Key = ssh_transport:extract_public_key(PrivKey),
public_key:ssh_encode(Key, ssh2_pubkey)
of
diff --git a/lib/ssh/src/ssh_file.erl b/lib/ssh/src/ssh_file.erl
index 510269bbb1..c3caa244f8 100644
--- a/lib/ssh/src/ssh_file.erl
+++ b/lib/ssh/src/ssh_file.erl
@@ -24,59 +24,45 @@
-module(ssh_file).
--behaviour(ssh_server_key_api).
--behaviour(ssh_client_key_api).
-
-include_lib("public_key/include/public_key.hrl").
-include_lib("kernel/include/file.hrl").
-include("ssh.hrl").
--export([host_key/2,
- user_key/2,
- is_host_key/4,
- add_host_key/3,
- is_auth_key/3]).
-
-
--export_type([system_dir_daemon_option/0,
- user_dir_common_option/0,
- user_dir_fun_common_option/0,
- pubkey_passphrase_client_options/0
- ]).
-
+%%%--------------------- server exports ---------------------------
+-behaviour(ssh_server_key_api).
+-export([host_key/2, is_auth_key/3]).
+-export_type([system_dir_daemon_option/0]).
-type system_dir_daemon_option() :: {system_dir, string()}.
--type user_dir_common_option() :: {user_dir, string()}.
--type user_dir_fun_common_option() :: {user_dir_fun, user2dir()}.
--type user2dir() :: fun((RemoteUserName::string()) -> UserDir :: string()) .
+%%%--------------------- client exports ---------------------------
+-behaviour(ssh_client_key_api).
+-export([is_host_key/4, user_key/2, add_host_key/3]).
+-export_type([pubkey_passphrase_client_options/0]).
-type pubkey_passphrase_client_options() :: {dsa_pass_phrase, string()}
| {rsa_pass_phrase, string()}
%% Not yet implemented: | {ed25519_pass_phrase, string()}
%% Not yet implemented: | {ed448_pass_phrase, string()}
| {ecdsa_pass_phrase, string()} .
+%%%--------------------- common exports ---------------------------
+-export_type([user_dir_common_option/0,
+ user_dir_fun_common_option/0
+ ]).
--define(PERM_700, 8#700).
--define(PERM_644, 8#644).
-
+-type user_dir_common_option() :: {user_dir, string()}.
+-type user_dir_fun_common_option() :: {user_dir_fun, user2dir()}.
+-type user2dir() :: fun((RemoteUserName::string()) -> UserDir :: string()) .
+%%%================================================================
+%%%
%%% API
+%%%
-%% Used by server
+%%%---------------- SERVER API ------------------------------------
host_key(Algorithm, Opts) ->
- File = file_name(system, file_base_name(Algorithm), Opts),
- %% We do not expect host keys to have pass phrases
- %% so probably we could hardcod Password = ignore, but
- %% we keep it as an undocumented option for now.
- Password = proplists:get_value(identity_pass_phrase(Algorithm), Opts, ignore),
- case decode(File, Password) of
- {ok,Key} ->
- check_key_type(Key, Algorithm);
- {error,DecodeError} ->
- {error,DecodeError}
- end.
-
+ read_ssh_key_file(system, private, Algorithm, Opts).
+
is_auth_key(Key, User,Opts) ->
case lookup_user_key(Key, User, Opts) of
{ok, Key} ->
@@ -85,97 +71,49 @@ is_auth_key(Key, User,Opts) ->
false
end.
-
-%% Used by client
-is_host_key(Key, PeerName, Algorithm, Opts) ->
- case lookup_host_key(Key, PeerName, Algorithm, Opts) of
- {ok, Key} ->
- true;
- _ ->
- false
- end.
-
+%%%---------------- CLIENT API ------------------------------------
user_key(Algorithm, Opts) ->
- File = file_name(user, identity_key_filename(Algorithm), Opts),
- Password = proplists:get_value(identity_pass_phrase(Algorithm), Opts, ignore),
- case decode(File, Password) of
- {ok, Key} ->
- check_key_type(Key, Algorithm);
- Error ->
- Error
- end.
-
-
-%% Internal functions %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-check_key_type(Key, Algorithm) ->
- case ssh_transport:valid_key_sha_alg(Key,Algorithm) of
- true -> {ok,Key};
- false -> {error,bad_keytype_in_file}
- end.
+ read_ssh_key_file(user, private, Algorithm, Opts).
-file_base_name('ssh-rsa' ) -> "ssh_host_rsa_key";
-file_base_name('rsa-sha2-256' ) -> "ssh_host_rsa_key";
-file_base_name('rsa-sha2-384' ) -> "ssh_host_rsa_key";
-file_base_name('rsa-sha2-512' ) -> "ssh_host_rsa_key";
-file_base_name('ssh-dss' ) -> "ssh_host_dsa_key";
-file_base_name('ecdsa-sha2-nistp256') -> "ssh_host_ecdsa_key";
-file_base_name('ecdsa-sha2-nistp384') -> "ssh_host_ecdsa_key";
-file_base_name('ecdsa-sha2-nistp521') -> "ssh_host_ecdsa_key";
-file_base_name('ssh-ed25519' ) -> "ssh_host_ed25519_key";
-file_base_name('ssh-ed448' ) -> "ssh_host_ed448_key";
-file_base_name(_ ) -> "ssh_host_key".
-
-decode(File, Password) ->
- try {ok, decode_ssh_file(read_ssh_file(File), Password)}
- catch
- throw:Reason ->
- {error, Reason};
- error:Reason ->
- {error, Reason}
- end.
-
-read_ssh_file(File) ->
- {ok, Bin} = file:read_file(File),
- Bin.
-
-%% Public key
-decode_ssh_file(SshBin, public_key) ->
- public_key:ssh_decode(SshBin, public_key);
-
-%% Private Key
-decode_ssh_file(Pem, Password) ->
- case public_key:pem_decode(Pem) of
- [{_, _, not_encrypted} = Entry] ->
- public_key:pem_entry_decode(Entry);
- [Entry] when Password =/= ignore ->
- public_key:pem_entry_decode(Entry, Password);
- _ ->
- throw("No pass phrase provided for private key file")
+is_host_key(Key, PeerName, Algorithm, Opts) ->
+ case ssh_transport:valid_key_sha_alg(public, Key, Algorithm) of
+ true ->
+ case file:open(file_name(user, "known_hosts", Opts), [read, binary]) of
+ {ok, Fd} ->
+ Res = is_host_key_fd(Fd, Key, replace_localhost(PeerName)),
+ file:close(Fd),
+ Res;
+ _ ->
+ false
+ end;
+ false ->
+ false
end.
-
-
-%% lookup_host_key
-%% return {ok, Key(s)} or {error, not_found}
-%%
-lookup_host_key(KeyToMatch, Host, Alg, Opts) ->
- Host1 = replace_localhost(Host),
- do_lookup_host_key(KeyToMatch, Host1, Alg, Opts).
-
add_host_key(Host, Key, Opts) ->
Host1 = add_ip(replace_localhost(Host)),
KnownHosts = file_name(user, "known_hosts", Opts),
case file:open(KnownHosts, [write,append]) of
{ok, Fd} ->
- ok = file:change_mode(KnownHosts, ?PERM_644),
- Res = add_key_fd(Fd, Host1, Key),
+ ok = file:change_mode(KnownHosts, 8#644),
+ SshBin = public_key:ssh_encode([{Key, [{hostnames, [Host1]}]}], known_hosts),
+ Res = file:write(Fd, SshBin),
file:close(Fd),
Res;
Error ->
Error
end.
+
+%%%================================================================
+%%%
+%%% Local functions
+%%%
+
+%%%---------------- SERVER FUNCTIONS ------------------------------
+
+%%% Try to find the User's public key Key in "authorized_keys" or "authorized_keys2"
lookup_user_key(Key, User, Opts) ->
SshDir = ssh_dir({remoteuser,User}, Opts),
case lookup_user_key_f(Key, User, SshDir, "authorized_keys", Opts) of
@@ -185,49 +123,74 @@ lookup_user_key(Key, User, Opts) ->
lookup_user_key_f(Key, User, SshDir, "authorized_keys2", Opts)
end.
+lookup_user_key_f(_, _User, [], _F, _Opts) ->
+ {error, nouserdir};
+lookup_user_key_f(_, _User, nouserdir, _F, _Opts) ->
+ {error, nouserdir};
+lookup_user_key_f(Key, _User, Dir, F, _Opts) ->
+ FileName = filename:join(Dir, F),
+ case file:open(FileName, [read, binary]) of
+ {ok, Fd} ->
+ Res = lookup_user_key_fd(Fd, Key),
+ file:close(Fd),
+ Res;
+ {error, Reason} ->
+ {error, {{openerr, Reason}, {file, FileName}}}
+ end.
-%%
-%% Utils
-%%
-
-%% server use this to find individual keys for
-%% an individual user when user tries to login
-%% with publickey
-ssh_dir({remoteuser, User}, Opts) ->
- case proplists:get_value(user_dir_fun, Opts) of
- undefined ->
- case proplists:get_value(user_dir, Opts, false) of
- false ->
- default_user_dir();
- Dir ->
- Dir
- end;
- FUN ->
- FUN(User)
- end;
-
-%% client use this to find client ssh keys
-ssh_dir(user, Opts) ->
- case proplists:get_value(user_dir, Opts, false) of
- false -> default_user_dir();
- D -> D
- end;
-
-%% server use this to find server host keys
-ssh_dir(system, Opts) ->
- proplists:get_value(system_dir, Opts, "/etc/ssh").
-
+lookup_user_key_fd(Fd, Key) ->
+ case io:get_line(Fd, '') of
+ eof ->
+ {error, not_found};
+ {error,Error} ->
+ %% Rare... For example NFS errors
+ {error,Error};
+ Line ->
+ try public_key:ssh_decode(Line, auth_keys)
+ of
+ [{Key, _}] ->
+ {ok, Key};
+ _ ->
+ lookup_user_key_fd(Fd, Key)
+ catch
+ _:_ ->
+ []
+ end
+ end.
-file_name(Type, Name, Opts) ->
- FN = filename:join(ssh_dir(Type, Opts), Name),
- FN.
+%%%---------------- CLIENT FUNCTIONS ------------------------------
+is_host_key_fd(Fd, KeyToMatch, Host) ->
+ case io:get_line(Fd, '') of
+ eof ->
+ false;
+ {error,_} ->
+ %% Rare... For example NFS errors
+ false;
+ Line ->
+ try public_key:ssh_decode(Line, known_hosts) of
+ [{Key, Attributes}] when KeyToMatch == Key ->
+ HostList = proplists:get_value(hostnames, Attributes),
+ case lists:member(Host, HostList) of
+ true ->
+ true;
+ _ ->
+ is_host_key_fd(Fd, KeyToMatch, Host)
+ end;
+ _ ->
+ is_host_key_fd(Fd, KeyToMatch, Host)
+ catch
+ _:_ ->
+ false
+ end
+ end.
+%%%--------------------------------
%% in: "host" out: "host,1.2.3.4.
add_ip(IP) when is_tuple(IP) ->
ssh_connection:encode_ip(IP);
-add_ip(Host) ->
+add_ip(Host) ->
case inet:getaddr(Host, inet) of
{ok, Addr} ->
case ssh_connection:encode_ip(Addr) of
@@ -235,7 +198,7 @@ add_ip(Host) ->
IPString -> Host ++ "," ++ IPString
end;
_ -> Host
- end.
+ end.
replace_localhost("localhost") ->
{ok, Hostname} = inet:gethostname(),
@@ -243,142 +206,120 @@ replace_localhost("localhost") ->
replace_localhost(Host) ->
Host.
-do_lookup_host_key(KeyToMatch, Host, Alg, Opts) ->
- case file:open(file_name(user, "known_hosts", Opts), [read, binary]) of
- {ok, Fd} ->
- Res = lookup_host_key_fd(Fd, KeyToMatch, Host, Alg),
- file:close(Fd),
- Res;
- {error, enoent} ->
- {error, not_found};
- Error ->
- Error
+%%%---------------- COMMON FUNCTIONS ------------------------------
+
+read_ssh_key_file(Role, PrivPub, Algorithm, Opts) ->
+ File = file_name(Role, file_base_name(Role,Algorithm), Opts),
+ Password = %% Pwd for Host Keys is an undocumented option and should not be used
+ proplists:get_value(identity_pass_phrase(Algorithm), Opts, ignore),
+
+ case file:read_file(File) of
+ {ok, Pem} ->
+ try decode_ssh_file(Pem, Password) of
+ Key ->
+ check_key_type(PrivPub, Key, Algorithm)
+ catch
+ throw:Reason ->
+ {error, Reason};
+ error:Reason ->
+ {error, Reason}
+ end;
+
+ {error, Reason} ->
+ {error, Reason}
end.
-identity_key_filename('ssh-dss' ) -> "id_dsa";
-identity_key_filename('ssh-rsa' ) -> "id_rsa";
-identity_key_filename('rsa-sha2-256' ) -> "id_rsa";
-identity_key_filename('rsa-sha2-384' ) -> "id_rsa";
-identity_key_filename('rsa-sha2-512' ) -> "id_rsa";
-identity_key_filename('ssh-ed25519' ) -> "id_ed25519";
-identity_key_filename('ssh-ed448' ) -> "id_ed448";
-identity_key_filename('ecdsa-sha2-nistp256') -> "id_ecdsa";
-identity_key_filename('ecdsa-sha2-nistp384') -> "id_ecdsa";
-identity_key_filename('ecdsa-sha2-nistp521') -> "id_ecdsa".
-
-identity_pass_phrase("ssh-dss" ) -> dsa_pass_phrase;
-identity_pass_phrase("ssh-rsa" ) -> rsa_pass_phrase;
-identity_pass_phrase("rsa-sha2-256" ) -> rsa_pass_phrase;
-identity_pass_phrase("rsa-sha2-384" ) -> rsa_pass_phrase;
-identity_pass_phrase("rsa-sha2-512" ) -> rsa_pass_phrase;
-%% Not yet implemented: identity_pass_phrase("ssh-ed25519" ) -> ed25519_pass_phrase;
-%% Not yet implemented: identity_pass_phrase("ssh-ed448" ) -> ed448_pass_phrase;
-identity_pass_phrase("ecdsa-sha2-"++_) -> ecdsa_pass_phrase;
-identity_pass_phrase(P) when is_atom(P) ->
- identity_pass_phrase(atom_to_list(P));
-identity_pass_phrase(_) -> undefined.
-
-lookup_host_key_fd(Fd, KeyToMatch, Host, KeyType) ->
- case io:get_line(Fd, '') of
- eof ->
- {error, not_found};
- {error,Error} ->
- %% Rare... For example NFS errors
- {error,Error};
- Line ->
- case ssh_decode_line(Line, known_hosts) of
- [{Key, Attributes}] ->
- handle_host(Fd, KeyToMatch, Host, proplists:get_value(hostnames, Attributes), Key, KeyType);
- [] ->
- lookup_host_key_fd(Fd, KeyToMatch, Host, KeyType)
- end
- end.
-ssh_decode_line(Line, Type) ->
- try
- public_key:ssh_decode(Line, Type)
- catch _:_ ->
- []
+decode_ssh_file(Pem, Password) ->
+ %% Private Key
+ case public_key:pem_decode(Pem) of
+ [{{no_asn1,new_openssh}, Bin, _}] ->
+ public_key:ssh_decode(Bin, new_openssh);
+
+ Other ->
+ pem_entry_decode(Other, Password)
end.
-handle_host(Fd, KeyToMatch, Host, HostList, Key, KeyType) ->
- Host1 = host_name(Host),
- case lists:member(Host1, HostList) andalso key_match(Key, KeyType) of
- true when KeyToMatch == Key ->
- {ok,Key};
- _ ->
- lookup_host_key_fd(Fd, KeyToMatch, Host, KeyType)
+
+check_key_type(PrivPub, Key, Algorithm) ->
+ case ssh_transport:valid_key_sha_alg(PrivPub, Key, Algorithm) of
+ true -> {ok,Key};
+ false -> {error,bad_keytype_in_file}
end.
-host_name(Atom) when is_atom(Atom) ->
- atom_to_list(Atom);
-host_name(List) ->
- List.
-
-key_match(#'RSAPublicKey'{}, 'ssh-rsa') ->
- true;
-key_match({_, #'Dss-Parms'{}}, 'ssh-dss') ->
- true;
-key_match({#'ECPoint'{},{namedCurve,Curve}}, Alg) ->
- case atom_to_list(Alg) of
- "ecdsa-sha2-"++IdS ->
- Curve == public_key:ssh_curvename2oid(list_to_binary(IdS));
- _ ->
- false
- end;
-key_match({ed_pub,ed25519,_}, 'ssh-ed25519') ->
- true;
-key_match({ed_pub,ed448,_}, 'ssh-ed448') ->
- true;
-key_match(_, _) ->
- false.
-add_key_fd(Fd, Host,Key) ->
- SshBin = public_key:ssh_encode([{Key, [{hostnames, [Host]}]}], known_hosts),
- file:write(Fd, SshBin).
+file_base_name(user, 'ecdsa-sha2-nistp256') -> "id_ecdsa";
+file_base_name(user, 'ecdsa-sha2-nistp384') -> "id_ecdsa";
+file_base_name(user, 'ecdsa-sha2-nistp521') -> "id_ecdsa";
+file_base_name(user, 'rsa-sha2-256' ) -> "id_rsa";
+file_base_name(user, 'rsa-sha2-384' ) -> "id_rsa";
+file_base_name(user, 'rsa-sha2-512' ) -> "id_rsa";
+file_base_name(user, 'ssh-dss' ) -> "id_dsa";
+file_base_name(user, 'ssh-ed25519' ) -> "id_ed25519";
+file_base_name(user, 'ssh-ed448' ) -> "id_ed448";
+file_base_name(user, 'ssh-rsa' ) -> "id_rsa";
+file_base_name(system, 'ecdsa-sha2-nistp256') -> "ssh_host_ecdsa_key";
+file_base_name(system, 'ecdsa-sha2-nistp384') -> "ssh_host_ecdsa_key";
+file_base_name(system, 'ecdsa-sha2-nistp521') -> "ssh_host_ecdsa_key";
+file_base_name(system, 'rsa-sha2-256' ) -> "ssh_host_rsa_key";
+file_base_name(system, 'rsa-sha2-384' ) -> "ssh_host_rsa_key";
+file_base_name(system, 'rsa-sha2-512' ) -> "ssh_host_rsa_key";
+file_base_name(system, 'ssh-dss' ) -> "ssh_host_dsa_key";
+file_base_name(system, 'ssh-ed25519' ) -> "ssh_host_ed25519_key";
+file_base_name(system, 'ssh-ed448' ) -> "ssh_host_ed448_key";
+file_base_name(system, 'ssh-rsa' ) -> "ssh_host_rsa_key";
+file_base_name(system, _ ) -> "ssh_host_key".
+
+
+identity_pass_phrase('ssh-dss' ) -> dsa_pass_phrase;
+identity_pass_phrase('ssh-rsa' ) -> rsa_pass_phrase;
+identity_pass_phrase('rsa-sha2-256' ) -> rsa_pass_phrase;
+identity_pass_phrase('rsa-sha2-384' ) -> rsa_pass_phrase;
+identity_pass_phrase('rsa-sha2-512' ) -> rsa_pass_phrase;
+identity_pass_phrase('ecdsa-sha2-nistp256') -> ecdsa_pass_phrase;
+identity_pass_phrase('ecdsa-sha2-nistp384') -> ecdsa_pass_phrase;
+identity_pass_phrase('ecdsa-sha2-nistp521') -> ecdsa_pass_phrase;
+%% Not yet implemented: identity_pass_phrase('ssh-ed25519' ) -> ed25519_pass_phrase;
+%% Not yet implemented: identity_pass_phrase('ssh-ed448' ) -> ed448_pass_phrase;
+identity_pass_phrase(_) -> undefined.
+
-lookup_user_key_f(_, _User, [], _F, _Opts) ->
- {error, nouserdir};
-lookup_user_key_f(_, _User, nouserdir, _F, _Opts) ->
- {error, nouserdir};
-lookup_user_key_f(Key, _User, Dir, F, _Opts) ->
- FileName = filename:join(Dir, F),
- case file:open(FileName, [read, binary]) of
- {ok, Fd} ->
- Res = lookup_user_key_fd(Fd, Key),
- file:close(Fd),
- Res;
- {error, Reason} ->
- {error, {{openerr, Reason}, {file, FileName}}}
- end.
+pem_entry_decode([{_, _, not_encrypted} = Entry], _Password) ->
+ public_key:pem_entry_decode(Entry);
+pem_entry_decode([Entry], Password) when Password =/= ignore ->
+ public_key:pem_entry_decode(Entry, Password);
+pem_entry_decode(_, _) ->
+ throw("No pass phrase provided for private key file").
-lookup_user_key_fd(Fd, Key) ->
- case io:get_line(Fd, '') of
- eof ->
- {error, not_found};
- {error,Error} ->
- %% Rare... For example NFS errors
- {error,Error};
- Line ->
- case ssh_decode_line(Line, auth_keys) of
- [{AuthKey, _}] ->
- case is_auth_key(Key, AuthKey) of
- true ->
- {ok, Key};
- false ->
- lookup_user_key_fd(Fd, Key)
- end;
- [] ->
- lookup_user_key_fd(Fd, Key)
- end
- end.
+%%%----------------------------------------------------------------
+file_name(Type, Name, Opts) ->
+ filename:join(ssh_dir(Type, Opts), Name).
+
+
+%%%--------------------------------
+ssh_dir({remoteuser, User}, Opts) ->
+ %% server use this to find individual keys for an individual
+ %% user when user tries to login with publickey
+ case proplists:get_value(user_dir_fun, Opts) of
+ undefined ->
+ %% Try the local user instead
+ ssh_dir(user, Opts);
+ FUN ->
+ FUN(User)
+ end;
-is_auth_key(Key, Key) ->
- true;
-is_auth_key(_,_) ->
- false.
+ssh_dir(user, Opts) ->
+ %% client use this to find client ssh keys
+ case proplists:get_value(user_dir, Opts, false) of
+ false -> default_user_dir();
+ D -> D
+ end;
+ssh_dir(system, Opts) ->
+ %% server use this to find server host keys
+ proplists:get_value(system_dir, Opts, "/etc/ssh").
+%%%--------------------------------
default_user_dir() ->
try
default_user_dir(os:getenv("HOME"))
@@ -395,9 +336,17 @@ default_user_dir(Home) when is_list(Home) ->
{ok,Info} = file:read_file_info(UserDir),
#file_info{mode=Mode} = Info,
case (Mode band 8#777) of
- ?PERM_700 ->
+ 8#700 ->
ok;
_Other ->
- ok = file:change_mode(UserDir, ?PERM_700)
+ ok = file:change_mode(UserDir, 8#700)
end,
UserDir.
+
+
+
+%%%################################################################
+%%%################################################################
+%%%################################################################
+%%%################################################################
+
diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl
index d446521a16..7f8565204e 100644
--- a/lib/ssh/src/ssh_transport.erl
+++ b/lib/ssh/src/ssh_transport.erl
@@ -50,7 +50,7 @@
parallell_gen_key/1,
extract_public_key/1,
ssh_packet/2, pack/2,
- valid_key_sha_alg/2,
+ valid_key_sha_alg/3,
sha/1, sign/3, verify/5,
get_host_key/2,
call_KeyCb/3]).
@@ -786,7 +786,7 @@ get_host_key(SignAlg, Opts) ->
case call_KeyCb(host_key, [SignAlg], Opts) of
{ok, PrivHostKey} ->
%% Check the key - the KeyCb may be a buggy plugin
- case valid_key_sha_alg(PrivHostKey, SignAlg) of
+ case valid_key_sha_alg(private, PrivHostKey, SignAlg) of
true -> PrivHostKey;
false -> exit({error, bad_hostkey})
end;
@@ -1787,29 +1787,29 @@ kex_alg_dependent({Min, NBits, Max, Prime, Gen, E, F, K}) ->
%%%----------------------------------------------------------------
-valid_key_sha_alg(#{engine:=_, key_id:=_}, _Alg) -> true; % Engine key
+valid_key_sha_alg(_, #{engine:=_, key_id:=_}, _Alg) -> true; % Engine key
-valid_key_sha_alg(#'RSAPublicKey'{}, 'rsa-sha2-512') -> true;
-valid_key_sha_alg(#'RSAPublicKey'{}, 'rsa-sha2-384') -> true;
-valid_key_sha_alg(#'RSAPublicKey'{}, 'rsa-sha2-256') -> true;
-valid_key_sha_alg(#'RSAPublicKey'{}, 'ssh-rsa' ) -> true;
+valid_key_sha_alg(public, #'RSAPublicKey'{}, 'rsa-sha2-512') -> true;
+valid_key_sha_alg(public, #'RSAPublicKey'{}, 'rsa-sha2-384') -> true;
+valid_key_sha_alg(public, #'RSAPublicKey'{}, 'rsa-sha2-256') -> true;
+valid_key_sha_alg(public, #'RSAPublicKey'{}, 'ssh-rsa' ) -> true;
-valid_key_sha_alg(#'RSAPrivateKey'{}, 'rsa-sha2-512') -> true;
-valid_key_sha_alg(#'RSAPrivateKey'{}, 'rsa-sha2-384') -> true;
-valid_key_sha_alg(#'RSAPrivateKey'{}, 'rsa-sha2-256') -> true;
-valid_key_sha_alg(#'RSAPrivateKey'{}, 'ssh-rsa' ) -> true;
+valid_key_sha_alg(private, #'RSAPrivateKey'{}, 'rsa-sha2-512') -> true;
+valid_key_sha_alg(private, #'RSAPrivateKey'{}, 'rsa-sha2-384') -> true;
+valid_key_sha_alg(private, #'RSAPrivateKey'{}, 'rsa-sha2-256') -> true;
+valid_key_sha_alg(private, #'RSAPrivateKey'{}, 'ssh-rsa' ) -> true;
-valid_key_sha_alg({_, #'Dss-Parms'{}}, 'ssh-dss') -> true;
-valid_key_sha_alg(#'DSAPrivateKey'{}, 'ssh-dss') -> true;
+valid_key_sha_alg(public, {_, #'Dss-Parms'{}}, 'ssh-dss') -> true;
+valid_key_sha_alg(private, #'DSAPrivateKey'{}, 'ssh-dss') -> true;
-valid_key_sha_alg({ed_pub, ed25519,_}, 'ssh-ed25519') -> true;
-valid_key_sha_alg({ed_pri, ed25519,_,_},'ssh-ed25519') -> true;
-valid_key_sha_alg({ed_pub, ed448,_}, 'ssh-ed448') -> true;
-valid_key_sha_alg({ed_pri, ed448,_,_}, 'ssh-ed448') -> true;
+valid_key_sha_alg(public, {ed_pub, ed25519,_}, 'ssh-ed25519') -> true;
+valid_key_sha_alg(private, {ed_pri, ed25519,_,_},'ssh-ed25519') -> true;
+valid_key_sha_alg(public, {ed_pub, ed448,_}, 'ssh-ed448') -> true;
+valid_key_sha_alg(private, {ed_pri, ed448,_,_}, 'ssh-ed448') -> true;
-valid_key_sha_alg({#'ECPoint'{},{namedCurve,OID}}, Alg) -> valid_key_sha_alg_ec(OID, Alg);
-valid_key_sha_alg(#'ECPrivateKey'{parameters = {namedCurve,OID}}, Alg) -> valid_key_sha_alg_ec(OID, Alg);
-valid_key_sha_alg(_, _) -> false.
+valid_key_sha_alg(public, {#'ECPoint'{},{namedCurve,OID}}, Alg) -> valid_key_sha_alg_ec(OID, Alg);
+valid_key_sha_alg(private, #'ECPrivateKey'{parameters = {namedCurve,OID}}, Alg) -> valid_key_sha_alg_ec(OID, Alg);
+valid_key_sha_alg(_, _, _) -> false.
valid_key_sha_alg_ec(OID, Alg) ->
Curve = public_key:oid2ssh_curvename(OID),
--
2.16.4