Skip to content

Commit

Permalink
fixup! ssh: handshakers removal prototype
Browse files Browse the repository at this point in the history
  • Loading branch information
u3s committed Dec 20, 2024
1 parent ab5836e commit e57594f
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 3 deletions.
14 changes: 13 additions & 1 deletion lib/ssh/src/ssh_connection_handler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -408,7 +408,16 @@ init([Role, Socket, Opts]) when Role==client ; Role==server ->
%% ssh_params will be updated after receiving socket_control event
%% in wait_for_socket state;
D = #data{socket = Socket, ssh_params = #ssh{role = Role, opts = Opts}},
{ok, {wait_for_socket, Role}, D}.
ParallelLogin = ?GET_OPT(parallel_login, Opts, disabled),
case ParallelLogin of
true ->
NegTimeout = ?GET_INTERNAL_OPT(negotiation_timeout, Opts,
?GET_OPT(negotiation_timeout, Opts)),
{ok, {wait_for_socket, Role}, D,
[{{timeout, negotiation_timeout}, NegTimeout, close_connection}]};
_ ->
{ok, {wait_for_socket, Role}, D}
end.

%%%----------------------------------------------------------------
%%% Connection start and initialization helpers
Expand Down Expand Up @@ -726,6 +735,9 @@ handle_event(internal, {#ssh_msg_kexinit{},_}, {connected,Role}, D0) ->
send_bytes(SshPacket, D),
{next_state, {kexinit,Role,renegotiate}, D, [postpone, {change_callback_module,ssh_fsm_kexinit}]};

handle_event({timeout, negotiation_timeout}, close_connection, _StateName, _D) ->
{stop, {shutdown,"Negotiation timeout."}};

handle_event(internal, #ssh_msg_disconnect{description=Desc} = Msg, StateName, D0) ->
{disconnect, _, RepliesCon} =
ssh_connection:handle_msg(Msg, D0#data.connection_state, ?role(StateName), D0#data.ssh_params),
Expand Down
4 changes: 4 additions & 0 deletions lib/ssh/src/ssh_fsm_userauth_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -74,6 +74,7 @@ handle_event(internal,
D = connected_state(Reply, Ssh1, User, Method, D0),
{next_state, {connected,server}, D,
[set_max_initial_idle_timeout(D),
{{timeout, negotiation_timeout}, cancel},
{change_callback_module,ssh_connection_handler}
]
}
Expand All @@ -90,6 +91,7 @@ handle_event(internal,
D = connected_state(Reply, Ssh1, User, Method, D0),
{next_state, {connected,server}, D,
[set_max_initial_idle_timeout(D),
{{timeout, negotiation_timeout}, cancel},
{change_callback_module,ssh_connection_handler}
]};
{not_authorized, {User, Reason}, {Reply, Ssh}} when Method == "keyboard-interactive" ->
Expand Down Expand Up @@ -126,6 +128,7 @@ handle_event(internal, #ssh_msg_userauth_info_response{} = Msg, {userauth_keyboa
D = connected_state(Reply, Ssh1, User, "keyboard-interactive", D0),
{next_state, {connected,server}, D,
[set_max_initial_idle_timeout(D),
{{timeout, negotiation_timeout}, cancel},
{change_callback_module,ssh_connection_handler}
]};
{not_authorized, {User, Reason}, {Reply, Ssh}} ->
Expand All @@ -144,6 +147,7 @@ handle_event(internal, #ssh_msg_userauth_info_response{} = Msg, {userauth_keyboa
D = connected_state(Reply, Ssh1, User, "keyboard-interactive", D0),
{next_state, {connected,server}, D,
[set_max_initial_idle_timeout(D),
{{timeout, negotiation_timeout}, cancel},
{change_callback_module,ssh_connection_handler}
]
};
Expand Down
4 changes: 2 additions & 2 deletions lib/ssh/test/ssh_protocol_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1024,7 +1024,7 @@ client_close_after_hello(Config0) ->
length(Handshakers), Handshakers,
length(Parents), Parents]),
if
length(Handshakers)>0 ->
length(Handshakers) == 0 -> % no handshakers are created after parallel_login rewrite
lists:foreach(fun(P) -> exit(P,some_reason) end, Parents),
ct:log("After sending exits; now going to sleep", []),
timer:sleep((SleepSec+15)*1000),
Expand Down Expand Up @@ -1052,7 +1052,7 @@ client_close_after_hello(Config0) ->
end;

true ->
{fail, no_handshakers}
{fail, handshakers_found}
end.


Expand Down

0 comments on commit e57594f

Please sign in to comment.