File 1447-ssh-use-map-for-alive-params-and-use-milliseconds-fo.patch of Package erlang

From d53ca954325ce91b54c9f2b47221a1d1a6e1cae1 Mon Sep 17 00:00:00 2001
From: Alexandre Rodrigues <alexandrejbr@live.com>
Date: Thu, 23 Oct 2025 09:15:42 +0200
Subject: [PATCH 17/20] ssh: use map for alive params and use milliseconds for
 interval

---
 lib/ssh/src/ssh.hrl                     | 19 +++++++++++++------
 lib/ssh/src/ssh_connection_handler.erl  | 12 ++++++------
 lib/ssh/src/ssh_fsm_kexinit.erl         |  2 +-
 lib/ssh/src/ssh_fsm_userauth_client.erl |  2 +-
 lib/ssh/src/ssh_fsm_userauth_server.erl |  2 +-
 lib/ssh/src/ssh_options.erl             | 12 ++++--------
 lib/ssh/test/ssh_options_SUITE.erl      |  2 +-
 lib/ssh/test/ssh_protocol_SUITE.erl     | 10 +++++-----
 8 files changed, 32 insertions(+), 29 deletions(-)

diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
index fa357325a4..52a501447a 100644
--- a/lib/ssh/src/ssh.hrl
+++ b/lib/ssh/src/ssh.hrl
@@ -113,6 +113,12 @@
 -define(GET_SOCKET_OPT(Key,Opts),       ?do_get_opt(socket_options,  Key,Opts    ) ).
 -define(GET_SOCKET_OPT(Key,Opts,Def),   ?do_get_opt(socket_options,  Key,Opts,Def) ).
 
+-define(GET_ALIVE_OPT(Opts),
+        begin
+            #{count_max := C, interval := I} = ?do_get_opt(user_options, alive, Opts),
+            {C, I}
+        end).
+
 -define(do_put_opt(C,KV,O),  ssh_options:put_value(C,KV,O, ?MODULE,?LINE)).
 
 -define(PUT_OPT(KeyVal,Opts),           ?do_put_opt(user_options,    KeyVal,Opts) ).
@@ -543,20 +549,21 @@ protocol).
 This option is used to configure the alive messages. Alive messages are sent through the encrypted
 channel and are typically used to detect that a connection became unresponsive.
 
-The first value of the tuple sets the maximum number
+The `count_max` sets the maximum number
 of alive messages which may be sent without receiving any messages back
 from the peer. If this threshold is reached the connection will be terminated.
 The second value of the tuple sets the timeout interval, in seconds, after which, if no data
 has been received from the peer, a message to request a response from the peer is sent.
 
-The default is `{3, infinity}`, which means that alive messages will not be sent to the peer,
-since the `Interval` is set to `infinity`.
+The default is `#{count_max => 3, interval => infinity}`, which means that alive
+messages will not be sent to the peer, since the `interval` is set to `infinity`.
 
-No alive messages are sent during renegotiation, however, a timeout derived from the alive parameters
-is set to ensure that unresponsive connections are terminated.
+No alive messages are sent during renegotiation, however, a timeout derived from
+the alive parameters is set to ensure that unresponsive connections are terminated.
 """.
 -doc(#{group => <<"Common Options">>}).
--type alive_common_option() :: {alive, {CountMax::pos_integer(), Interval::timeout()}}.
+-type alive_common_option() :: {alive, #{count_max := CountMax::pos_integer(),
+                                         interval := Interval::timeout()}}.
 
 -doc """
 Experimental options that should not to be used in products.
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index 19ca1fc333..eacd4550b0 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -2184,7 +2184,7 @@ update_inet_buffers(Socket) ->
 
 %% Reset the last_alive timer on #data{ssh_params=#ssh{}} record
 reset_alive(D = #data{ssh_params = Ssh0}) ->
-    case ?GET_OPT(alive, Ssh0#ssh.opts) of
+    case ?GET_ALIVE_OPT(Ssh0#ssh.opts) of
         {_AliveCount, AliveInterval} when is_integer(AliveInterval) ->
             Now = erlang:monotonic_time(milli_seconds),
             Ssh = Ssh0#ssh{alive_probes_sent = 0, alive_last_sent_at = Now},
@@ -2196,7 +2196,7 @@ reset_alive(D = #data{ssh_params = Ssh0}) ->
 %% the timeout has been triggered already and it is time to disconnect, and
 %% Actions may contain a new timeout action to check for the timeout again.
 get_next_alive_timeout(#ssh{alive_last_sent_at  = LastAlive, opts = Opts}) ->
-    case ?GET_OPT(alive, Opts) of
+    case ?GET_ALIVE_OPT(Opts) of
         {_AliveCount, AliveInterval} when erlang:is_integer(AliveInterval) ->
             TimeToNextAlive =
                 AliveInterval - (erlang:monotonic_time(milli_seconds) - LastAlive),
@@ -2213,7 +2213,7 @@ get_next_alive_timeout(#ssh{alive_last_sent_at  = LastAlive, opts = Opts}) ->
 
 triggered_alive(StateName, D0 = #data{},
                 #ssh{opts = Opts, alive_probes_sent = SentProbes}, Actions) ->
-    case ?GET_OPT(alive, Opts) of
+    case ?GET_ALIVE_OPT(Opts) of
           {AliveCount, _AliveInterval} when SentProbes >= AliveCount ->
             %% Max probes count reached (equal to `alive_count`), we disconnect
             Details = "Alive timeout triggered",
@@ -2237,7 +2237,7 @@ triggered_alive(StateName, D0 = #data{},
 %% For simplicity the timeout value is derived from alive_interval and
 %% alive_count.
 renegotiation_alive_timeout(#ssh{opts = Opts}) ->
-    case ?GET_OPT(alive, Opts) of
+    case ?GET_ALIVE_OPT(Opts) of
         {_AliveCount, infinity} -> infinity;
         {AliveCount, AliveInterval} -> AliveCount * AliveInterval
     end.
@@ -2309,7 +2309,7 @@ ssh_dbg_off(connections) -> dbg:ctpg(?MODULE, init, 1),
         io_lib:format("~p:~p/~p [Alive event] ~s", [_MOD, _FUN, _ARITY, _DATA])).
 
 ssh_dbg_format(alive, {return_from, {?MODULE, F=init_ssh_record, A=4}, Ssh}) ->
-    {AliveCount, AliveInterval} = ?GET_OPT(alive, Ssh#ssh.opts),
+    {AliveCount, AliveInterval} = ?GET_ALIVE_OPT(Ssh#ssh.opts),
     Str = io_lib:format("Interval=~p Count=~p", [AliveInterval, AliveCount]),
     ?PRINT_ALIVE_EVENT(?MODULE, F, A, Str);
 ssh_dbg_format(alive, {call, {?MODULE,F=handle_event,
@@ -2327,7 +2327,7 @@ ssh_dbg_format(alive, {call, {?MODULE,F=triggered_alive,
                               [State, _,
                                #ssh{opts = Opts, alive_probes_sent = SentProbesCount}, _]
                              }}) ->
-    {Count, _AliveInterval} = ?GET_OPT(alive, Opts),
+    {Count, _AliveInterval} = ?GET_ALIVE_OPT(Opts),
     Str = io_lib:format("~n~p out ~p alive probes sent (state: ~w)", [SentProbesCount, Count, State]),
     ?PRINT_ALIVE_EVENT(?MODULE, F, 4, Str);
 ssh_dbg_format(alive, {return_from, {?MODULE, F=triggered_alive, 4}, {stop, Details, _}}) ->
diff --git a/lib/ssh/src/ssh_fsm_kexinit.erl b/lib/ssh/src/ssh_fsm_kexinit.erl
index 68dfbded4f..3ba4bd833e 100644
--- a/lib/ssh/src/ssh_fsm_kexinit.erl
+++ b/lib/ssh/src/ssh_fsm_kexinit.erl
@@ -215,7 +215,7 @@ handle_event(internal, #ssh_msg_newkeys{} = Msg, {new_keys,Role,renegotiate}, D)
     {ok, Ssh} = ssh_transport:handle_new_keys(Msg, D#data.ssh_params),
     %% {ok, ExtInfo, Ssh} = ssh_transport:ext_info_message(Ssh1),
     %% ssh_connection_handler:send_bytes(ExtInfo, D),
-    {_AliveCount, AliveInterval} = ?GET_OPT(alive, Ssh#ssh.opts),
+    {_AliveCount, AliveInterval} = ?GET_ALIVE_OPT(Ssh#ssh.opts),
     {next_state, {ext_info,Role,renegotiate}, D#data{ssh_params=Ssh},
      [{{timeout, alive}, AliveInterval, none},
       {{timeout, renegotiation_alive}, cancel}]};
diff --git a/lib/ssh/src/ssh_fsm_userauth_client.erl b/lib/ssh/src/ssh_fsm_userauth_client.erl
index 2fd862a281..4a02caf121 100644
--- a/lib/ssh/src/ssh_fsm_userauth_client.erl
+++ b/lib/ssh/src/ssh_fsm_userauth_client.erl
@@ -69,7 +69,7 @@ handle_event(internal, #ssh_msg_userauth_success{}, {userauth,client}, D0=#data{
     ssh_auth:ssh_msg_userauth_result(success),
     ssh_connection_handler:handshake(ssh_connected, D0),
     D = D0#data{ssh_params=Ssh#ssh{authenticated = true}},
-    {_AliveCount, AliveInterval} = ?GET_OPT(alive, Ssh#ssh.opts),
+    {_AliveCount, AliveInterval} = ?GET_ALIVE_OPT(Ssh#ssh.opts),
     {next_state, {connected,client}, D,
      [{{timeout, alive}, AliveInterval, none},
       {change_callback_module,ssh_connection_handler}]};
diff --git a/lib/ssh/src/ssh_fsm_userauth_server.erl b/lib/ssh/src/ssh_fsm_userauth_server.erl
index 1930e13ff9..b1656cef75 100644
--- a/lib/ssh/src/ssh_fsm_userauth_server.erl
+++ b/lib/ssh/src/ssh_fsm_userauth_server.erl
@@ -181,7 +181,7 @@ connected_state(Reply, Ssh1, User, Method, D0) ->
             ssh_params = Ssh#ssh{authenticated = true}}.
 
 set_alive_timeout(#data{ssh_params = #ssh{opts=Opts}}) ->
-    {_AliveCount, AliveInterval} = ?GET_OPT(alive,Opts),
+    {_AliveCount, AliveInterval} = ?GET_ALIVE_OPT(Opts),
     {{timeout, alive}, AliveInterval, none}.
 
 set_max_initial_idle_timeout(#data{ssh_params = #ssh{opts=Opts}}) ->
diff --git a/lib/ssh/src/ssh_options.erl b/lib/ssh/src/ssh_options.erl
index 2e07689a44..902ab0fd7c 100644
--- a/lib/ssh/src/ssh_options.erl
+++ b/lib/ssh/src/ssh_options.erl
@@ -861,14 +861,10 @@ default(common) ->
             },
 
       alive =>
-          #{default => {3, infinity},
-            chk => fun({AliveCount, AliveIntervalSeconds}) ->
-                        case check_pos_integer(AliveCount) andalso
-                               check_timeout(AliveIntervalSeconds) of
-                            true when is_integer(AliveIntervalSeconds) ->
-                                {true, {AliveCount, AliveIntervalSeconds * 1000}};
-                            R -> R
-                     end
+          #{default => #{count_max => 3, interval => infinity},
+            chk => fun(#{count_max := Count, interval := IntervalSeconds}) ->
+                           check_pos_integer(Count) andalso
+                               check_timeout(IntervalSeconds)
                    end,
             class => user_option
            },
diff --git a/lib/ssh/test/ssh_options_SUITE.erl b/lib/ssh/test/ssh_options_SUITE.erl
index e61b1c3edb..675157011d 100644
--- a/lib/ssh/test/ssh_options_SUITE.erl
+++ b/lib/ssh/test/ssh_options_SUITE.erl
@@ -606,7 +606,7 @@ auth_none(Config) ->
 			     {user_dir, UserDir},
 			     {auth_methods, "password"}, % to make even more sure we don't use public-key-auth
 			     {user_passwords, [{"foo","somepwd"}]}, % Not to be used
-                             {alive, {1, 2}},
+                             {alive, #{count_max => 1, interval => 2000}},
                              {no_auth_needed, true} % we test this
 			    ]),
     ClientConnRef1 =
diff --git a/lib/ssh/test/ssh_protocol_SUITE.erl b/lib/ssh/test/ssh_protocol_SUITE.erl
index 6e43972683..c1e8e8cdad 100644
--- a/lib/ssh/test/ssh_protocol_SUITE.erl
+++ b/lib/ssh/test/ssh_protocol_SUITE.erl
@@ -1510,7 +1510,7 @@ alive_eserver_tclient(Config) ->
 					     {user_dir, UserDir},
 					     {password, Pwd},
 					     {failfun, fun ssh_test_lib:failfun/2},
-					     {alive, {3,1}}]),
+					     {alive, #{count_max => 3, interval => 1000}}]),
     {ok,AfterUserAuthReqState} = connect_and_userauth_request(Host, Port, User, Pwd, UserDir),
     {ok, AliveOkState} =
 	ssh_trpt_test_lib:exec(
@@ -1591,7 +1591,7 @@ alive_tserver_eclient(Config) ->
 			 [{preferred_algorithms,[{kex,[?DEFAULT_KEX]},
                                                  {cipher,?DEFAULT_CIPHERS}
                                                 ]},
-                          {alive, {3,1}}
+                          {alive, #{count_max => 3, interval => 1000}}
                          ]
 			),
     %% Check that the daemon got expected result:
@@ -1609,7 +1609,7 @@ alive_reneg_eserver_tclient(Config) ->
                                                    {password, Pwd},
                                                    {max_log_item_len, 20000},
                                                    {failfun, fun ssh_test_lib:failfun/2},
-                                                   {alive, {3,1}}]),
+                                                   {alive, #{count_max => 3, interval => 1000}}]),
     ?CT_LOG("[starting] Alive feature - normal conditions"),
     {ok, TrptState0} = connect_and_userauth_request(Host, Port, User, Pwd, UserDir),
     CheckAlive =
@@ -1697,7 +1697,7 @@ alive_reneg_tserver_eclient(Config) ->
 			 [{preferred_algorithms,[{kex,[?DEFAULT_KEX]},
                                                  {cipher,?DEFAULT_CIPHERS}
                                                 ]},
-                          {alive, {3,1}}
+                          {alive, #{count_max => 3, interval => 1000}}
                          ]
 			),
     %% Check that the daemon got expected result:
@@ -1731,7 +1731,7 @@ alive_reneg_tserver_eclient(Config) ->
 			 [{preferred_algorithms,[{kex,[?DEFAULT_KEX]},
                                                  {cipher,?DEFAULT_CIPHERS}
                                                 ]},
-                          {alive, {3,1}}]),
+                          {alive, #{count_max => 3, interval => 1000}}]),
     ?CT_LOG("~n~s", [ssh_info:string()]),
     ?CT_LOG("Client side connection handler PID: ~p", [CHandlerPid]),
     ssh_connection_handler:renegotiate(CHandlerPid),
-- 
2.51.0

openSUSE Build Service is sponsored by