File 4981-ssh-Add-bannerfun-to-the-server-role.patch of Package erlang
From fffdce8db422cad9868703019b25f35f58eab3e5 Mon Sep 17 00:00:00 2001
From: Alexandre Rodrigues <alexandrejbr@live.com>
Date: Thu, 5 Dec 2024 14:10:42 +0100
Subject: [PATCH 1/4] ssh: Add bannerfun to the server role
bannerfun/1 enables the server to send a SSH_MSG_USERAUTH_BANNER
at the beginning of user authentication, immediately after receiving
the first SSH_MSG_USERAUTH_BANNER
---
lib/ssh/src/ssh.hrl | 10 ++++--
lib/ssh/src/ssh_fsm_userauth_server.erl | 47 +++++++++++++++++++------
lib/ssh/src/ssh_options.erl | 6 ++++
lib/ssh/test/ssh_options_SUITE.erl | 45 ++++++++++++++++++++++-
4 files changed, 94 insertions(+), 14 deletions(-)
diff --git a/lib/ssh/doc/src/ssh.xml b/lib/ssh/dpc/src/ssh.xml
index bb4b4f35e1..af4d8bc5e4 100644
--- a/lib/ssh/doc/src/ssh.xml
+++ b/lib/ssh/doc/src/ssh.xml
@@ -851,6 +851,13 @@
<item>
<p>Provides a fun to implement your own logging when a user fails to authenticate.</p>
</item>
+
+ <tag><c>bannerfun</c></tag>
+ <item>
+ <p>Provides a fun to implement the construction of a banner text that is sent
+ at the beginning of the user authentication.
+ The banner will not be sent if the function does not return a binary.</p>
+ </item>
</taglist>
</desc>
</datatype>
diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
index bb4b4f35e1..af4d8bc5e4 100644
--- a/lib/ssh/src/ssh.hrl
+++ b/lib/ssh/src/ssh.hrl
@@ -1143,7 +1143,8 @@ in the User's Guide chapter.
-type callbacks_daemon_options() ::
{failfun, fun((User::string(), Peer::{inet:ip_address(), inet:port_number()}, Reason::term()) -> _)}
- | {connectfun, fun((User::string(), Peer::{inet:ip_address(), inet:port_number()}, Method::string()) ->_)} .
+ | {connectfun, fun((User::string(), Peer::{inet:ip_address(), inet:port_number()}, Method::string()) ->_)}
+ | {bannerfun, fun((User::string()) -> binary())}.
-type opaque_daemon_options() ::
{infofun, fun()}
@@ -1246,7 +1251,8 @@ in the User's Guide chapter.
userauth_preference,
available_host_keys,
pwdfun_user_state,
- authenticated = false
+ authenticated = false,
+ userauth_banner_sent = false
}).
-record(alg,
diff --git a/lib/ssh/src/ssh_fsm_userauth_server.erl b/lib/ssh/src/ssh_fsm_userauth_server.erl
index 140f0b068f..47d98c9376 100644
--- a/lib/ssh/src/ssh_fsm_userauth_server.erl
+++ b/lib/ssh/src/ssh_fsm_userauth_server.erl
@@ -58,20 +58,22 @@ callback_mode() ->
%%---- userauth request to server
handle_event(internal,
Msg = #ssh_msg_userauth_request{service = ServiceName,
- method = Method},
+ method = Method,
+ user = User},
StateName = {userauth,server},
- D0 = #data{ssh_params=Ssh0}) ->
-
+ D0) ->
+ D1 = maybe_send_banner(D0, User),
+ #data{ssh_params=Ssh0} = D1,
case {ServiceName, Ssh0#ssh.service, Method} of
{"ssh-connection", "ssh-connection", "none"} ->
%% Probably the very first userauth_request but we deny unauthorized login
%% However, we *may* accept unauthorized login if instructed so
case ssh_auth:handle_userauth_request(Msg, Ssh0#ssh.session_id, Ssh0) of
{not_authorized, _, {Reply,Ssh}} ->
- D = ssh_connection_handler:send_msg(Reply, D0#data{ssh_params = Ssh}),
+ D = ssh_connection_handler:send_msg(Reply, D1#data{ssh_params = Ssh}),
{keep_state, D};
{authorized, User, {Reply, Ssh1}} ->
- D = connected_state(Reply, Ssh1, User, Method, D0),
+ D = connected_state(Reply, Ssh1, User, Method, D1),
{next_state, {connected,server}, D,
[set_max_initial_idle_timeout(D),
{change_callback_module,ssh_connection_handler}
@@ -87,18 +89,18 @@ handle_event(internal,
%% Yepp! we support this method
case ssh_auth:handle_userauth_request(Msg, Ssh0#ssh.session_id, Ssh0) of
{authorized, User, {Reply, Ssh1}} ->
- D = connected_state(Reply, Ssh1, User, Method, D0),
+ D = connected_state(Reply, Ssh1, User, Method, D1),
{next_state, {connected,server}, D,
[set_max_initial_idle_timeout(D),
{change_callback_module,ssh_connection_handler}
]};
{not_authorized, {User, Reason}, {Reply, Ssh}} when Method == "keyboard-interactive" ->
- retry_fun(User, Reason, D0),
- D = ssh_connection_handler:send_msg(Reply, D0#data{ssh_params = Ssh}),
+ retry_fun(User, Reason, D1),
+ D = ssh_connection_handler:send_msg(Reply, D1#data{ssh_params = Ssh}),
{next_state, {userauth_keyboard_interactive,server}, D};
{not_authorized, {User, Reason}, {Reply, Ssh}} ->
- retry_fun(User, Reason, D0),
- D = ssh_connection_handler:send_msg(Reply, D0#data{ssh_params = Ssh}),
+ retry_fun(User, Reason, D1),
+ D = ssh_connection_handler:send_msg(Reply, D1#data{ssh_params = Ssh}),
{keep_state, D}
end;
false ->
@@ -116,7 +118,7 @@ handle_event(internal,
{Shutdown, D} =
?send_disconnect(?SSH_DISCONNECT_SERVICE_NOT_AVAILABLE,
io_lib:format("Unknown service: ~p",[ServiceName]),
- StateName, D0),
+ StateName, D1),
{stop, Shutdown, D}
end;
@@ -213,3 +215,26 @@ retry_fun(User, Reason, #data{ssh_params = #ssh{opts = Opts,
ok
end.
+maybe_send_banner(D0 = #data{ssh_params = #ssh{userauth_banner_sent = false} = Ssh}, User) ->
+ Opts = Ssh#ssh.opts,
+ BannerText = case maps:get(bannerfun, Opts, undefined) of
+ undefined ->
+ <<>>;
+ BannerFun when is_function(BannerFun, 1) ->
+ %% Ignore bad banner texts
+ case BannerFun(User) of
+ B when is_binary(B) -> B;
+ _ -> <<>>
+ end
+ end,
+ case BannerText of
+ <<>> ->
+ D0;
+ BannerText ->
+ Banner = #ssh_msg_userauth_banner{message = BannerText,
+ language = <<>>},
+ D = D0#data{ssh_params = Ssh#ssh{userauth_banner_sent = true}},
+ ssh_connection_handler:send_msg(Banner, D)
+ end;
+maybe_send_banner(D, _) ->
+ D.
diff --git a/lib/ssh/src/ssh_options.erl b/lib/ssh/src/ssh_options.erl
index 6a55954bd0..a77233429a 100644
--- a/lib/ssh/src/ssh_options.erl
+++ b/lib/ssh/src/ssh_options.erl
@@ -588,6 +588,12 @@ default(server) ->
class => user_option
},
+ bannerfun =>
+ #{default => undefined,
+ chk => fun(V) -> check_function1(V) end,
+ class => user_option
+ },
+
%%%%% Undocumented
infofun =>
#{default => fun(_,_,_) -> void end,
diff --git a/lib/ssh/test/ssh_options_SUITE.erl b/lib/ssh/test/ssh_options_SUITE.erl
index 0017570ff6..da4091319f 100644
--- a/lib/ssh/test/ssh_options_SUITE.erl
+++ b/lib/ssh/test/ssh_options_SUITE.erl
@@ -37,7 +37,8 @@
auth_none/1,
connectfun_disconnectfun_client/1,
disconnectfun_option_client/1,
- disconnectfun_option_server/1,
+ disconnectfun_option_server/1,
+ bannerfun_server/1,
id_string_no_opt_client/1,
id_string_no_opt_server/1,
id_string_own_string_client/1,
@@ -114,6 +115,7 @@ suite() ->
all() ->
[connectfun_disconnectfun_server,
+ bannerfun_server,
connectfun_disconnectfun_client,
server_password_option,
server_userpassword_option,
@@ -778,6 +780,47 @@ connectfun_disconnectfun_server(Config) ->
{fail, "No connectfun action"}
end.
+%%--------------------------------------------------------------------
+bannerfun_server(Config) ->
+ UserDir = proplists:get_value(user_dir, Config),
+ SysDir = proplists:get_value(data_dir, Config),
+
+ Parent = self(),
+ Ref = make_ref(),
+ BannerFun = fun(U) -> Parent ! {banner,Ref,U}, list_to_binary(U) end,
+
+ {Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, SysDir},
+ {user_dir, UserDir},
+ {password, "morot"},
+ {failfun, fun ssh_test_lib:failfun/2},
+ {bannerfun, BannerFun}]),
+ ConnectionRef =
+ ssh_test_lib:connect(Host, Port, [{silently_accept_hosts, true},
+ {user, "foo"},
+ {password, "morot"},
+ {user_dir, UserDir},
+ {user_interaction, false}]),
+ receive
+ {banner,Ref,U} ->
+ "foo" = U,
+ %% Make sure no second banner is sent
+ receive
+ {banner,Ref,U} ->
+ ssh:close(ConnectionRef),
+ ssh:stop_daemon(Pid),
+ {fail, "More than 1 banner sent"}
+ after 2000 ->
+ ssh:close(ConnectionRef),
+ ssh:stop_daemon(Pid)
+ end
+ after 10000 ->
+ receive
+ X -> ct:log("received ~p",[X])
+ after 0 -> ok
+ end,
+ {fail, "No bannerfun action"}
+ end.
+
%%--------------------------------------------------------------------
connectfun_disconnectfun_client(Config) ->
UserDir = proplists:get_value(user_dir, Config),
--
2.43.0