File 2384-ssh-option-silently_accept_hosts-reworked.patch of Package erlang

From 2f212c1a3e8bc3070b51dfc5607f30e501ba24ea Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Fri, 10 Mar 2017 13:08:08 +0100
Subject: [PATCH 04/13] ssh: option 'silently_accept_hosts' reworked New (yet)
 undocumented option value {false,Alg} where Alg :: md5 | sha | sha224 |
 sha256 | sha384 | sha512 This option includes the fingerprint value in the
 accept question to the user. The fingerprint is calculated with the Alg
 provided

---
 lib/ssh/src/ssh_options.erl   | 21 ++++++++++-----------
 lib/ssh/src/ssh_transport.erl | 43 ++++++++++++++++++++++++++++++++++---------
 2 files changed, 44 insertions(+), 20 deletions(-)

diff --git a/lib/ssh/src/ssh_options.erl b/lib/ssh/src/ssh_options.erl
index 512aefa76..6a2e7ce69 100644
--- a/lib/ssh/src/ssh_options.erl
+++ b/lib/ssh/src/ssh_options.erl
@@ -431,7 +431,7 @@ default(client) ->
            },
 
       {silently_accept_hosts, def} =>
-          #{default => false,
+          #{default => {false,none},
             chk => fun check_silently_accept_hosts/1,
             class => user_options
            },
@@ -804,18 +804,17 @@ read_moduli_file(D, I, Acc) ->
 
 check_silently_accept_hosts(B) when is_boolean(B) -> true;
 check_silently_accept_hosts(F) when is_function(F,2) -> true;
-check_silently_accept_hosts({S,F}) when is_atom(S),
-                                        is_function(F,2) -> 
-    lists:member(S, ?SHAs) andalso
-        lists:member(S, proplists:get_value(hashs,crypto:supports()));
-check_silently_accept_hosts({L,F}) when is_list(L),
-                                        is_function(F,2) -> 
-    lists:all(fun(S) ->
-                      lists:member(S, ?SHAs) andalso
-                          lists:member(S, proplists:get_value(hashs,crypto:supports()))
-              end, L);
+check_silently_accept_hosts({false,S}) when is_atom(S) -> valid_hash(S);
+check_silently_accept_hosts({S,F}) when is_function(F,2) -> valid_hash(S);
 check_silently_accept_hosts(_) -> false.
 
+
+valid_hash(S) -> valid_hash(S, proplists:get_value(hashs,crypto:supports())).
+
+valid_hash(S, Ss) when is_atom(S) -> lists:member(S, ?SHAs) andalso lists:member(S, Ss);
+valid_hash(L, Ss) when is_list(L) -> lists:all(fun(S) -> valid_hash(S,Ss) end, L);
+valid_hash(X,  _) -> error_in_check(X, "Expect atom or list in fingerprint spec").
+
 %%%----------------------------------------------------------------
 check_preferred_algorithms(Algs) ->
     try alg_duplicates(Algs, [], [])
diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl
index 5d896e02a..54ea80c72 100644
--- a/lib/ssh/src/ssh_transport.erl
+++ b/lib/ssh/src/ssh_transport.erl
@@ -200,9 +200,6 @@ is_valid_mac(Mac, Data, #ssh{recv_mac = Algorithm,
 			     recv_mac_key = Key, recv_sequence = SeqNum}) ->
     Mac == mac(Algorithm, Key, SeqNum, Data).
 
-yes_no(Ssh, Prompt)  ->
-    (Ssh#ssh.io_cb):yes_no(Prompt, Ssh#ssh.opts).
-
 format_version({Major,Minor}, SoftwareVersion) ->
     "SSH-" ++ integer_to_list(Major) ++ "." ++ 
 	integer_to_list(Minor) ++ "-" ++ SoftwareVersion.
@@ -755,16 +752,44 @@ public_algo({#'ECPoint'{},{namedCurve,OID}}) ->
 
 accepted_host(Ssh, PeerName, Public, Opts) ->
     case ?GET_OPT(silently_accept_hosts, Opts) of
-	F when is_function(F,2) ->
+
+        %% Original option values; User question and no host key fingerprints known.
+        %% Keep the original question unchanged:
+	false -> yes == yes_no(Ssh, "New host " ++ PeerName ++ " accept");
+	true -> true;
+
+        %% Variant: User question but with host key fingerprint in the question:
+        {false,Alg} ->
+            HostKeyAlg = (Ssh#ssh.algorithms)#alg.hkey,
+            Prompt = io_lib:format("The authenticity of the host can't be established.~n"
+                                   "~s host key fingerprint is ~s.~n"
+                                   "New host ~p accept",
+                                   [fmt_hostkey(HostKeyAlg),
+                                    public_key:ssh_hostkey_fingerprint(Alg,Public),
+                                    PeerName]),
+            yes == yes_no(Ssh, Prompt);
+
+        %% Call-back alternatives: A user provided fun is called for the decision:
+        F when is_function(F,2) ->
 	    true == (catch F(PeerName, public_key:ssh_hostkey_fingerprint(Public)));
+
 	{DigestAlg,F} when is_function(F,2) ->
-	    true == (catch F(PeerName, public_key:ssh_hostkey_fingerprint(DigestAlg,Public)));
-	true ->
-	    true;
-	false ->
-	    yes == yes_no(Ssh, "New host " ++ PeerName ++ " accept")
+	    true == (catch F(PeerName, public_key:ssh_hostkey_fingerprint(DigestAlg,Public)))
+        
     end.
 
+
+yes_no(Ssh, Prompt)  ->
+    (Ssh#ssh.io_cb):yes_no(Prompt, Ssh#ssh.opts).
+
+
+fmt_hostkey('ssh-rsa') -> "RSA";
+fmt_hostkey('ssh-dss') -> "DSA";
+fmt_hostkey(A) when is_atom(A) -> fmt_hostkey(atom_to_list(A));
+fmt_hostkey("ecdsa"++_) -> "ECDSA";
+fmt_hostkey(X) -> X.
+
+
 known_host_key(#ssh{opts = Opts, key_cb = {KeyCb,KeyCbOpts}, peer = {PeerName,_}} = Ssh, 
 	       Public, Alg) ->
     UserOpts = ?GET_OPT(user_options, Opts),
-- 
2.12.2

openSUSE Build Service is sponsored by