File 4914-ssh-Tests-of-ssh-daemon_replace_options-2.patch of Package erlang

From 338920484e8293af9ff6cc1945ecd8a5d492b01b Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Wed, 3 Aug 2022 12:04:41 +0200
Subject: [PATCH 4/5] ssh: Tests of ssh:daemon_replace_options/2

---
 lib/ssh/test/ssh_options_SUITE.erl | 296 ++++++++++++++++++++++++-----
 1 file changed, 251 insertions(+), 45 deletions(-)

diff --git a/lib/ssh/test/ssh_options_SUITE.erl b/lib/ssh/test/ssh_options_SUITE.erl
index 631a0c9b25..c02b20d6a2 100644
--- a/lib/ssh/test/ssh_options_SUITE.erl
+++ b/lib/ssh/test/ssh_options_SUITE.erl
@@ -84,7 +84,11 @@
          save_accepted_host_option/1,
          raw_option/1,
          config_file/1,
-         config_file_modify_algorithms_order/1
+         config_file_modify_algorithms_order/1,
+         daemon_replace_options_simple/1,
+         daemon_replace_options_algs/1,
+         daemon_replace_options_algs_connect/1,
+         daemon_replace_options_algs_conf_file/1
 	]).
 
 %%% Common test callbacks
@@ -94,6 +98,10 @@
 	 init_per_testcase/2, end_per_testcase/2
 	]).
 
+%%% For test nodes
+-export([get_preferred_algorithms/2
+        ]).
+
 -define(NEWLINE, <<"\r\n">>).
 
 %%--------------------------------------------------------------------
@@ -147,6 +155,10 @@ all() ->
      raw_option,
      config_file,
      config_file_modify_algorithms_order,
+     daemon_replace_options_simple,
+     daemon_replace_options_algs,
+     daemon_replace_options_algs_connect,
+     daemon_replace_options_algs_conf_file,
      {group, hardening_tests}
     ].
 
@@ -1700,27 +1712,21 @@ config_file(Config) ->
             [{_,[Ch1|_]}|_] = proplists:get_value(cipher, CommonAlgs),
 
             %% Make config file:
-            Contents = 
-                [{ssh, [{preferred_algorithms,
-                         [{cipher, [Ch1]},
-                          {kex,    [K1a]}
-                         ] ++ AdjustClient},
-                        {client_options,
-                         [{modify_algorithms,
-                           [{rm,     [{kex, [K1a]}]},
-                            {append, [{kex, [K1b]}]}
+            {ok,ConfFile} = 
+                make_config_file_in_privdir(
+                  "c2.config", Config,
+                  [{ssh, [{preferred_algorithms,
+                           [{cipher, [Ch1]},
+                            {kex,    [K1a]}
+                           ] ++ AdjustClient},
+                          {client_options,
+                           [{modify_algorithms,
+                             [{rm,     [{kex, [K1a]}]},
+                              {append, [{kex, [K1b]}]}
+                             ]}
                            ]}
                          ]}
-                       ]}
-                ],          
-            %% write the file:
-            PrivDir = proplists:get_value(priv_dir, Config),
-            ConfFile = filename:join(PrivDir,"c2.config"),
-            {ok,D} = file:open(ConfFile, [write]),
-            io:format(D, "~p.~n", [Contents]),
-            file:close(D),
-            {ok,Cnfs} = file:read_file(ConfFile),
-            ct:log("c2.config:~n~s", [Cnfs]),
+                  ]),
 
             %% Start the slave node with the configuration just made:
             {ok,Node} = start_node(random_node_name(?MODULE), ConfFile),
@@ -1792,33 +1798,27 @@ config_file_modify_algorithms_order(Config) ->
             [{_,[Ch1|_]}|_] = proplists:get_value(cipher, CommonAlgs),
 
             %% Make config file:
-            Contents = 
-                [{ssh, [{preferred_algorithms,
-                         [{cipher, [Ch1]},
-                          {kex,    [K1]}
-                         ]},
-                        {server_options,
-                         [{modify_algorithms,
-                           [{rm,     [{kex, [K1]}]},
-                            {append, [{kex, [K2]}]}
-                           ]}
-                         ]},
-                        {client_options,
-                         [{modify_algorithms,
-                           [{rm,     [{kex, [K1]}]},
-                            {append, [{kex, [K3]}]}
+            {ok, ConfFile} =
+                make_config_file_in_privdir(
+                  "c3.config", Config,
+                  [{ssh, [{preferred_algorithms,
+                           [{cipher, [Ch1]},
+                            {kex,    [K1]}
+                           ]},
+                          {server_options,
+                           [{modify_algorithms,
+                             [{rm,     [{kex, [K1]}]},
+                              {append, [{kex, [K2]}]}
+                             ]}
+                           ]},
+                          {client_options,
+                           [{modify_algorithms,
+                             [{rm,     [{kex, [K1]}]},
+                              {append, [{kex, [K3]}]}
+                             ]}
                            ]}
                          ]}
-                       ]}
-                ],          
-            %% write the file:
-            PrivDir = proplists:get_value(priv_dir, Config),
-            ConfFile = filename:join(PrivDir,"c3.config"),
-            {ok,D} = file:open(ConfFile, [write]),
-            io:format(D, "~p.~n", [Contents]),
-            file:close(D),
-            {ok,Cnfs} = file:read_file(ConfFile),
-            ct:log("c3.config:~n~s", [Cnfs]),
+                  ]),
 
             %% Start the slave node with the configuration just made:
             {ok,Node} = start_node(random_node_name(?MODULE), ConfFile),
@@ -1865,6 +1865,171 @@ config_file_modify_algorithms_order(Config) ->
     end.
 
     
+%%--------------------------------------------------------------------
+daemon_replace_options_simple(Config) ->
+    SysDir = proplists:get_value(data_dir, Config),
+
+    UserDir1 = proplists:get_value(user_dir, Config),
+    UserDir2 = filename:join(UserDir1, "foo"),
+    file:make_dir(UserDir2),
+
+    {Pid, _Host, _Port} = ssh_test_lib:daemon([{system_dir, SysDir},
+                                               {user_dir, UserDir1}
+                                              ]),
+    {ok,Opts1} = ssh:daemon_info(Pid),
+    UserDir1 = proplists:get_value(user_dir, proplists:get_value(options,Opts1,[])),
+
+    {ok, Pid} = ssh:daemon_replace_options(Pid, [{user_dir,UserDir2}]),
+    {ok,Opts2} = ssh:daemon_info(Pid),
+    case proplists:get_value(user_dir, proplists:get_value(options,Opts2,[])) of
+        UserDir2 ->
+            ok;
+        UserDir1 ->
+            ct:log("~p:~p Got old value ~p~nExpected ~p", [?MODULE,?LINE,UserDir1,UserDir2]),
+            {fail, "Not changed"};
+        Other ->
+            ct:log("~p:~p Got ~p~nExpected ~p", [?MODULE,?LINE,Other,UserDir2]),
+            {fail, "Strange value"}
+    end.
+
+%%--------------------------------------------------------------------
+daemon_replace_options_algs(Config) ->
+    SysDir = proplists:get_value(data_dir, Config),
+    UserDir = proplists:get_value(user_dir, Config),
+
+    DefaultKex =
+        ssh_transport:default_algorithms(kex),
+    NonDefaultKex =
+        ssh_transport:supported_algorithms(kex) -- DefaultKex,
+
+    case NonDefaultKex of
+        [A1|_] ->
+            [A2,A3|_] = DefaultKex,
+            {Pid, _Host, _Port} = ssh_test_lib:daemon([{system_dir, SysDir},
+                                                       {user_dir, UserDir},
+                                                       {preferred_algorithms,[{kex,[A1]}]}
+                                                      ]),
+            [A1] = get_preferred_algorithms(Pid, kex),
+            {ok, Pid} =
+                ssh:daemon_replace_options(Pid, [{modify_algorithms,
+                                                  [{prepend,[{kex,[A2]}]}]
+                                                 }
+                                                ]),
+            [A2,A1] = get_preferred_algorithms(Pid, kex),
+
+            {ok, Pid} =
+                ssh:daemon_replace_options(Pid, [{preferred_algorithms,[{kex,[A3]}]
+                                                 }
+                                                ]),
+            [A2,A3] = get_preferred_algorithms(Pid, kex)
+            ;
+        [] ->
+            {skip, "No non-default kex"}
+    end.
+
+%%--------------------------------------------------------------------
+daemon_replace_options_algs_connect(Config) ->
+    [A1,A2|_] =
+        ssh_transport:default_algorithms(kex),
+
+    {Pid, Host, Port} =
+        ssh_test_lib:std_daemon(Config,
+                                [{preferred_algorithms,[{kex,[A1]}]}
+                                ]),
+    [A1] = get_preferred_algorithms(Pid, kex),
+
+    %% Open a connection with A1 as kex and test it
+    C1 =
+        ssh_test_lib:std_connect(Config, Host, Port,
+                                 [{preferred_algorithms,[{kex,[A1]}]}
+                                 ]),
+    ok = test_connection(C1),
+    ok = test_not_connect(Config, Host, Port,
+                          [{preferred_algorithms,[{kex,[A2]}]}
+                          ]),
+
+    %% Change kex to A2
+    {ok, Pid} =
+        ssh:daemon_replace_options(Pid,
+                                   [{preferred_algorithms,[{kex,[A2]}]}]),
+    [A2] = get_preferred_algorithms(Pid, kex),
+
+    %% and open the second connection with this kex, and test it
+    C2 =
+        ssh_test_lib:std_connect(Config, Host, Port,
+                                 [{preferred_algorithms,[{kex,[A2]}]}
+                                 ]),
+    ok = test_connection(C2),
+    ok = test_not_connect(Config, Host, Port,
+                          [{preferred_algorithms,[{kex,[A1]}]}
+                          ]),
+
+    %% Test that the first connection is still alive:
+    ok = test_connection(C1),
+
+    ssh:close(C1),
+    ssh:close(C2),
+    ssh:stop_daemon(Pid).
+
+%%--------------------------------------------------------------------
+daemon_replace_options_algs_conf_file(Config) ->
+    SysDir = proplists:get_value(data_dir, Config),
+    UserDir = proplists:get_value(user_dir, Config),
+
+    DefaultKex =
+        ssh_transport:default_algorithms(kex),
+    NonDefaultKex =
+        ssh_transport:supported_algorithms(kex) -- DefaultKex,
+
+    case NonDefaultKex of
+        [A0,A1|_] ->
+            %% Make config file:
+            {ok,ConfFile} =
+                make_config_file_in_privdir(
+                  "c4.config", Config,
+                  [{ssh, [{modify_algorithms,
+                           %% Whatever happens, always put A0 first in the kex list:
+                           [{prepend, [{kex, [A0]}]}
+                           ]}
+                         ]}
+                  ]),
+
+            [A2|_] = DefaultKex,
+            ct:log("[A0, A1, A2] = ~p", [[A0, A1, A2]]),
+
+            %% Start the slave node with the configuration just made:
+            {ok, Peer, Node} = ?CT_PEER(["-config", ConfFile]),
+
+            %% Start ssh on the slave. This should apply the ConfFile:
+            rpc:call(Node, ssh, start, []),
+
+            {Pid, _Host, _Port} =
+                rpc:call(Node, ssh_test_lib, daemon,
+                         [
+                          [{system_dir, SysDir},
+                           {user_dir, UserDir},
+                           {preferred_algorithms,[{kex,[A1]}]}
+                          ]
+                         ]),
+
+            [A0,A1] =
+                rpc:call(Node, ?MODULE, get_preferred_algorithms, [Pid, kex]),
+            {ok, Pid} =
+                rpc:call(Node, ssh, daemon_replace_options,
+                         [Pid,
+                          [{modify_algorithms,
+                            [{prepend,[{kex,[A2]}]}]
+                           }
+                          ]
+                         ]),
+
+            %% Check that the precedens order is fulfilled:
+            [A2,A0,A1] =
+                rpc:call(Node, ?MODULE, get_preferred_algorithms, [Pid, kex]),
+        [] ->
+            {skip, "No non-default kex"}
+    end.
+
 %%--------------------------------------------------------------------
 %% Internal functions ------------------------------------------------
 %%--------------------------------------------------------------------
@@ -1920,3 +2087,42 @@ fake_daemon(_Config) ->
     after 
 	10000 -> ct:fail("timeout ~p:~p",[?MODULE,?LINE])
     end.
+
+
+make_config_file_in_privdir(FileName, Config, Contents) ->
+    %% write the file:
+    PrivDir = proplists:get_value(priv_dir, Config),
+    ConfFile = filename:join(PrivDir, FileName),
+    {ok,D} = file:open(ConfFile, [write]),
+    io:format(D, "~p.~n", [Contents]),
+    file:close(D),
+    {ok,Cnfs} = file:read_file(ConfFile),
+    ct:log("Config file ~p :~n~s", [ConfFile,Cnfs]),
+    {ok,ConfFile}.
+
+
+get_preferred_algorithms(Pid, Type) ->
+    {ok,#{preferred_algorithms:=As}} = ssh_system_sup:get_acceptor_options(Pid),
+    proplists:get_value(Type, As).
+
+test_connection(C) ->
+    {ok, Ch} = ssh_connection:session_channel(C, infinity),
+    A = rand:uniform(100),
+    B = rand:uniform(100),
+    A_plus_B = lists:concat([A,"+",B,"."]),
+    Sum = integer_to_binary(A+B),
+    success = ssh_connection:exec(C, Ch, A_plus_B, infinity),
+    expected = ssh_test_lib:receive_exec_result(
+                 {ssh_cm, C, {data, Ch, 0, Sum}} ),
+    ssh_test_lib:receive_exec_end(C, Ch),
+    ok.
+
+test_not_connect(Config, Host, Port, Opts) ->
+    try
+        ssh_test_lib:std_connect(Config, Host, Port, Opts)
+    of
+        Cx when is_pid(Cx) -> {error, connected}
+    catch
+        error:{badmatch, {error,_}} -> ok
+    end.
+
-- 
2.35.3

openSUSE Build Service is sponsored by