File 2851-ssh-Use-env-config-for-Options.patch of Package erlang

From 4c61f11a80c7c0fa706889777a449c4fa1703146 Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Fri, 6 Mar 2020 10:30:12 +0100
Subject: [PATCH 1/3] ssh: Use env config for Options

---
 lib/ssh/src/ssh.erl           |   4 ++
 lib/ssh/src/ssh_options.erl   | 106 +++++++++++++++++++++++++++++++++++-------
 lib/ssh/src/ssh_transport.erl |  60 +++++++++++++++++++++---
 3 files changed, 147 insertions(+), 23 deletions(-)

diff --git a/lib/ssh/src/ssh.erl b/lib/ssh/src/ssh.erl
index 655dcafc25..0404327b2a 100644
--- a/lib/ssh/src/ssh.erl
+++ b/lib/ssh/src/ssh.erl
@@ -95,6 +95,10 @@ start() ->
 start(Type) ->
     case application:ensure_all_started(ssh, Type) of
         {ok, _} ->
+            %% Clear cached default_algorithms (if exists) ...
+            ssh_transport:clear_default_algorithms_env(),
+            %% ... and rebuld them taking configure options in account
+            ssh_transport:default_algorithms(),
             ok;
         Other ->
             Other
diff --git a/lib/ssh/src/ssh_options.erl b/lib/ssh/src/ssh_options.erl
index f6e1320b53..fbf791f800 100644
--- a/lib/ssh/src/ssh_options.erl
+++ b/lib/ssh/src/ssh_options.erl
@@ -31,7 +31,10 @@
          delete_key/5,
          handle_options/2,
          keep_user_options/2,
-         keep_set_options/2
+         keep_set_options/2,
+
+         initial_default_algorithms/2,
+         check_preferred_algorithms/1
         ]).
 
 -export_type([private_options/0
@@ -161,35 +164,99 @@ handle_options(Role, PropList0) ->
                                       user_options     => []
                                      }).
 
-handle_options(Role, PropList0, Opts0) when is_map(Opts0),
-                                            is_list(PropList0) ->
-    PropList1 = proplists:unfold(PropList0), 
+handle_options(Role, OptsList0, Opts0) when is_map(Opts0),
+                                            is_list(OptsList0) ->
+    OptsList1 = proplists:unfold(OptsList0),
     try
         OptionDefinitions = default(Role),
-        InitialMap =
+        RoleCnfs = application:get_env(ssh, cnf_key(Role), []),
+        {InitialMap,OptsList2} =
             maps:fold(
-              fun(K, #{default:=V}, M) -> M#{K=>V};
-                 (_,_,M) -> M
+              fun(K, #{default:=Vd}, {M,PL}) ->
+                      %% Now set as the default value:
+                      %%   1: from erl command list: erl -ssh opt val
+                      %%   2: from config file:  {options, [..., {opt,val}, ....]}
+                      %%   3: from the hard-coded option values in default/1
+                      %% The value in the option list will be handled later in save/3 later
+                      case config_val(K, RoleCnfs, OptsList1) of
+                          {ok,V1} ->
+                              %% A value set in config or options. Replace the current.
+                              {M#{K => V1,
+                                  user_options => [{K,V1} | maps:get(user_options,M)]},
+                               [{K,V1} | PL]
+                              };
+
+                          {append,V1} ->
+                              %% A value set in config or options, but should be
+                              %% appended to the existing value
+                              NewVal = maps:get(K,M,[]) ++ V1,
+                              {M#{K => NewVal,
+                                  user_options => [{K,NewVal} |
+                                                   lists:keydelete(K,1,maps:get(user_options,M))]},
+                               [{K,NewVal} | lists:keydelete(K,1,PL)]
+                              };
+                              
+                          undefined ->
+                              %% Use the default value
+                              {M#{K => Vd}, PL}
+                      end
+                 %%          ;
+                 %% (_,_,Acc) ->
+                 %%      Acc
               end,
-              Opts0#{user_options => 
-                         maps:get(user_options,Opts0) ++ PropList1
-                   },
+              {Opts0#{user_options => maps:get(user_options,Opts0)},
+               [{K,V} || {K,V} <- OptsList1,
+                         not maps:is_key(K,Opts0) % Keep socket opts
+               ]
+              },
               OptionDefinitions),
+
+
         %% Enter the user's values into the map; unknown keys are
         %% treated as socket options
         final_preferred_algorithms(
           lists:foldl(fun(KV, Vals) ->
                               save(KV, OptionDefinitions, Vals)
-                      end, InitialMap, PropList1))
+                      end, InitialMap, OptsList2))
     catch
-        error:{eoptions, KV, undefined} -> 
-            {error, {eoptions,KV}};
+        error:{EO, KV, Reason} when EO == eoptions ; EO == eerl_env ->
+            if
+                Reason == undefined ->
+                    {error, {EO,KV}};
+                is_list(Reason) ->
+                    {error, {EO,{KV,lists:flatten(Reason)}}};
+                true ->
+                    {error, {EO,{KV,Reason}}}
+            end
+    end.
+
+cnf_key(server) -> server_options;
+cnf_key(client) -> client_options.
 
-        error:{eoptions, KV, Txt} when is_list(Txt) -> 
-            {error, {eoptions,{KV,lists:flatten(Txt)}}};
 
-        error:{eoptions, KV, Extra} ->
-            {error, {eoptions,{KV,Extra}}}
+config_val(modify_algorithms=Key, RoleCnfs, Opts) ->
+    V = case application:get_env(ssh, Key) of
+            {ok,V0} -> V0;
+            _ -> []
+        end
+        ++ proplists:get_value(Key, RoleCnfs, [])
+        ++ proplists:get_value(Key, Opts, []),
+    case V of
+        [] -> undefined;
+        _ -> {append,V}
+    end;
+
+config_val(Key, RoleCnfs, Opts) ->
+    case lists:keysearch(Key, 1, Opts) of
+        {value, {_,V}} ->
+            {ok,V};
+        false ->
+            case lists:keysearch(Key, 1, RoleCnfs) of
+                {value, {_,V}} ->
+                    {ok,V};
+                false ->
+                    application:get_env(ssh, Key) % returns {ok,V} | undefined
+            end
     end.
 
 
@@ -913,6 +980,11 @@ valid_hash(S, Ss) when is_atom(S) -> lists:member(S, ?SHAs) andalso lists:member
 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").
 
+%%%----------------------------------------------------------------
+initial_default_algorithms(DefList, ModList) ->
+    {true, L0} = check_modify_algorithms(ModList),
+    rm_non_supported(false, eval_ops(DefList,L0)).
+
 %%%----------------------------------------------------------------
 check_modify_algorithms(M) when is_list(M) ->
     [error_in_check(Op_KVs, "Bad modify_algorithms")
diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl
index a634fc65b8..1110fc7fc3 100644
--- a/lib/ssh/src/ssh_transport.erl
+++ b/lib/ssh/src/ssh_transport.erl
@@ -34,6 +34,7 @@
 -export([next_seqnum/1, 
 	 supported_algorithms/0, supported_algorithms/1,
 	 default_algorithms/0, default_algorithms/1,
+         clear_default_algorithms_env/0,
          algo_classes/0, algo_class/1,
          algo_two_spec_classes/0, algo_two_spec_class/1,
 	 handle_packet_part/5,
@@ -77,7 +78,46 @@
 %%% and test them without letting the default users know about them.
 %%%
 
-default_algorithms() -> [{K,default_algorithms(K)} || K <- algo_classes()].
+-define(DEFAULT_ALGS, '$def-algs$').
+
+clear_default_algorithms_env() ->
+    application:unset_env(ssh, ?DEFAULT_ALGS).
+
+-spec default_algorithms() -> algs_list()
+                                  | no_return() %  error(Reason)
+                                  .
+default_algorithms() ->
+    case application:get_env(ssh, ?DEFAULT_ALGS) of
+        undefined ->
+            %% Not cached, have to build the default, connection independent
+            %% set of algorithms:
+            Opts = get_alg_conf(),
+            Algs1 =
+                case proplists:get_value(preferred_algorithms, Opts) of
+                    undefined ->
+                        [{K,default_algorithms1(K)} || K <- algo_classes()];
+                    Algs0 ->
+                        {true,Algs01} = ssh_options:check_preferred_algorithms(Algs0),
+                        Algs01
+                end,
+            Algs =
+                case proplists:get_value(modify_algorithms, Opts) of
+                    undefined ->
+                        Algs1;
+                    Modifications ->
+                        ssh_options:initial_default_algorithms(Algs1, Modifications)
+                end,
+            application:set_env(ssh, ?DEFAULT_ALGS, Algs),
+            Algs;
+
+        {ok,Algs} ->
+            Algs
+    end.
+
+get_alg_conf() ->
+    [{T,L} || T <- [preferred_algorithms, modify_algorithms],
+              L <- [application:get_env(ssh, T, [])],
+              L =/= []].
 
 algo_classes() -> [kex, public_key, cipher, mac, compression].
 
@@ -96,9 +136,17 @@ algo_two_spec_class(mac) -> true;
 algo_two_spec_class(compression) -> true;
 algo_two_spec_class(_) -> false.
 
+
+default_algorithms(Tag) ->
+    case application:get_env(ssh, ?DEFAULT_ALGS) of
+        undefined ->
+            default_algorithms1(Tag);
+        {ok,Algs} ->
+            proplists:get_value(Tag, Algs, [])
+    end.
     
 
-default_algorithms(kex) ->
+default_algorithms1(kex) ->
     supported_algorithms(kex, [
                                %%  Gone in OpenSSH 7.3.p1:
                                'diffie-hellman-group1-sha1',
@@ -107,23 +155,23 @@ default_algorithms(kex) ->
                                'diffie-hellman-group-exchange-sha1'
                               ]);
 
-default_algorithms(cipher) ->
+default_algorithms1(cipher) ->
     supported_algorithms(cipher, same(['AEAD_AES_128_GCM',
 				       'AEAD_AES_256_GCM'
                                       ]));
-default_algorithms(mac) ->
+default_algorithms1(mac) ->
     supported_algorithms(mac, same(['AEAD_AES_128_GCM',
 				    'AEAD_AES_256_GCM',
                                     'hmac-sha1-96'
                                    ]));
 
-default_algorithms(public_key) ->
+default_algorithms1(public_key) ->
     supported_algorithms(public_key, [
                                       %% Gone in OpenSSH 7.3.p1:
                                       'ssh-dss'
                                      ]);
 
-default_algorithms(Alg) ->
+default_algorithms1(Alg) ->
     supported_algorithms(Alg, []).
 
 
-- 
2.16.4

openSUSE Build Service is sponsored by