Skip to content

Commit

Permalink
ssh: Fix parallel_login option and an intermediate controlling proc
Browse files Browse the repository at this point in the history
This option was erroneously not implemented when the state machine
was re-strutctured for the OTP-24.0 release.

The intermedite process is needed when parallel login is allowed.
Otherwise all logins would be handled sequentially.
  • Loading branch information
HansN committed Jan 11, 2022
1 parent a9225fd commit 1963f95
Show file tree
Hide file tree
Showing 2 changed files with 63 additions and 34 deletions.
92 changes: 59 additions & 33 deletions lib/ssh/src/ssh_acceptor.erl
Original file line number Diff line number Diff line change
Expand Up @@ -133,47 +133,73 @@ acceptor_loop(Port, Address, Opts, ListenSocket, AcceptTimeout, SystemSup) ->
try
case accept(ListenSocket, AcceptTimeout, Opts) of
{ok,Socket} ->
case inet:peername(Socket) of
{ok, {FromIP,FromPort}} ->
case handle_connection(SystemSup, Address, Port, Opts, Socket) of
{error,Error} ->
catch close(Socket, Opts),
handle_error(Error, Address, Port, FromIP, FromPort);
_ ->
ok
end;
PeerName = inet:peername(Socket),
MaxSessions = ?GET_OPT(max_sessions, Opts),
NumSessions = number_of_connections(SystemSup),
ParallelLogin = ?GET_OPT(parallel_login, Opts),
case handle_connection(Address, Port, PeerName, Opts, Socket, MaxSessions, NumSessions, ParallelLogin) of
{error,Error} ->
handle_error(Error, Address, Port)
catch close(Socket, Opts),
handle_error(Error, Address, Port, PeerName);
_ ->
ok
end;
{error,Error} ->
handle_error(Error, Address, Port)
handle_error(Error, Address, Port, undefined)
end
catch
Class:Err:Stack ->
handle_error({error, {unhandled,Class,Err,Stack}}, Address, Port)
handle_error({error, {unhandled,Class,Err,Stack}}, Address, Port, undefined)
end,
?MODULE:acceptor_loop(Port, Address, Opts, ListenSocket, AcceptTimeout, SystemSup).

%%%----------------------------------------------------------------
handle_connection(SystemSup, Address, Port, Options0, Socket) ->
MaxSessions = ?GET_OPT(max_sessions, Options0),
case number_of_connections(SystemSup) < MaxSessions of
true ->
Options = ?PUT_INTERNAL_OPT([{user_pid, self()}
], Options0),
ssh_system_sup:start_subsystem(server,
#address{address = Address,
port = Port,
profile = ?GET_OPT(profile,Options)
},
Socket,
Options);
false ->
{error,{max_sessions,MaxSessions}}
end.
handle_connection(_Address, _Port, _Peer, _Options, _Socket, MaxSessions, NumSessions, _ParallelLogin)
when NumSessions >= MaxSessions->
{error,{max_sessions,MaxSessions}};

handle_connection(_Address, _Port, {error,Error}, _Options, _Socket, _MaxSessions, _NumSessions, _ParallelLogin) ->
{error,Error};

handle_connection(Address, Port, _Peer, Options, Socket, _MaxSessions, _NumSessions, ParallelLogin)
when ParallelLogin == false ->
handle_connection(Address, Port, Options, Socket);

handle_connection(Address, Port, _Peer, Options, Socket, _MaxSessions, _NumSessions, ParallelLogin)
when ParallelLogin == true ->
Ref = make_ref(),
Pid = spawn_link(
fun() ->
process_flag(trap_exit, true),
receive
{start,Ref} ->
handle_connection(Address, Port, Options, Socket)
after 10000 ->
{error, timeout2}
end
end),
catch gen_tcp:controlling_process(Socket, Pid),
Pid ! {start,Ref},
ok.



handle_connection(Address, Port, Options0, Socket) ->
Options = ?PUT_INTERNAL_OPT([{user_pid, self()}
], Options0),
ssh_system_sup:start_subsystem(server,
#address{address = Address,
port = Port,
profile = ?GET_OPT(profile,Options)
},
Socket,
Options).

%%%----------------------------------------------------------------
handle_error(Reason, ToAddress, ToPort) ->
handle_error(Reason, ToAddress, ToPort, {ok, {FromIP,FromPort}}) ->
handle_error(Reason, ToAddress, ToPort, FromIP, FromPort);

handle_error(Reason, ToAddress, ToPort, _) ->
handle_error(Reason, ToAddress, ToPort, undefined, undefined).


Expand Down Expand Up @@ -236,14 +262,14 @@ ssh_dbg_on(tcp) -> dbg:tp(?MODULE, listen, 2, x),
dbg:tpl(?MODULE, close, 2, x);

ssh_dbg_on(connections) -> dbg:tp(?MODULE, acceptor_init, 4, x),
dbg:tpl(?MODULE, handle_connection, 5, x).
dbg:tpl(?MODULE, handle_connection, 4, x).

ssh_dbg_off(tcp) -> dbg:ctpg(?MODULE, listen, 2),
dbg:ctpl(?MODULE, accept, 3),
dbg:ctpl(?MODULE, close, 2);

ssh_dbg_off(connections) -> dbg:ctp(?MODULE, acceptor_init, 4),
dbg:ctp(?MODULE, handle_connection, 5).
dbg:ctp(?MODULE, handle_connection, 4).

ssh_dbg_format(tcp, {call, {?MODULE,listen, [Port,_Opts]}}, Stack) ->
{skip, [{port,Port}|Stack]};
Expand Down Expand Up @@ -287,9 +313,9 @@ ssh_dbg_format(connections, {call, {?MODULE,acceptor_init, [_Parent, _SysSup, Ad
ssh_dbg_format(connections, {return_from, {?MODULE,acceptor_init,4}, _Ret}) ->
skip;

ssh_dbg_format(connections, {call, {?MODULE,handle_connection,[_SystemSup,_Address,_Port,_Options,_Sock]}}) ->
ssh_dbg_format(connections, {call, {?MODULE,handle_connection,[_Address,_Port,_Options,_Sock]}}) ->
skip;
ssh_dbg_format(connections, {return_from, {?MODULE,handle_connection,5}, {error,Error}}) ->
ssh_dbg_format(connections, {return_from, {?MODULE,handle_connection,4}, {error,Error}}) ->
["Starting connection to server failed:\n",
io_lib:format("Error = ~p", [Error])
].
5 changes: 4 additions & 1 deletion lib/ssh/src/ssh_connection_handler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -514,7 +514,10 @@ handshake(Pid, Ref, Timeout) ->
{'DOWN', Ref, process, Pid, {shutdown, Reason}} ->
{error, Reason};
{'DOWN', Ref, process, Pid, Reason} ->
{error, Reason}
{error, Reason};
{'EXIT',_,Reason} ->
stop(Pid),
{error, {exit,Reason}}
after Timeout ->
erlang:demonitor(Ref, [flush]),
ssh_connection_handler:stop(Pid),
Expand Down

0 comments on commit 1963f95

Please sign in to comment.