File 4486-ssh-rename-alive_params-to-alive.patch of Package erlang
From 52e9862a584c815660516cfa24306869ef7a6f28 Mon Sep 17 00:00:00 2001
From: Alexandre Rodrigues <alexandrejbr@live.com>
Date: Thu, 23 Oct 2025 08:03:14 +0200
Subject: [PATCH 16/20] ssh: rename alive_params to alive
---
lib/ssh/src/ssh.hrl | 4 ++--
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 | 2 +-
lib/ssh/test/ssh_options_SUITE.erl | 2 +-
lib/ssh/test/ssh_protocol_SUITE.erl | 18 +++++++++---------
8 files changed, 22 insertions(+), 22 deletions(-)
diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
index 448467964a..fa357325a4 100644
--- a/lib/ssh/src/ssh.hrl
+++ b/lib/ssh/src/ssh.hrl
@@ -550,7 +550,7 @@
-type inet_common_option() :: {inet, inet | inet6} .
-type fd_common_option() :: {fd, gen_tcp:socket()} .
--type alive_common_option() :: {alive_params, {AliveCountMax::pos_integer(), AliveInterval::timeout()}}.
+-type alive_common_option() :: {alive, {CountMax::pos_integer(), Interval::timeout()}}.
-type opaque_common_options() ::
{transport, {atom(),atom(),atom()} }
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index 77acaa9781..19ca1fc333 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_params, Ssh0#ssh.opts) of
+ case ?GET_OPT(alive, 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_params, Opts) of
+ case ?GET_OPT(alive, 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_params, Opts) of
+ case ?GET_OPT(alive, 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_params, Opts) of
+ case ?GET_OPT(alive, 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_params, Ssh#ssh.opts),
+ {AliveCount, AliveInterval} = ?GET_OPT(alive, 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_params, Opts),
+ {Count, _AliveInterval} = ?GET_OPT(alive, 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 bc4b525ade..68dfbded4f 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_params, Ssh#ssh.opts),
+ {_AliveCount, AliveInterval} = ?GET_OPT(alive, 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 61f6259081..2fd862a281 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_params, Ssh#ssh.opts),
+ {_AliveCount, AliveInterval} = ?GET_OPT(alive, 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 c06a623f25..1930e13ff9 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_params,Opts),
+ {_AliveCount, AliveInterval} = ?GET_OPT(alive,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 5c69d4b5a7..2e07689a44 100644
--- a/lib/ssh/src/ssh_options.erl
+++ b/lib/ssh/src/ssh_options.erl
@@ -860,7 +860,7 @@ default(common) ->
class => user_option
},
- alive_params =>
+ alive =>
#{default => {3, infinity},
chk => fun({AliveCount, AliveIntervalSeconds}) ->
case check_pos_integer(AliveCount) andalso
diff --git a/lib/ssh/test/ssh_options_SUITE.erl b/lib/ssh/test/ssh_options_SUITE.erl
index 010573ea15..e61b1c3edb 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_params, {1, 2}},
+ {alive, {1, 2}},
{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 9b339e8fd2..6e43972683 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_params, {3,1}}]),
+ {alive, {3,1}}]),
{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_params, {3,1}}
+ {alive, {3,1}}
]
),
%% Check that the daemon got expected result:
@@ -1605,11 +1605,11 @@ alive_reneg_eserver_tclient(Config) ->
Pwd = "morot",
UserDir = user_dir(Config),
{DaemonPid, Host, Port} = ssh_test_lib:daemon([{system_dir, system_dir(Config)},
- {user_dir, UserDir},
- {password, Pwd},
- {max_log_item_len, 20000},
- {failfun, fun ssh_test_lib:failfun/2},
- {alive_params, {3,1}}]),
+ {user_dir, UserDir},
+ {password, Pwd},
+ {max_log_item_len, 20000},
+ {failfun, fun ssh_test_lib:failfun/2},
+ {alive, {3,1}}]),
?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_params, {3,1}}
+ {alive, {3,1}}
]
),
%% 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_params, {3,1}}]),
+ {alive, {3,1}}]),
?CT_LOG("~n~s", [ssh_info:string()]),
?CT_LOG("Client side connection handler PID: ~p", [CHandlerPid]),
ssh_connection_handler:renegotiate(CHandlerPid),
--
2.51.0