File 5181-ssh-Introduce-option-max_log_item_len.patch of Package erlang

From 8d715399f19f67139a0dc6516618fe6cac7d5132 Mon Sep 17 00:00:00 2001
From: Hans Nilsson <hans@erlang.org>
Date: Fri, 13 May 2022 16:20:09 +0200
Subject: [PATCH] ssh: Introduce option max_log_item_len

---
 lib/ssh/doc/src/ssh.xml                |  9 ++++
 lib/ssh/src/ssh.hrl                    |  2 +
 lib/ssh/src/ssh_connection_handler.erl | 33 +++++++++++---
 lib/ssh/src/ssh_options.erl            |  8 ++++
 lib/ssh/test/ssh_options_SUITE.erl     | 61 ++++++++++++++++++++++++++
 5 files changed, 106 insertions(+), 7 deletions(-)

diff --git a/lib/ssh/doc/src/ssh.xml b/lib/ssh/doc/src/ssh.xml
index 44188ea34c..442b52eeb1 100644
--- a/lib/ssh/doc/src/ssh.xml
+++ b/lib/ssh/doc/src/ssh.xml
@@ -883,6 +883,15 @@
       </desc>
     </datatype>
 
+    <datatype>
+      <name name="max_log_item_len_common_option"/>
+      <desc>
+	<p>Sets a limit for the size of a logged item excluding a header.
+	The unit is bytes and the value defaults to 500.
+	</p>
+      </desc>
+    </datatype>
+
     <datatype>
       <name name="rekey_limit_common_option"/>
       <name name="limit_bytes"/>
diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
index 2f6e961457..e662122807 100644
--- a/lib/ssh/src/ssh.hrl
+++ b/lib/ssh/src/ssh.hrl
@@ -209,6 +209,7 @@
         ssh_file:user_dir_common_option()
       | profile_common_option()
       | max_idle_time_common_option()
+      | max_log_item_len_common_option()
       | key_cb_common_option()
       | disconnectfun_common_option()
       | unexpectedfun_common_option()
@@ -230,6 +231,7 @@
 -type rekey_limit_common_option()   :: {rekey_limit, Bytes::limit_bytes() |
                                                      {Minutes::limit_time(), Bytes::limit_bytes()}
                                        }.
+-type max_log_item_len_common_option() :: {max_log_item_len, limit_bytes()} .
 
 -type limit_bytes() :: non_neg_integer() | infinity .  % non_neg_integer due to compatibility
 -type limit_time()  :: pos_integer() | infinity .
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index b2545c4db4..c200fca6b4 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -1867,13 +1867,9 @@ log(Tag, D, Reason) ->
     end.
 
 
-do_log(F, Reason0, #data{ssh_params = S}) ->
-    Reason =
-        try io_lib:format("~s",[Reason0])
-        of _ -> Reason0
-        catch
-            _:_ -> io_lib:format("~p",[Reason0])
-        end,
+do_log(F, Reason0, #data{ssh_params=S}) ->
+    Reason1 = string:chomp(assure_string(Reason0)),
+    Reason = limit_size(Reason1, ?GET_OPT(max_log_item_len,S#ssh.opts)),
     case S of
         #ssh{role = Role} when Role==server ;
                                Role==client ->
@@ -1899,6 +1895,29 @@ do_log(F, Reason0, #data{ssh_params = S}) ->
                             Reason])
     end.
 
+assure_string(S) ->
+    try io_lib:format("~s",[S])
+    of _ -> S
+    catch
+        _:_ -> io_lib:format("~p",[S])
+    end.
+
+limit_size(S, MaxLen) when is_integer(MaxLen) ->
+    limit_size(S, lists:flatlength(S), MaxLen);
+limit_size(S, _) ->
+    S.
+
+limit_size(S, Len, MaxLen) when Len =< MaxLen ->
+    S;
+limit_size(S, Len, MaxLen) when Len =< (MaxLen + 5) ->
+    %% Looks silly with e.g "... (2 bytes skipped)"
+    S;
+limit_size(S, Len, MaxLen) when Len > MaxLen ->
+    %% Cut
+    io_lib:format("~s ... (~w bytes skipped)", 
+                  [string:substr(lists:flatten(S), 1, MaxLen),
+                   Len-MaxLen]).
+
 crypto_log_info() ->
     try 
         [{_,_,CI}] = crypto:info_lib(),
diff --git a/lib/ssh/src/ssh_options.erl b/lib/ssh/src/ssh_options.erl
index e06c2ed27c..017d25b5be 100644
--- a/lib/ssh/src/ssh_options.erl
+++ b/lib/ssh/src/ssh_options.erl
@@ -771,6 +771,14 @@ default(common) ->
              class => user_option
             },
 
+       max_log_item_len =>
+           #{default => 500,
+             chk => fun(infinity) -> true;
+                       (I) -> check_non_neg_integer(I)
+                    end,
+             class => user_option
+            },
+
       rekey_limit =>
           #{default => {3600000, 1024000000}, % {1 hour, 1 GB}
             chk => fun({infinity, infinity}) ->
diff --git a/lib/ssh/test/ssh_options_SUITE.erl b/lib/ssh/test/ssh_options_SUITE.erl
index 82c8b956c9..1bff7f945b 100644
--- a/lib/ssh/test/ssh_options_SUITE.erl
+++ b/lib/ssh/test/ssh_options_SUITE.erl
@@ -45,6 +45,7 @@
 	 id_string_own_string_server_trail_space/1, 
 	 id_string_random_client/1, 
 	 id_string_random_server/1, 
+         max_log_item_len/1,
 	 max_sessions_sftp_start_channel_parallel/1, 
 	 max_sessions_sftp_start_channel_sequential/1, 
 	 max_sessions_ssh_connect_parallel/1, 
@@ -139,6 +140,7 @@ all() ->
      id_string_own_string_server,
      id_string_own_string_server_trail_space,
      id_string_random_server,
+     max_log_item_len,
      save_accepted_host_option,
      {group, hardening_tests},
      raw_option,
@@ -1351,6 +1353,65 @@ one_shell_op(IO, TimeOut) ->
     after TimeOut ->  ct:fail("Timeout waiting for result")
     end.
 
+%%--------------------------------------------------------------------
+max_log_item_len(Config) ->
+    %% Find a supported algorithm (to be removed from the daemon):
+    {ok, {Type,Alg}} = select_alg( ssh:default_algorithms() ),
+
+    %% Start a test daemon without support for {Type,Alg}
+    SystemDir = proplists:get_value(data_dir, Config),
+    UserDir = proplists:get_value(priv_dir, Config),
+    {_Pid, Host0, Port} =
+        ssh_test_lib:daemon([
+                             {system_dir, SystemDir},
+                             {user_dir, UserDir},
+                             {user_passwords, [{"carni", "meat"}]},
+                             {modify_algorithms, [{rm, [{Type,[Alg]}]}]},
+                             {max_log_item_len, 10}
+                            ]),
+    Host = ssh_test_lib:mangle_connect_address(Host0),
+    ct:log("~p:~p Listen ~p:~p. Mangled Host = ~p",
+           [?MODULE,?LINE,Host0,Port,Host]),
+
+    {ok,ReportHandlerPid} = ssh_eqc_event_handler:add_report_handler(),
+
+    %% Connect to it with the {Type,Alg} to force a failure and log entry:
+    {error,_} = R =
+        ssh:connect(Host, Port, 
+                    [{preferred_algorithms, [{Type,[Alg]}]},
+                     {max_log_item_len, 10},
+                     {silently_accept_hosts, true},
+                     {save_accepted_host, false},
+                     {user_dir, UserDir},
+                     {user_interaction, false},
+                     {user, "carni"},
+                     {password, "meat"}
+                    ]),
+
+    {ok, Reports} = ssh_eqc_event_handler:get_reports(ReportHandlerPid),
+    ct:log("~p:~p ssh:connect -> ~p~n~p", [?MODULE,?LINE,R,Reports]),
+
+    [ok,ok] =
+        [check_skip_part(
+           string:tokens(
+             lists:flatten(io_lib:format(Fmt,Args)),
+             " \n"))
+         || {info_msg,_,{_,Fmt,Args}} <- Reports].
+
+
+check_skip_part(["Disconnect","...","("++_NumSkipped, "bytes","skipped)"]) ->
+    ok;
+check_skip_part([_|T]) ->
+    check_skip_part(T);
+check_skip_part([]) ->
+    error.
+
+select_alg([{Type,[A,_|_]}|_]) when is_atom(A) -> {ok, {Type,A}};
+select_alg([{Type,[{Dir,[A,_|_]}, _]}|_]) when is_atom(A), is_atom(Dir) -> {ok, {Type,A}};
+select_alg([{Type,[_,{Dir,[A,_|_]}]}|_]) when is_atom(A), is_atom(Dir) -> {ok, {Type,A}};
+select_alg([_|Algs]) -> select_alg(Algs);
+select_alg([]) -> false.
+
 %%--------------------------------------------------------------------
 max_sessions_ssh_connect_parallel(Config) -> 
     max_sessions(Config, true, connect_fun(ssh__connect,Config)).
-- 
2.35.3

openSUSE Build Service is sponsored by