Skip to content

Commit 42a576e

Browse files
committed
ssh: postpone ssh_connection_handler init
1 parent bfa0b9e commit 42a576e

File tree

1 file changed

+37
-28
lines changed

1 file changed

+37
-28
lines changed

lib/ssh/src/ssh_connection_handler.erl

Lines changed: 37 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -399,34 +399,14 @@ alg(ConnectionHandler) ->
399399
%%====================================================================
400400
%% Intitialisation
401401
%%====================================================================
402-
403402
init([Role, Socket, Opts]) when Role==client ; Role==server ->
404-
case inet:peername(Socket) of
405-
{ok, PeerAddr} ->
406-
try
407-
{Protocol, Callback, CloseTag} = ?GET_OPT(transport, Opts),
408-
D = #data{starter = ?GET_INTERNAL_OPT(user_pid, Opts),
409-
socket = Socket,
410-
transport_protocol = Protocol,
411-
transport_cb = Callback,
412-
transport_close_tag = CloseTag,
413-
ssh_params = init_ssh_record(Role, Socket, PeerAddr, Opts),
414-
connection_state = init_connection_record(Role, Socket, Opts)
415-
},
416-
process_flag(trap_exit, true),
417-
{ok, {hello,Role}, D}
418-
catch
419-
_:{error,Error} -> {stop, {error,Error}};
420-
error:Error -> {stop, {error,Error}}
421-
end;
422-
423-
{error,Error} ->
424-
{stop, {shutdown,Error}}
425-
end.
403+
%% ssh_params will be updated after receiving socket_control event
404+
%% in wait_for_socket state;
405+
D = #data{socket = Socket, ssh_params = #ssh{opts = Opts}},
406+
{ok, {wait_for_socket, Role}, D}.
426407

427408
%%%----------------------------------------------------------------
428409
%%% Connection start and initialization helpers
429-
430410
init_connection_record(Role, Socket, Opts) ->
431411
{WinSz, PktSz} = init_inet_buffers_window(Socket),
432412
C = #connection{channel_cache = ssh_client_channel:cache_create(),
@@ -576,15 +556,40 @@ renegotiation(_) -> false.
576556
{next_event,internal,{conn_msg,Msg}}]).
577557

578558
%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
579-
580559
callback_mode() ->
581560
[handle_event_function,
582561
state_enter].
583562

584-
585563
%%% ######## {hello, client|server} ####
586-
%% The very first event that is sent when the we are set as controlling process of Socket
587-
handle_event(cast, socket_control, {hello,_}=StateName, #data{ssh_params = Ssh0} = D) ->
564+
%% The very first event that is sent when ssh_connection_handler
565+
%% becomes owner process for Socket
566+
handle_event(cast, socket_control, {wait_for_socket, Role},
567+
#data{socket = Socket, ssh_params = #ssh{opts = Opts}}) ->
568+
case inet:peername(Socket) of
569+
{ok, PeerAddr} ->
570+
try
571+
{Protocol, Callback, CloseTag} = ?GET_OPT(transport, Opts),
572+
D = #data{starter = ?GET_INTERNAL_OPT(user_pid, Opts),
573+
socket = Socket,
574+
transport_protocol = Protocol,
575+
transport_cb = Callback,
576+
transport_close_tag = CloseTag,
577+
ssh_params = init_ssh_record(Role, Socket, PeerAddr, Opts),
578+
connection_state = init_connection_record(Role, Socket, Opts)
579+
},
580+
process_flag(trap_exit, true),
581+
NextEvent = {next_event, internal, socket_ready},
582+
{next_state, {hello,Role}, D, NextEvent}
583+
catch
584+
_:{error,Error} -> {stop, {error,Error}};
585+
error:Error -> {stop, {error,Error}}
586+
end;
587+
588+
{error,Error} ->
589+
{stop, {shutdown,Error}}
590+
end;
591+
592+
handle_event(internal, socket_ready, {hello,_}=StateName, #data{ssh_params = Ssh0} = D) ->
588593
VsnMsg = ssh_transport:hello_version_msg(string_version(Ssh0)),
589594
send_bytes(VsnMsg, D),
590595
case inet:getopts(Socket=D#data.socket, [recbuf]) of
@@ -1363,6 +1368,10 @@ handle_event(Type, Ev, StateName, D0) ->
13631368
) -> term().
13641369

13651370
%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
1371+
terminate(_, {wait_for_socket, _}, _) ->
1372+
%% No need to to anything - maybe we have not yet gotten
1373+
%% control over the socket
1374+
ok;
13661375

13671376
terminate(normal, _StateName, D) ->
13681377
close_transport(D);

0 commit comments

Comments
 (0)