Skip to content

Commit

Permalink
ssh: Add bannerfun to the server role
Browse files Browse the repository at this point in the history
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
  • Loading branch information
alexandrejbr committed Dec 5, 2024
1 parent 4c18cc7 commit 5f14347
Show file tree
Hide file tree
Showing 4 changed files with 86 additions and 14 deletions.
6 changes: 4 additions & 2 deletions lib/ssh/src/ssh.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -1147,7 +1147,8 @@ in the User's Guide chapter.
-doc(#{title => <<"Daemon Options">>}).
-type callbacks_daemon_options() ::
{failfun, fun((User::string(), PeerAddress::inet:ip_address(), Reason::term()) -> _)}
| {connectfun, fun((User::string(), PeerAddress::inet:ip_address(), Method::string()) ->_)} .
| {connectfun, fun((User::string(), PeerAddress::inet:ip_address(), Method::string()) ->_)}
| {bannerfun, fun((User::string()) -> binary())}.

-doc(#{title => <<"Other data types">>}).
-type opaque_daemon_options() ::
Expand Down Expand Up @@ -1246,7 +1247,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,
Expand Down
43 changes: 32 additions & 11 deletions lib/ssh/src/ssh_fsm_userauth_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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}
Expand All @@ -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 ->
Expand All @@ -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;

Expand Down Expand Up @@ -213,3 +215,22 @@ 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) ->
BannerFun(User)
end,
case BannerText of
<<>> ->
D0;
_ ->
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.
6 changes: 6 additions & 0 deletions lib/ssh/src/ssh_options.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down
45 changes: 44 additions & 1 deletion lib/ssh/test/ssh_options_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down Expand Up @@ -114,6 +115,7 @@ suite() ->

all() ->
[connectfun_disconnectfun_server,
bannerfun_server,
connectfun_disconnectfun_client,
server_password_option,
server_userpassword_option,
Expand Down Expand Up @@ -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),
Expand Down

0 comments on commit 5f14347

Please sign in to comment.