1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2008-2020. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20%%
21%%----------------------------------------------------------------------
22%% Purpose: Handles an ssh connection, e.i. both the
23%% setup SSH Transport Layer Protocol (RFC 4253), Authentication
24%% Protocol (RFC 4252) and SSH connection Protocol (RFC 4255)
25%% Details of the different protocols are
26%% implemented in ssh_transport.erl, ssh_auth.erl and ssh_connection.erl
27%% ----------------------------------------------------------------------
28
29-module(ssh_connection_handler).
30
31-behaviour(gen_statem).
32
33-include("ssh.hrl").
34-include("ssh_transport.hrl").
35-include("ssh_auth.hrl").
36-include("ssh_connect.hrl").
37
38-include("ssh_fsm.hrl").
39
40%%====================================================================
41%%% Exports
42%%====================================================================
43
44%%% Start and stop
45-export([start_link/4, start_link/5,
46         takeover/4,
47	 stop/1
48	]).
49
50%%% Internal application API
51-export([available_hkey_algorithms/2,
52	 open_channel/6,
53         start_channel/5,
54         handshake/2,
55         handle_direct_tcpip/6,
56	 request/6, request/7,
57	 reply_request/3,
58         global_request/5,
59         handle_ssh_msg_ext_info/2,
60	 send/5,
61         send_bytes/2,
62         send_msg/2,
63	 send_eof/2,
64         send_disconnect/6,
65         send_disconnect/7,
66         store/3,
67         retrieve/2,
68	 info/1, info/2,
69	 connection_info/2,
70	 channel_info/3,
71	 adjust_window/3, close/2,
72	 disconnect/4,
73	 get_print_info/1,
74         set_sock_opts/2, get_sock_opts/2,
75         prohibited_sock_option/1
76	]).
77
78%%% Behaviour callbacks
79-export([init/1, callback_mode/0, handle_event/4, terminate/3,
80	 format_status/2, code_change/4]).
81
82%%% Exports not intended to be used :). They are used for spawning and tests
83-export([init_ssh_record/3,		   % Export of this internal function
84					   % intended for low-level protocol test suites
85	 renegotiate/1, alg/1 % Export intended for test cases
86	]).
87
88-behaviour(ssh_dbg).
89-export([ssh_dbg_trace_points/0, ssh_dbg_flags/1, ssh_dbg_on/1, ssh_dbg_off/1, ssh_dbg_format/2]).
90
91
92-define(call_disconnectfun_and_log_cond(LogMsg, DetailedText, StateName, D),
93        call_disconnectfun_and_log_cond(LogMsg, DetailedText, ?MODULE, ?LINE, StateName, D)).
94
95%%====================================================================
96%% Start / stop
97%%====================================================================
98
99start_link(Role, Address, Socket, Options) ->
100    start_link(Role, Address, undefined, Socket, Options).
101
102start_link(Role, _Address=#address{}, Id, Socket, Options) ->
103    case gen_statem:start_link(?MODULE,
104                               [Role, Socket, Options],
105                               [{spawn_opt, [{message_queue_data,off_heap}]}]) of
106
107        {ok, Pid} when Id =/= undefined ->
108            %% Announce the ConnectionRef to the system supervisor so it could
109            %%   1) initiate the socket handover, and
110            %%   2) be returned to whoever called for example ssh:connect; the Pid
111            %%      returned from this function is "consumed" by the subsystem
112            %%      supervisor.
113            ?GET_INTERNAL_OPT(user_pid,Options) ! {new_connection_ref, Id, Pid},
114            {ok, Pid};
115
116        Others ->
117            Others
118    end.
119
120
121takeover(ConnPid, client, Socket, Options) ->
122    group_leader(group_leader(), ConnPid),
123    takeover(ConnPid, common, Socket, Options);
124
125takeover(ConnPid, _, Socket, Options) ->
126    {_, Callback, _} = ?GET_OPT(transport, Options),
127    case Callback:controlling_process(Socket, ConnPid) of
128        ok ->
129            gen_statem:cast(ConnPid, socket_control),
130            NegTimeout = ?GET_INTERNAL_OPT(negotiation_timeout,
131                                           Options,
132                                           ?GET_OPT(negotiation_timeout, Options)
133                                          ),
134            handshake(ConnPid, erlang:monitor(process,ConnPid), NegTimeout);
135        {error, Reason}	->
136            {error, Reason}
137    end.
138
139%%--------------------------------------------------------------------
140-spec stop(connection_ref()
141	  ) -> ok | {error, term()}.
142%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
143stop(ConnectionHandler)->
144    case call(ConnectionHandler, stop) of
145       {error, closed} ->
146	    ok;
147	Other ->
148	    Other
149    end.
150
151%%====================================================================
152%% Internal application API
153%%====================================================================
154
155%%--------------------------------------------------------------------
156%%% Some other module has decided to disconnect.
157
158-spec disconnect(Code::integer(), Details::iodata(),
159                      Module::atom(), Line::integer()) -> no_return().
160%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
161
162% Preferable called with the macro ?DISCONNECT
163
164disconnect(Code, DetailedText, Module, Line) ->
165    throw({keep_state_and_data,
166	   [{next_event, internal, {send_disconnect, Code, DetailedText, Module, Line}}]}).
167
168%%--------------------------------------------------------------------
169%%% Open a channel in the connection to the peer, that is, do the ssh
170%%% signalling with the peer.
171-spec open_channel(connection_ref(),
172		   string(),
173		   iodata(),
174		   pos_integer() | undefined,
175		   pos_integer() | undefined,
176		   timeout()
177		  ) -> {open, channel_id()} | {error, term()}.
178
179%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
180open_channel(ConnectionHandler,
181	     ChannelType, ChannelSpecificData, InitialWindowSize, MaxPacketSize,
182	     Timeout) ->
183    call(ConnectionHandler,
184	 {open,
185	  self(),
186	  ChannelType, InitialWindowSize, MaxPacketSize, ChannelSpecificData,
187	  Timeout}).
188
189%%--------------------------------------------------------------------
190%%% Start a channel handling process in the superviser tree
191-spec start_channel(connection_ref(), atom(), channel_id(), list(), term()) ->
192                           {ok, pid()} | {error, term()}.
193
194%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
195start_channel(ConnectionHandler, CallbackModule, ChannelId, Args, Exec) ->
196    {ok, {SubSysSup,Role,Opts}} = call(ConnectionHandler, get_misc),
197    ssh_subsystem_sup:start_channel(Role, SubSysSup,
198                                    ConnectionHandler, CallbackModule, ChannelId,
199                                    Args, Exec, Opts).
200
201%%--------------------------------------------------------------------
202handle_direct_tcpip(ConnectionHandler, ListenHost, ListenPort, ConnectToHost, ConnectToPort, Timeout) ->
203    call(ConnectionHandler, {handle_direct_tcpip, ListenHost, ListenPort, ConnectToHost, ConnectToPort, Timeout}).
204
205%%--------------------------------------------------------------------
206-spec request(connection_ref(),
207	      pid(),
208	      channel_id(),
209	      string(),
210	      boolean(),
211	      iodata(),
212	      timeout()
213	     ) -> success | failure | ok | {error,timeout}.
214
215-spec request(connection_ref(),
216	      channel_id(),
217	      string(),
218	      boolean(),
219	      iodata(),
220	      timeout()
221	     ) -> success | failure | ok | {error,timeout}.
222%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
223request(ConnectionHandler, ChannelPid, ChannelId, Type, true, Data, Timeout) ->
224    call(ConnectionHandler, {request, ChannelPid, ChannelId, Type, Data, Timeout});
225request(ConnectionHandler, ChannelPid, ChannelId, Type, false, Data, _) ->
226    cast(ConnectionHandler, {request, ChannelPid, ChannelId, Type, Data}).
227
228request(ConnectionHandler, ChannelId, Type, true, Data, Timeout) ->
229    call(ConnectionHandler, {request, ChannelId, Type, Data, Timeout});
230request(ConnectionHandler, ChannelId, Type, false, Data, _) ->
231    cast(ConnectionHandler, {request, ChannelId, Type, Data}).
232
233%%--------------------------------------------------------------------
234-spec reply_request(connection_ref(),
235		    success | failure,
236		    channel_id()
237		   ) -> ok.
238
239%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
240reply_request(ConnectionHandler, Status, ChannelId) ->
241    cast(ConnectionHandler, {reply_request, Status, ChannelId}).
242
243%%--------------------------------------------------------------------
244global_request(ConnectionHandler, Type, true, Data, Timeout) ->
245    call(ConnectionHandler, {global_request, Type, Data, Timeout});
246global_request(ConnectionHandler, Type, false, Data, _) ->
247    cast(ConnectionHandler, {global_request, Type, Data}).
248
249%%--------------------------------------------------------------------
250-spec send(connection_ref(),
251	   channel_id(),
252	   non_neg_integer(),
253	   iodata(),
254	   timeout()
255	  ) -> ok | {error, timeout|closed}.
256%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
257send(ConnectionHandler, ChannelId, Type, Data, Timeout) ->
258    call(ConnectionHandler, {data, ChannelId, Type, Data, Timeout}).
259
260%%--------------------------------------------------------------------
261-spec send_eof(connection_ref(),
262	       channel_id()
263	      ) -> ok | {error,closed}.
264%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
265send_eof(ConnectionHandler, ChannelId) ->
266    call(ConnectionHandler, {eof, ChannelId}).
267
268%%--------------------------------------------------------------------
269-spec info(connection_ref()
270	  ) -> {ok, [#channel{}]} .
271
272-spec info(connection_ref(),
273	   pid() | all
274	  ) -> {ok, [#channel{}]} .
275%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
276info(ConnectionHandler) ->
277    info(ConnectionHandler, all).
278
279info(ConnectionHandler, ChannelProcess) ->
280    call(ConnectionHandler, {info, ChannelProcess}).
281
282%%--------------------------------------------------------------------
283-type local_sock_info() :: {inet:ip_address(), non_neg_integer()} | string().
284-type peer_sock_info()  :: {inet:ip_address(), non_neg_integer()} | string().
285-type state_info() :: iolist().
286
287-spec get_print_info(connection_ref()
288		    ) -> {{local_sock_info(), peer_sock_info()},
289			  state_info()
290			 }.
291%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
292get_print_info(ConnectionHandler) ->
293    call(ConnectionHandler, get_print_info, 1000).
294
295%%--------------------------------------------------------------------
296connection_info(ConnectionHandler, []) ->
297    connection_info(ConnectionHandler, conn_info_keys());
298connection_info(ConnectionHandler, Key) when is_atom(Key) ->
299    case connection_info(ConnectionHandler, [Key]) of
300        [{Key,Val}] -> {Key,Val};
301        Other -> Other
302    end;
303connection_info(ConnectionHandler, Options) ->
304    call(ConnectionHandler, {connection_info, Options}).
305
306%%--------------------------------------------------------------------
307-spec channel_info(connection_ref(),
308		   channel_id(),
309		   [atom()]
310		  ) -> proplists:proplist().
311%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
312channel_info(ConnectionHandler, ChannelId, Options) ->
313    call(ConnectionHandler, {channel_info, ChannelId, Options}).
314
315%%--------------------------------------------------------------------
316-spec adjust_window(connection_ref(),
317		    channel_id(),
318		    integer()
319		   ) -> ok.
320%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
321adjust_window(ConnectionHandler, Channel, Bytes) ->
322    cast(ConnectionHandler, {adjust_window, Channel, Bytes}).
323
324%%--------------------------------------------------------------------
325-spec close(connection_ref(),
326	    channel_id()
327	   ) -> ok.
328%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
329close(ConnectionHandler, ChannelId) ->
330    case call(ConnectionHandler, {close, ChannelId}) of
331	ok ->
332	    ok;
333	{error, closed} ->
334	    ok
335    end.
336
337
338%%--------------------------------------------------------------------
339store(ConnectionHandler, Key, Value) ->
340    cast(ConnectionHandler, {store,Key,Value}).
341
342retrieve(#connection{options=Opts}, Key) ->
343    try ?GET_INTERNAL_OPT(Key, Opts) of
344        Value ->
345            {ok,Value}
346    catch
347        error:{badkey,Key} ->
348            undefined
349    end;
350retrieve(ConnectionHandler, Key) ->
351    call(ConnectionHandler, {retrieve,Key}).
352
353%%--------------------------------------------------------------------
354%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
355set_sock_opts(ConnectionRef, SocketOptions) ->
356    try lists:foldr(fun({Name,_Val}, Acc) ->
357                            case prohibited_sock_option(Name) of
358                                true -> [Name|Acc];
359                                false -> Acc
360                            end
361                    end, [], SocketOptions)
362    of
363        [] ->
364            call(ConnectionRef, {set_sock_opts,SocketOptions});
365        Bad ->
366            {error, {not_allowed,Bad}}
367    catch
368        _:_ ->
369            {error, badarg}
370    end.
371
372prohibited_sock_option(active)    -> true;
373prohibited_sock_option(deliver)   -> true;
374prohibited_sock_option(mode)      -> true;
375prohibited_sock_option(packet)    -> true;
376prohibited_sock_option(_) -> false.
377
378%%--------------------------------------------------------------------
379%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
380get_sock_opts(ConnectionRef, SocketGetOptions) ->
381    call(ConnectionRef, {get_sock_opts,SocketGetOptions}).
382
383%%====================================================================
384%% Test support
385%%====================================================================
386%%--------------------------------------------------------------------
387-spec renegotiate(connection_ref()
388		 ) -> ok.
389%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
390renegotiate(ConnectionHandler) ->
391    cast(ConnectionHandler, force_renegotiate).
392
393%%--------------------------------------------------------------------
394alg(ConnectionHandler) ->
395    call(ConnectionHandler, get_alg).
396
397%%====================================================================
398%% Intitialisation
399%%====================================================================
400
401init([Role, Socket, Opts]) when Role==client ; Role==server ->
402    case inet:peername(Socket) of
403        {ok, PeerAddr} ->
404            try
405                {Protocol, Callback, CloseTag} = ?GET_OPT(transport, Opts),
406                D = #data{starter = ?GET_INTERNAL_OPT(user_pid, Opts),
407                          socket = Socket,
408                          transport_protocol = Protocol,
409                          transport_cb = Callback,
410                          transport_close_tag = CloseTag,
411                          ssh_params = init_ssh_record(Role, Socket, PeerAddr, Opts),
412                          connection_state = init_connection_record(Role, Socket, Opts)
413                         },
414                process_flag(trap_exit, true),
415                {ok, {hello,Role}, D}
416            catch
417                _:{error,Error} -> {stop, {error,Error}};
418                error:Error ->     {stop, {error,Error}}
419            end;
420
421        {error,Error} ->
422            {stop, {error,Error}}
423    end.
424
425%%%----------------------------------------------------------------
426%%% Connection start and initalization helpers
427
428init_connection_record(Role, Socket, Opts) ->
429    {WinSz, PktSz} = init_inet_buffers_window(Socket),
430    C = #connection{channel_cache = ssh_client_channel:cache_create(),
431                    channel_id_seed = 0,
432                    suggest_window_size = WinSz,
433                    suggest_packet_size = PktSz,
434                    requests = [],
435                    options = Opts,
436                    sub_system_supervisor = ?GET_INTERNAL_OPT(subsystem_sup, Opts)
437                   },
438    case Role of
439        server ->
440            C#connection{cli_spec =
441                             ?GET_OPT(ssh_cli, Opts, {ssh_cli,[?GET_OPT(shell, Opts)]}),
442                         exec =
443                             ?GET_OPT(exec, Opts)};
444        client ->
445            C
446    end.
447
448init_ssh_record(Role, Socket, Opts) ->
449    %% Export of this internal function is
450    %% intended for low-level protocol test suites
451    {ok,PeerAddr} = inet:peername(Socket),
452    init_ssh_record(Role, Socket, PeerAddr, Opts).
453
454init_ssh_record(Role, Socket, PeerAddr, Opts) ->
455    AuthMethods = ?GET_OPT(auth_methods, Opts),
456    S0 = #ssh{role = Role,
457	      opts = Opts,
458	      userauth_supported_methods = AuthMethods,
459	      available_host_keys = available_hkey_algorithms(Role, Opts),
460	      random_length_padding = ?GET_OPT(max_random_length_padding, Opts)
461	   },
462
463    {Vsn, Version} = ssh_transport:versions(Role, Opts),
464    LocalName = case inet:sockname(Socket) of
465                    {ok,Local} -> Local;
466                    _ -> undefined
467                end,
468    case Role of
469	client ->
470	    PeerName = case ?GET_INTERNAL_OPT(host, Opts, element(1,PeerAddr)) of
471                           PeerIP when is_tuple(PeerIP) ->
472                               inet_parse:ntoa(PeerIP);
473                           PeerName0 when is_atom(PeerName0) ->
474                               atom_to_list(PeerName0);
475                           PeerName0 when is_list(PeerName0) ->
476                               PeerName0
477                       end,
478            S1 =
479                S0#ssh{c_vsn = Vsn,
480                       c_version = Version,
481                       opts = ?PUT_INTERNAL_OPT({io_cb, case ?GET_OPT(user_interaction, Opts) of
482                                                            true ->  ssh_io;
483                                                            false -> ssh_no_io
484                                                        end},
485                                                Opts),
486                       userauth_quiet_mode = ?GET_OPT(quiet_mode, Opts),
487                       peer = {PeerName, PeerAddr},
488                       local = LocalName
489                      },
490            S1#ssh{userauth_pubkeys = [K || K <- ?GET_OPT(pref_public_key_algs, Opts),
491                                            is_usable_user_pubkey(K, S1)
492                                      ]
493                  };
494
495	server ->
496	    S0#ssh{s_vsn = Vsn,
497		   s_version = Version,
498		   userauth_methods = string:tokens(AuthMethods, ","),
499		   kb_tries_left = 3,
500		   peer = {undefined, PeerAddr},
501                   local = LocalName
502		  }
503    end.
504
505
506handshake(Pid, Ref, Timeout) ->
507    receive
508	{Pid, ssh_connected} ->
509	    erlang:demonitor(Ref, [flush]),
510	    {ok, Pid};
511	{Pid, {not_connected, Reason}} ->
512	    erlang:demonitor(Ref, [flush]),
513	    {error, Reason};
514	{'DOWN', Ref, process, Pid, {shutdown, Reason}} ->
515	    {error, Reason};
516	{'DOWN', Ref, process, Pid, Reason} ->
517	    {error, Reason}
518    after Timeout ->
519	    erlang:demonitor(Ref, [flush]),
520	    ssh_connection_handler:stop(Pid),
521	    {error, timeout}
522    end.
523
524handshake(Msg, #data{starter = User}) ->
525    User ! {self(), Msg}.
526
527%%====================================================================
528%% gen_statem callbacks
529%%====================================================================
530%%--------------------------------------------------------------------
531-type event_content() ::  any().
532
533-type renegotiate_flag() :: init | renegotiate.
534
535-type state_name() ::
536        {hello,                     role()                    }
537      | {kexinit,                   role(), renegotiate_flag()}
538      | {key_exchange,              role(), renegotiate_flag()}
539      | {key_exchange_dh_gex_init,  server, renegotiate_flag()}
540      | {key_exchange_dh_gex_reply, client, renegotiate_flag()}
541      | {new_keys,                  role(), renegotiate_flag()}
542      | {ext_info,                  role(), renegotiate_flag()}
543      | {service_request,           role()                    }
544      | {userauth,                  role()                    }
545      | {userauth_keyboard_interactive,       role()          }
546      | {userauth_keyboard_interactive_extra, server          }
547      | {userauth_keyboard_interactive_info_response, client  }
548      | {connected,                 role()                    }
549	.
550
551%% The state names must fulfill some rules regarding
552%% where the role() and the renegotiate_flag() is placed:
553
554-spec renegotiation(state_name()) -> boolean().
555renegotiation({_,_,ReNeg}) -> ReNeg == renegotiate;
556renegotiation(_) -> false.
557
558
559-define(CONNECTED(StateName),
560        (element(1,StateName) == connected orelse
561         element(1,StateName) == ext_info ) ).
562
563-spec handle_event(gen_statem:event_type(),
564		   event_content(),
565		   state_name(),
566		   #data{}
567		  ) -> gen_statem:event_handler_result(state_name()) .
568
569-define(CONNECTION_MSG(Msg),
570        [{next_event, internal, prepare_next_packet},
571         {next_event,internal,{conn_msg,Msg}}]).
572
573%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
574
575callback_mode() ->
576    [handle_event_function,
577     state_enter].
578
579
580%%% ######## {hello, client|server} ####
581%% The very first event that is sent when the we are set as controlling process of Socket
582handle_event(cast, socket_control, {hello,_}=StateName, #data{ssh_params = Ssh0} = D) ->
583    VsnMsg = ssh_transport:hello_version_msg(string_version(Ssh0)),
584    send_bytes(VsnMsg, D),
585    case inet:getopts(Socket=D#data.socket, [recbuf]) of
586	{ok, [{recbuf,Size}]} ->
587	    %% Set the socket to the hello text line handling mode:
588	    inet:setopts(Socket, [{packet, line},
589				  {active, once},
590				  % Expecting the version string which might
591				  % be max ?MAX_PROTO_VERSION bytes:
592				  {recbuf, ?MAX_PROTO_VERSION},
593				  {nodelay,true}]),
594            Time = ?GET_OPT(hello_timeout, Ssh0#ssh.opts, infinity),
595	    {keep_state, D#data{inet_initial_recbuf_size=Size}, [{state_timeout,Time,no_hello_received}] };
596
597	Other ->
598            ?call_disconnectfun_and_log_cond("Option return",
599                                             io_lib:format("Unexpected getopts return:~n  ~p",[Other]),
600                                             StateName, D),
601	    {stop, {shutdown,{unexpected_getopts_return, Other}}}
602    end;
603
604handle_event(internal, {info_line,_Line}, {hello,client}, D) ->
605    %% The server may send info lines to the client before the version_exchange
606    %% RFC4253/4.2
607    inet:setopts(D#data.socket, [{active, once}]),
608    keep_state_and_data;
609
610handle_event(internal, {info_line,Line}, {hello,server}=StateName, D) ->
611    %% But the client may NOT send them to the server. Openssh answers with cleartext,
612    %% and so do we
613    send_bytes("Protocol mismatch.", D),
614    Msg = io_lib:format("Protocol mismatch in version exchange. Client sent info lines.~n~s",
615                        [ssh_dbg:hex_dump(Line, 64)]),
616    ?call_disconnectfun_and_log_cond("Protocol mismatch.", Msg, StateName, D),
617    {stop, {shutdown,"Protocol mismatch in version exchange. Client sent info lines."}};
618
619handle_event(internal, {version_exchange,Version}, {hello,Role}, D0) ->
620    {NumVsn, StrVsn} = ssh_transport:handle_hello_version(Version),
621    case handle_version(NumVsn, StrVsn, D0#data.ssh_params) of
622	{ok, Ssh1} ->
623	    %% Since the hello part is finnished correctly, we set the
624	    %% socket to the packet handling mode (including recbuf size):
625	    inet:setopts(D0#data.socket, [{packet,0},
626					 {mode,binary},
627					 {active, once},
628					 {recbuf, D0#data.inet_initial_recbuf_size}]),
629	    {KeyInitMsg, SshPacket, Ssh} = ssh_transport:key_exchange_init_msg(Ssh1),
630	    send_bytes(SshPacket, D0),
631            D = D0#data{ssh_params = Ssh,
632                        key_exchange_init_msg = KeyInitMsg},
633	    {next_state, {kexinit,Role,init}, D, {change_callback_module, ssh_fsm_kexinit}};
634
635	not_supported ->
636            {Shutdown, D} =
637                ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_VERSION_NOT_SUPPORTED,
638                                 io_lib:format("Offending version is ~p",[string:chomp(Version)]),
639                                 {hello,Role},
640                                 D0),
641	    {stop, Shutdown, D}
642    end;
643
644%%% timeout after tcp:connect but then nothing arrives
645handle_event(state_timeout, no_hello_received, {hello,_Role}=StateName, D0 = #data{ssh_params = Ssh0}) ->
646    Time = ?GET_OPT(hello_timeout, Ssh0#ssh.opts),
647    {Shutdown, D} =
648        ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
649                         lists:concat(["No HELLO recieved within ",ssh_lib:format_time_ms(Time)]),
650                         StateName, D0),
651    {stop, Shutdown, D};
652
653
654%%% ######## {service_request, client|server} ####
655
656handle_event(internal, Msg = #ssh_msg_service_request{name=ServiceName}, StateName = {service_request,server}, D0) ->
657    case ServiceName of
658	"ssh-userauth" ->
659	    Ssh0 = #ssh{session_id=SessionId} = D0#data.ssh_params,
660	    {ok, {Reply, Ssh}} = ssh_auth:handle_userauth_request(Msg, SessionId, Ssh0),
661            D = send_msg(Reply, D0#data{ssh_params = Ssh}),
662	    {next_state, {userauth,server}, D, {change_callback_module,ssh_fsm_userauth_server}};
663
664	_ ->
665            {Shutdown, D} =
666                ?send_disconnect(?SSH_DISCONNECT_SERVICE_NOT_AVAILABLE,
667                                 io_lib:format("Unknown service: ~p",[ServiceName]),
668                                 StateName, D0),
669            {stop, Shutdown, D}
670    end;
671
672handle_event(internal, #ssh_msg_service_accept{name = "ssh-userauth"}, {service_request,client},
673	     #data{ssh_params = #ssh{service="ssh-userauth"} = Ssh0} = D0) ->
674    {Msg, Ssh} = ssh_auth:init_userauth_request_msg(Ssh0),
675    D = send_msg(Msg, D0#data{ssh_params = Ssh,
676                              auth_user = Ssh#ssh.user
677                             }),
678    {next_state, {userauth,client}, D, {change_callback_module,ssh_fsm_userauth_client}};
679
680
681%% Skip ext_info messages in connected state (for example from OpenSSH >= 7.7)
682handle_event(internal, #ssh_msg_ext_info{}, {connected,_Role}, D) ->
683    {keep_state, D};
684
685handle_event(internal, {#ssh_msg_kexinit{},_}, {connected,Role}, D0) ->
686    {KeyInitMsg, SshPacket, Ssh} = ssh_transport:key_exchange_init_msg(D0#data.ssh_params),
687    D = D0#data{ssh_params = Ssh,
688		key_exchange_init_msg = KeyInitMsg},
689    send_bytes(SshPacket, D),
690    {next_state, {kexinit,Role,renegotiate}, D, [postpone, {change_callback_module,ssh_fsm_kexinit}]};
691
692handle_event(internal, #ssh_msg_disconnect{description=Desc} = Msg, StateName, D0) ->
693    {disconnect, _, RepliesCon} =
694	ssh_connection:handle_msg(Msg, D0#data.connection_state, ?role(StateName), D0#data.ssh_params),
695    {Actions,D} = send_replies(RepliesCon, D0),
696    disconnect_fun("Received disconnect: "++Desc, D),
697    {stop_and_reply, {shutdown,Desc}, Actions, D};
698
699handle_event(internal, #ssh_msg_ignore{}, _StateName, _) ->
700    keep_state_and_data;
701
702handle_event(internal, #ssh_msg_unimplemented{}, _StateName, _) ->
703    keep_state_and_data;
704
705%% Quick fix of failing test case (ssh_options_SUITE:ssh_msg_debug_fun_option_{client|server}/1)
706handle_event(cast, #ssh_msg_debug{} = Msg, State, D) ->
707    handle_event(internal, Msg, State, D);
708
709handle_event(internal, #ssh_msg_debug{} = Msg, _StateName, D) ->
710    debug_fun(Msg, D),
711    keep_state_and_data;
712
713handle_event(internal, {conn_msg,Msg}, StateName, #data{connection_state = Connection0,
714                                                        event_queue = Qev0} = D0) ->
715    Role = ?role(StateName),
716    Rengotation = renegotiation(StateName),
717    try ssh_connection:handle_msg(Msg, Connection0, Role, D0#data.ssh_params) of
718	{disconnect, Reason0, RepliesConn} ->
719            {Repls, D} = send_replies(RepliesConn, D0),
720            case {Reason0,Role} of
721                {{_, Reason}, client} when ((StateName =/= {connected,client})
722                                            and (not Rengotation)) ->
723                    handshake({not_connected,Reason}, D);
724                _ ->
725                    ok
726            end,
727            {stop_and_reply, {shutdown,normal}, Repls, D};
728
729	{Replies, Connection} when is_list(Replies) ->
730	    {Repls, D} =
731		case StateName of
732		    {connected,_} ->
733			send_replies(Replies, D0#data{connection_state=Connection});
734		    _ ->
735			{ConnReplies, NonConnReplies} = lists:splitwith(fun not_connected_filter/1, Replies),
736			send_replies(NonConnReplies, D0#data{event_queue = Qev0 ++ ConnReplies})
737		end,
738            case {Msg, StateName} of
739                {#ssh_msg_channel_close{}, {connected,_}} ->
740                    {keep_state, D, [cond_set_idle_timer(D)|Repls]};
741                {#ssh_msg_channel_success{}, _} ->
742                    update_inet_buffers(D#data.socket),
743                    {keep_state, D, Repls};
744                _ ->
745                    {keep_state, D, Repls}
746            end
747
748    catch
749	Class:Error ->
750            {Repls, D1} = send_replies(ssh_connection:handle_stop(Connection0), D0),
751            {Shutdown, D} = ?send_disconnect(?SSH_DISCONNECT_BY_APPLICATION,
752                                             io_lib:format("Internal error: ~p:~p",[Class,Error]),
753                                             StateName, D1),
754            {stop_and_reply, Shutdown, Repls, D}
755    end;
756
757
758handle_event(enter, OldState, {connected,_}=NewState, D) ->
759    %% Entering the state where re-negotiation is possible
760    init_renegotiate_timers(OldState, NewState, D);
761
762handle_event(enter, OldState, {ext_info,_,renegotiate}=NewState, D) ->
763    %% Could be hanging in exit_info state if nothing else arrives
764    init_renegotiate_timers(OldState, NewState, D);
765
766handle_event(enter, {connected,_}=OldState, NewState, D) ->
767    %% Exiting the state where re-negotiation is possible
768    pause_renegotiate_timers(OldState, NewState, D);
769
770handle_event(cast, force_renegotiate, StateName, D) ->
771    handle_event({timeout,renegotiate}, undefined, StateName, D);
772
773handle_event({timeout,renegotiate}, _, StateName, D0) ->
774    case StateName of
775        {connected,Role} ->
776            start_rekeying(Role, D0);
777        {ext_info,Role,renegotiate} ->
778            start_rekeying(Role, D0);
779        _ ->
780            %% Wrong state for starting a renegotiation, must be in re-negotiation
781            keep_state_and_data
782    end;
783
784handle_event({timeout,check_data_size}, _, StateName, D0) ->
785    %% Rekey due to sent data limit reached? (Can't be in {ext_info,...} if data is sent)
786    case StateName of
787        {connected,Role} ->
788            check_data_rekeying(Role, D0);
789        _ ->
790            %% Wrong state for starting a renegotiation, must be in re-negotiation
791            keep_state_and_data
792    end;
793
794handle_event({call,From}, get_alg, _, D) ->
795    #ssh{algorithms=Algs} = D#data.ssh_params,
796    {keep_state_and_data, [{reply,From,Algs}]};
797
798handle_event(cast, _, StateName, _) when not ?CONNECTED(StateName) ->
799    {keep_state_and_data, [postpone]};
800
801handle_event(cast, {adjust_window,ChannelId,Bytes}, StateName, D) when ?CONNECTED(StateName) ->
802    case ssh_client_channel:cache_lookup(cache(D), ChannelId) of
803	#channel{recv_window_size = WinSize,
804		 recv_window_pending = Pending,
805		 recv_packet_size = PktSize} = Channel
806	  when (WinSize-Bytes) >= 2*PktSize ->
807	    %% The peer can send at least two more *full* packet, no hurry.
808	    ssh_client_channel:cache_update(cache(D),
809				     Channel#channel{recv_window_pending = Pending + Bytes}),
810	    keep_state_and_data;
811
812	#channel{recv_window_size = WinSize,
813		 recv_window_pending = Pending,
814		 remote_id = Id} = Channel ->
815	    %% Now we have to update the window - we can't receive so many more pkts
816	    ssh_client_channel:cache_update(cache(D),
817				     Channel#channel{recv_window_size =
818							 WinSize + Bytes + Pending,
819						     recv_window_pending = 0}),
820	    Msg = ssh_connection:channel_adjust_window_msg(Id, Bytes + Pending),
821	    {keep_state, send_msg(Msg,D)};
822
823	undefined ->
824	    keep_state_and_data
825    end;
826
827handle_event(cast, {reply_request,Resp,ChannelId}, StateName, D) when ?CONNECTED(StateName) ->
828    case ssh_client_channel:cache_lookup(cache(D), ChannelId) of
829        #channel{remote_id = RemoteId} when Resp== success ; Resp==failure ->
830            Msg =
831                case Resp of
832                    success -> ssh_connection:channel_success_msg(RemoteId);
833                    failure -> ssh_connection:channel_failure_msg(RemoteId)
834                end,
835            update_inet_buffers(D#data.socket),
836            {keep_state, send_msg(Msg,D)};
837
838        #channel{} ->
839            Details = io_lib:format("Unhandled reply in state ~p:~n~p", [StateName,Resp]),
840            {_Shutdown, D1} =
841                ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR, Details, StateName, D),
842            {keep_state, D1};
843
844	undefined ->
845	    keep_state_and_data
846    end;
847
848handle_event(cast, {request,ChannelPid, ChannelId, Type, Data}, StateName, D) when ?CONNECTED(StateName) ->
849    {keep_state,  handle_request(ChannelPid, ChannelId, Type, Data, false, none, D)};
850
851handle_event(cast, {request,ChannelId,Type,Data}, StateName, D) when ?CONNECTED(StateName) ->
852    {keep_state,  handle_request(ChannelId, Type, Data, false, none, D)};
853
854handle_event(cast, {unknown,Data}, StateName, D) when ?CONNECTED(StateName) ->
855    Msg = #ssh_msg_unimplemented{sequence = Data},
856    {keep_state, send_msg(Msg,D)};
857
858handle_event(cast, {global_request, Type, Data}, StateName, D) when ?CONNECTED(StateName) ->
859    {keep_state, send_msg(ssh_connection:request_global_msg(Type,false,Data), D)};
860
861
862%%% Previously handle_sync_event began here
863handle_event({call,From}, get_print_info, StateName, D) ->
864    Reply =
865	try
866	    {inet:sockname(D#data.socket),
867	     inet:peername(D#data.socket)
868	    }
869	of
870	    {{ok,Local}, {ok,Remote}} ->
871		{{Local,Remote},io_lib:format("statename=~p",[StateName])};
872	    _ ->
873		{{"-",0},"-"}
874	catch
875	    _:_ ->
876		{{"?",0},"?"}
877	end,
878    {keep_state_and_data, [{reply,From,Reply}]};
879
880handle_event({call,From}, {connection_info, Options}, _, D) ->
881    Info = fold_keys(Options, fun conn_info/2, D),
882    {keep_state_and_data, [{reply,From,Info}]};
883
884handle_event({call,From}, {channel_info,ChannelId,Options}, _, D) ->
885    case ssh_client_channel:cache_lookup(cache(D), ChannelId) of
886	#channel{} = Channel ->
887	    Info = fold_keys(Options, fun chann_info/2, Channel),
888	    {keep_state_and_data, [{reply,From,Info}]};
889	undefined ->
890	    {keep_state_and_data, [{reply,From,[]}]}
891    end;
892
893
894handle_event({call,From}, {info, all}, _, D) ->
895    Result = ssh_client_channel:cache_foldl(fun(Channel, Acc) ->
896					     [Channel | Acc]
897				     end,
898				     [], cache(D)),
899    {keep_state_and_data, [{reply, From, {ok,Result}}]};
900
901handle_event({call,From}, {info, ChannelPid}, _, D) ->
902    Result = ssh_client_channel:cache_foldl(
903	       fun(Channel, Acc) when Channel#channel.user == ChannelPid ->
904		       [Channel | Acc];
905		  (_, Acc) ->
906		       Acc
907	       end, [], cache(D)),
908    {keep_state_and_data, [{reply, From, {ok,Result}}]};
909
910handle_event({call,From}, {set_sock_opts,SocketOptions}, _StateName, D) ->
911    Result = try inet:setopts(D#data.socket, SocketOptions)
912             catch
913                 _:_ -> {error, badarg}
914             end,
915    {keep_state_and_data, [{reply,From,Result}]};
916
917handle_event({call,From}, {get_sock_opts,SocketGetOptions}, _StateName, D) ->
918    Result = try inet:getopts(D#data.socket, SocketGetOptions)
919             catch
920                 _:_ -> {error, badarg}
921             end,
922    {keep_state_and_data, [{reply,From,Result}]};
923
924handle_event({call,From}, stop, _StateName, D0) ->
925    {Repls,D} = send_replies(ssh_connection:handle_stop(D0#data.connection_state), D0),
926    {stop_and_reply, normal, [{reply,From,ok}|Repls], D};
927
928handle_event({call,_}, _, StateName, _) when not ?CONNECTED(StateName) ->
929    {keep_state_and_data, [postpone]};
930
931handle_event({call,From}, {request, ChannelPid, ChannelId, Type, Data, Timeout}, StateName, D0)
932  when ?CONNECTED(StateName) ->
933    case handle_request(ChannelPid, ChannelId, Type, Data, true, From, D0) of
934        {error,Error} ->
935            {keep_state, D0, {reply,From,{error,Error}}};
936        D ->
937            %% Note reply to channel will happen later when reply is recived from peer on the socket
938            start_channel_request_timer(ChannelId, From, Timeout),
939            {keep_state, D, cond_set_idle_timer(D)}
940    end;
941
942handle_event({call,From}, {request, ChannelId, Type, Data, Timeout}, StateName, D0)
943  when ?CONNECTED(StateName) ->
944    case handle_request(ChannelId, Type, Data, true, From, D0) of
945        {error,Error} ->
946            {keep_state, D0, {reply,From,{error,Error}}};
947        D ->
948            %% Note reply to channel will happen later when reply is recived from peer on the socket
949            start_channel_request_timer(ChannelId, From, Timeout),
950            {keep_state, D, cond_set_idle_timer(D)}
951    end;
952
953handle_event({call,From}, {global_request, "tcpip-forward" = Type,
954                           {ListenHost,ListenPort,ConnectToHost,ConnectToPort},
955                           Timeout}, StateName, D0) when ?CONNECTED(StateName) ->
956    Id = make_ref(),
957    Data =  <<?STRING(ListenHost), ?Euint32(ListenPort)>>,
958    Fun = fun({success, <<Port:32/unsigned-integer>>}, C) ->
959                  Key = {tcpip_forward,ListenHost,Port},
960                  Value = {ConnectToHost,ConnectToPort},
961                  C#connection{options = ?PUT_INTERNAL_OPT({Key,Value}, C#connection.options)};
962             ({success, <<>>}, C) ->
963                  Key = {tcpip_forward,ListenHost,ListenPort},
964                  Value = {ConnectToHost,ConnectToPort},
965                  C#connection{options = ?PUT_INTERNAL_OPT({Key,Value}, C#connection.options)};
966             (_, C) ->
967                  C
968          end,
969    D = send_msg(ssh_connection:request_global_msg(Type, true, Data),
970                 add_request(Fun, Id, From, D0)),
971    start_channel_request_timer(Id, From, Timeout),
972    {keep_state, D, cond_set_idle_timer(D)};
973
974handle_event({call,From}, {global_request, Type, Data, Timeout}, StateName, D0) when ?CONNECTED(StateName) ->
975    Id = make_ref(),
976    D = send_msg(ssh_connection:request_global_msg(Type, true, Data),
977                 add_request(true, Id, From, D0)),
978    start_channel_request_timer(Id, From, Timeout),
979    {keep_state, D, cond_set_idle_timer(D)};
980
981handle_event({call,From}, {data, ChannelId, Type, Data, Timeout}, StateName, D0)
982  when ?CONNECTED(StateName) ->
983    {Repls,D} = send_replies(ssh_connection:channel_data(ChannelId, Type, Data, D0#data.connection_state, From),
984                             D0),
985    start_channel_request_timer(ChannelId, From, Timeout), % FIXME: No message exchange so why?
986    {keep_state, D, Repls};
987
988handle_event({call,From}, {eof, ChannelId}, StateName, D0)
989  when ?CONNECTED(StateName) ->
990    case ssh_client_channel:cache_lookup(cache(D0), ChannelId) of
991	#channel{remote_id = Id, sent_close = false} ->
992	    D = send_msg(ssh_connection:channel_eof_msg(Id), D0),
993	    {keep_state, D, [{reply,From,ok}]};
994	_ ->
995	    {keep_state, D0, [{reply,From,{error,closed}}]}
996    end;
997
998handle_event({call,From}, get_misc, StateName,
999             #data{connection_state = #connection{options = Opts}} = D) when ?CONNECTED(StateName) ->
1000    SubSysSup = ?GET_INTERNAL_OPT(subsystem_sup, Opts),
1001    Reply = {ok, {SubSysSup, ?role(StateName), Opts}},
1002    {keep_state, D, [{reply,From,Reply}]};
1003
1004handle_event({call,From},
1005	     {open, ChannelPid, Type, InitialWindowSize, MaxPacketSize, Data, Timeout},
1006	     StateName,
1007	     D0 = #data{connection_state = C}) when ?CONNECTED(StateName) ->
1008    erlang:monitor(process, ChannelPid),
1009    {ChannelId, D1} = new_channel_id(D0),
1010    WinSz = case InitialWindowSize of
1011                undefined -> C#connection.suggest_window_size;
1012                _ -> InitialWindowSize
1013            end,
1014    PktSz = case MaxPacketSize of
1015                undefined -> C#connection.suggest_packet_size;
1016                _ -> MaxPacketSize
1017            end,
1018    D2 = send_msg(ssh_connection:channel_open_msg(Type, ChannelId, WinSz, PktSz, Data),
1019		  D1),
1020    ssh_client_channel:cache_update(cache(D2),
1021			     #channel{type = Type,
1022				      sys = "none",
1023				      user = ChannelPid,
1024				      local_id = ChannelId,
1025				      recv_window_size = WinSz,
1026				      recv_packet_size = PktSz,
1027				      send_buf = queue:new()
1028				     }),
1029    D = add_request(true, ChannelId, From, D2),
1030    start_channel_request_timer(ChannelId, From, Timeout),
1031    {keep_state, D, cond_set_idle_timer(D)};
1032
1033handle_event({call,From}, {send_window, ChannelId}, StateName, D)
1034  when ?CONNECTED(StateName) ->
1035    Reply = case ssh_client_channel:cache_lookup(cache(D), ChannelId) of
1036		#channel{send_window_size = WinSize,
1037			 send_packet_size = Packsize} ->
1038		    {ok, {WinSize, Packsize}};
1039		undefined ->
1040		    {error, einval}
1041	    end,
1042    {keep_state_and_data, [{reply,From,Reply}]};
1043
1044handle_event({call,From}, {recv_window, ChannelId}, StateName, D)
1045  when ?CONNECTED(StateName) ->
1046    Reply = case ssh_client_channel:cache_lookup(cache(D), ChannelId) of
1047		#channel{recv_window_size = WinSize,
1048			 recv_packet_size = Packsize} ->
1049		    {ok, {WinSize, Packsize}};
1050		undefined ->
1051		    {error, einval}
1052	    end,
1053    {keep_state_and_data, [{reply,From,Reply}]};
1054
1055handle_event({call,From}, {close, ChannelId}, StateName, D0)
1056  when ?CONNECTED(StateName) ->
1057    case ssh_client_channel:cache_lookup(cache(D0), ChannelId) of
1058	#channel{remote_id = Id} = Channel ->
1059	    D1 = send_msg(ssh_connection:channel_close_msg(Id), D0),
1060	    ssh_client_channel:cache_update(cache(D1), Channel#channel{sent_close = true}),
1061	    {keep_state, D1, [cond_set_idle_timer(D1), {reply,From,ok}]};
1062	undefined ->
1063	    {keep_state_and_data, [{reply,From,ok}]}
1064    end;
1065
1066handle_event(cast, {store,Key,Value}, _StateName, #data{connection_state=C0} = D) ->
1067    C = C0#connection{options = ?PUT_INTERNAL_OPT({Key,Value}, C0#connection.options)},
1068    {keep_state, D#data{connection_state = C}};
1069
1070handle_event({call,From}, {retrieve,Key}, _StateName, #data{connection_state=C}) ->
1071    case retrieve(C, Key) of
1072        {ok,Value} ->
1073            {keep_state_and_data, [{reply,From,{ok,Value}}]};
1074        _ ->
1075            {keep_state_and_data, [{reply,From,undefined}]}
1076    end;
1077
1078%%===== Reception of encrypted bytes, decryption and framing
1079handle_event(info, {Proto, Sock, Info}, {hello,_}, #data{socket = Sock,
1080							 transport_protocol = Proto}) ->
1081    case Info of
1082	"SSH-" ++ _ ->
1083	    {keep_state_and_data, [{next_event, internal, {version_exchange,Info}}]};
1084	_ ->
1085	    {keep_state_and_data, [{next_event, internal, {info_line,Info}}]}
1086    end;
1087
1088
1089handle_event(info, {Proto, Sock, NewData}, StateName, D0 = #data{socket = Sock,
1090								 transport_protocol = Proto}) ->
1091    try ssh_transport:handle_packet_part(
1092	  D0#data.decrypted_data_buffer,
1093	  <<(D0#data.encrypted_data_buffer)/binary, NewData/binary>>,
1094          D0#data.aead_data,
1095          D0#data.undecrypted_packet_length,
1096	  D0#data.ssh_params)
1097    of
1098	{packet_decrypted, DecryptedBytes, EncryptedDataRest, Ssh1} ->
1099	    D1 = D0#data{ssh_params =
1100			    Ssh1#ssh{recv_sequence = ssh_transport:next_seqnum(Ssh1#ssh.recv_sequence)},
1101			decrypted_data_buffer = <<>>,
1102                        undecrypted_packet_length = undefined,
1103                        aead_data = <<>>,
1104			encrypted_data_buffer = EncryptedDataRest},
1105	    try
1106		ssh_message:decode(set_kex_overload_prefix(DecryptedBytes,D1))
1107	    of
1108		#ssh_msg_kexinit{} = Msg ->
1109		    {keep_state, D1, [{next_event, internal, prepare_next_packet},
1110				     {next_event, internal, {Msg,DecryptedBytes}}
1111				    ]};
1112
1113                #ssh_msg_global_request{}            = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1114                #ssh_msg_request_success{}           = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1115                #ssh_msg_request_failure{}           = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1116                #ssh_msg_channel_open{}              = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1117                #ssh_msg_channel_open_confirmation{} = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1118                #ssh_msg_channel_open_failure{}      = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1119                #ssh_msg_channel_window_adjust{}     = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1120                #ssh_msg_channel_data{}              = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1121                #ssh_msg_channel_extended_data{}     = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1122                #ssh_msg_channel_eof{}               = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1123                #ssh_msg_channel_close{}             = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1124                #ssh_msg_channel_request{}           = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1125                #ssh_msg_channel_failure{}           = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1126                #ssh_msg_channel_success{}           = Msg -> {keep_state, D1, ?CONNECTION_MSG(Msg)};
1127
1128		Msg ->
1129		    {keep_state, D1, [{next_event, internal, prepare_next_packet},
1130                                      {next_event, internal, Msg}
1131				    ]}
1132	    catch
1133		C:E:ST  ->
1134                    {Shutdown, D} =
1135                        ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
1136                                         io_lib:format("Bad packet: Decrypted, but can't decode~n~p:~p~n~p",
1137                                                       [C,E,ST]),
1138                                         StateName, D1),
1139                    {stop, Shutdown, D}
1140	    end;
1141
1142	{get_more, DecryptedBytes, EncryptedDataRest, AeadData, RemainingSshPacketLen, Ssh1} ->
1143	    %% Here we know that there are not enough bytes in
1144	    %% EncryptedDataRest to use. We must wait for more.
1145	    inet:setopts(Sock, [{active, once}]),
1146	    {keep_state, D0#data{encrypted_data_buffer = EncryptedDataRest,
1147				 decrypted_data_buffer = DecryptedBytes,
1148                                 undecrypted_packet_length = RemainingSshPacketLen,
1149                                 aead_data = AeadData,
1150				 ssh_params = Ssh1}};
1151
1152	{bad_mac, Ssh1} ->
1153            {Shutdown, D} =
1154                ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
1155                                 "Bad packet: bad mac",
1156                                 StateName, D0#data{ssh_params=Ssh1}),
1157            {stop, Shutdown, D};
1158
1159	{error, {exceeds_max_size,PacketLen}} ->
1160            {Shutdown, D} =
1161                ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
1162                                 io_lib:format("Bad packet: Size (~p bytes) exceeds max size",
1163                                               [PacketLen]),
1164                                 StateName, D0),
1165            {stop, Shutdown, D}
1166    catch
1167	C:E:ST ->
1168            {Shutdown, D} =
1169                ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR,
1170                                 io_lib:format("Bad packet: Couldn't decrypt~n~p:~p~n~p",[C,E,ST]),
1171                                 StateName, D0),
1172            {stop, Shutdown, D}
1173    end;
1174
1175
1176%%%====
1177handle_event(internal, prepare_next_packet, _StateName, D) ->
1178    Enough =  erlang:max(8, D#data.ssh_params#ssh.decrypt_block_size),
1179    case size(D#data.encrypted_data_buffer) of
1180	Sz when Sz >= Enough ->
1181	    self() ! {D#data.transport_protocol, D#data.socket, <<>>};
1182	_ ->
1183	    ok
1184    end,
1185    inet:setopts(D#data.socket, [{active, once}]),
1186    keep_state_and_data;
1187
1188handle_event(info, {CloseTag,Socket}, _StateName,
1189	     D0 = #data{socket = Socket,
1190                        transport_close_tag = CloseTag,
1191                        connection_state = C0}) ->
1192    {Repls, D} = send_replies(ssh_connection:handle_stop(C0), D0),
1193    disconnect_fun("Received a transport close", D),
1194    {stop_and_reply, {shutdown,"Connection closed"}, Repls, D};
1195
1196handle_event(info, {timeout, {_, From} = Request}, _,
1197	     #data{connection_state = #connection{requests = Requests} = C0} = D) ->
1198    case lists:member(Request, Requests) of
1199	true ->
1200	    %% A channel request is not answered in time. Answer {error,timeout}
1201	    %% to the caller
1202	    C = C0#connection{requests = lists:delete(Request, Requests)},
1203	    {keep_state, D#data{connection_state=C}, [{reply,From,{error,timeout}}]};
1204	false ->
1205	    %% The request is answered - just ignore the timeout
1206	    keep_state_and_data
1207    end;
1208
1209%%% Handle that ssh channels user process goes down
1210handle_event(info, {'DOWN', _Ref, process, ChannelPid, _Reason}, _, D) ->
1211    Cache = cache(D),
1212    ssh_client_channel:cache_foldl(
1213      fun(#channel{user=U,
1214                   local_id=Id}, Acc) when U == ChannelPid ->
1215              ssh_client_channel:cache_delete(Cache, Id),
1216              Acc;
1217         (_,Acc) ->
1218              Acc
1219      end, [], Cache),
1220    {keep_state, D, cond_set_idle_timer(D)};
1221
1222handle_event({timeout,idle_time}, _Data,  _StateName, D) ->
1223    case ssh_client_channel:cache_info(num_entries, cache(D)) of
1224        0 ->
1225            {stop, {shutdown, "Timeout"}};
1226        _ ->
1227            keep_state_and_data
1228    end;
1229
1230%%% So that terminate will be run when supervisor is shutdown
1231handle_event(info, {'EXIT', _Sup, Reason}, StateName, _D) ->
1232    Role = ?role(StateName),
1233    if
1234	Role == client ->
1235	    %% OTP-8111 tells this function clause fixes a problem in
1236	    %% clients, but there were no check for that role.
1237	    {stop, {shutdown, Reason}};
1238
1239	Reason == normal ->
1240	    %% An exit normal should not cause a server to crash. This has happend...
1241	    keep_state_and_data;
1242
1243	true ->
1244	    {stop, {shutdown, Reason}}
1245    end;
1246
1247handle_event(info, check_cache, _, D) ->
1248    {keep_state, D, cond_set_idle_timer(D)};
1249
1250handle_event(info, {fwd_connect_received, Sock, ChId, ChanCB}, StateName, #data{connection_state = Connection}) ->
1251    #connection{options = Options,
1252                channel_cache = Cache,
1253                sub_system_supervisor = SubSysSup} = Connection,
1254    Channel = ssh_client_channel:cache_lookup(Cache, ChId),
1255    {ok,Pid} = ssh_subsystem_sup:start_channel(?role(StateName), SubSysSup, self(), ChanCB, ChId, [Sock], undefined, Options),
1256    ssh_client_channel:cache_update(Cache, Channel#channel{user=Pid}),
1257    gen_tcp:controlling_process(Sock, Pid),
1258    inet:setopts(Sock, [{active,once}]),
1259    keep_state_and_data;
1260
1261handle_event({call,From},
1262             {handle_direct_tcpip, ListenHost, ListenPort, ConnectToHost, ConnectToPort, _Timeout},
1263             _StateName,
1264             #data{connection_state = #connection{sub_system_supervisor=SubSysSup}}) ->
1265    case ssh_tcpip_forward_acceptor:supervised_start(ssh_subsystem_sup:tcpip_fwd_supervisor(SubSysSup),
1266                                                     {ListenHost, ListenPort},
1267                                                     {ConnectToHost, ConnectToPort},
1268                                                     "direct-tcpip", ssh_tcpip_forward_client,
1269                                                     self()) of
1270        {ok,LPort} ->
1271            {keep_state_and_data, [{reply,From,{ok,LPort}}]};
1272        {error,Error} ->
1273            {keep_state_and_data, [{reply,From,{error,Error}}]}
1274    end;
1275
1276handle_event(info, UnexpectedMessage, StateName, D = #data{ssh_params = Ssh}) ->
1277    case unexpected_fun(UnexpectedMessage, D) of
1278	report ->
1279	    Msg = lists:flatten(
1280		    io_lib:format(
1281                      "*** SSH: "
1282		      "Unexpected message '~p' received in state '~p'\n"
1283		      "Role: ~p\n"
1284		      "Peer: ~p\n"
1285		      "Local Address: ~p\n",
1286                      [UnexpectedMessage,
1287                       StateName,
1288                       Ssh#ssh.role,
1289                       Ssh#ssh.peer,
1290                       ?GET_INTERNAL_OPT(address, Ssh#ssh.opts, undefined)])),
1291	    error_logger:info_report(Msg),
1292	    keep_state_and_data;
1293
1294	skip ->
1295	    keep_state_and_data;
1296
1297	Other ->
1298	    Msg = lists:flatten(
1299		    io_lib:format("*** SSH: "
1300                                  "Call to fun in 'unexpectedfun' failed:~n"
1301				  "Return: ~p\n"
1302				  "Message: ~p\n"
1303				  "Role: ~p\n"
1304				  "Peer: ~p\n"
1305				  "Local Address: ~p\n",
1306                                  [Other,
1307                                   UnexpectedMessage,
1308                                   Ssh#ssh.role,
1309                                   Ssh#ssh.peer,
1310                                   ?GET_INTERNAL_OPT(address, Ssh#ssh.opts, undefined)]
1311				 )),
1312	    error_logger:error_report(Msg),
1313	    keep_state_and_data
1314    end;
1315
1316handle_event(internal, {send_disconnect,Code,DetailedText,Module,Line}, StateName, D0) ->
1317    {Shutdown, D} =
1318        send_disconnect(Code, DetailedText, Module, Line, StateName, D0),
1319    {stop, Shutdown, D};
1320
1321
1322handle_event(enter, _OldState, State, D) ->
1323    %% Just skip
1324    {next_state, State, D};
1325
1326handle_event(_Type, _Msg, {ext_info,Role,_ReNegFlag}, D) ->
1327    %% If something else arrives, goto next state and handle the event in that one
1328    {next_state, {connected,Role}, D, [postpone]};
1329
1330handle_event(Type, Ev, StateName, D0) ->
1331    Details =
1332	case catch atom_to_list(element(1,Ev)) of
1333	    "ssh_msg_" ++_ when Type==internal ->
1334                lists:flatten(io_lib:format("Message ~p in wrong state (~p)", [element(1,Ev), StateName]));
1335	    _ ->
1336		io_lib:format("Unhandled event in state ~p and type ~p:~n~p", [StateName,Type,Ev])
1337	end,
1338    {Shutdown, D} =
1339        ?send_disconnect(?SSH_DISCONNECT_PROTOCOL_ERROR, Details, StateName, D0),
1340    {stop, Shutdown, D}.
1341
1342
1343%%--------------------------------------------------------------------
1344-spec terminate(any(),
1345		state_name(),
1346		#data{}
1347	       ) -> term().
1348
1349%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
1350
1351terminate(normal, _StateName, D) ->
1352    close_transport(D);
1353
1354terminate({shutdown,_R}, _StateName, D) ->
1355    %% Internal termination, usually already reported via ?send_disconnect resulting in a log entry
1356    close_transport(D);
1357
1358terminate(shutdown, _StateName, D0) ->
1359    %% Terminated by supervisor
1360    %% Use send_msg directly instead of ?send_disconnect to avoid filling the log
1361    D = send_msg(#ssh_msg_disconnect{code = ?SSH_DISCONNECT_BY_APPLICATION,
1362                                     description = "Terminated (shutdown) by supervisor"},
1363                 D0),
1364    close_transport(D);
1365
1366terminate(Reason, StateName, D0) ->
1367    %% Others, e.g  undef, {badmatch,_}, ...
1368    log(error, D0, Reason),
1369    {_ShutdownReason, D} = ?send_disconnect(?SSH_DISCONNECT_BY_APPLICATION,
1370                                            "Internal error",
1371                                            io_lib:format("Reason: ~p",[Reason]),
1372                                            StateName, D0),
1373    close_transport(D).
1374
1375%%--------------------------------------------------------------------
1376
1377%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
1378
1379format_status(A, B) ->
1380    try format_status0(A, B)
1381    catch
1382        _:_ -> "????"
1383    end.
1384
1385format_status0(normal, [_PDict, _StateName, D]) ->
1386    [{data, [{"State", D}]}];
1387format_status0(terminate, [_, _StateName, D]) ->
1388    [{data, [{"State", clean(D)}]}].
1389
1390
1391clean(#data{}=R) ->
1392    fmt_stat_rec(record_info(fields,data), R,
1393                 [decrypted_data_buffer,
1394                  encrypted_data_buffer,
1395                  key_exchange_init_msg,
1396                  user_passwords,
1397                  opts,
1398                  inet_initial_recbuf_size]);
1399clean(#ssh{}=R) ->
1400    fmt_stat_rec(record_info(fields, ssh), R,
1401                 [c_keyinit,
1402                  s_keyinit,
1403                  send_mac_key,
1404                  send_mac_size,
1405                  recv_mac_key,
1406                  recv_mac_size,
1407                  encrypt_keys,
1408                  encrypt_ctx,
1409                  decrypt_keys,
1410                  decrypt_ctx,
1411                  compress_ctx,
1412                  decompress_ctx,
1413                  shared_secret,
1414                  exchanged_hash,
1415                  session_id,
1416                  keyex_key,
1417                  keyex_info,
1418                  available_host_keys]);
1419clean(#connection{}=R) ->
1420    fmt_stat_rec(record_info(fields, connection), R,
1421                 []);
1422clean(L) when is_list(L) ->
1423    lists:map(fun clean/1, L);
1424clean(T) when is_tuple(T) ->
1425    list_to_tuple( clean(tuple_to_list(T)));
1426clean(X) ->
1427    ssh_options:no_sensitive(filter, X).
1428
1429fmt_stat_rec(FieldNames, Rec, Exclude) ->
1430    Values = tl(tuple_to_list(Rec)),
1431    list_to_tuple(
1432      [element(1,Rec) |
1433       lists:map(fun({K,V}) ->
1434                         case lists:member(K, Exclude) of
1435                             true -> '****';
1436                             false -> clean(V)
1437                         end
1438                 end, lists:zip(FieldNames, Values))
1439      ]).
1440
1441%%--------------------------------------------------------------------
1442-spec code_change(term() | {down,term()},
1443		  state_name(),
1444		  #data{},
1445		  term()
1446		 ) -> {ok, state_name(), #data{}}.
1447
1448%% . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
1449
1450code_change(_OldVsn, StateName, State, _Extra) ->
1451    {ok, StateName, State}.
1452
1453
1454%%====================================================================
1455%% Internal functions
1456%%====================================================================
1457
1458%%--------------------------------------------------------------------
1459close_transport(#data{transport_cb = Transport,
1460                      socket = Socket}) ->
1461    catch Transport:close(Socket),
1462    ok.
1463
1464%%--------------------------------------------------------------------
1465available_hkey_algorithms(client, Options) ->
1466    case available_hkey_algos(Options) of
1467        [] ->
1468            error({shutdown, "No public key algs"});
1469        Algs ->
1470	    [atom_to_list(A) || A<-Algs]
1471    end;
1472
1473available_hkey_algorithms(server, Options) ->
1474    case [A || A <- available_hkey_algos(Options),
1475               is_usable_host_key(A, Options)] of
1476        [] ->
1477            error({shutdown, "No host key available"});
1478	Algs ->
1479	    [atom_to_list(A) || A<-Algs]
1480    end.
1481
1482
1483available_hkey_algos(Options) ->
1484    SupAlgos = ssh_transport:supported_algorithms(public_key),
1485    HKeys = proplists:get_value(public_key,
1486                                ?GET_OPT(preferred_algorithms,Options)
1487                               ),
1488    NonSupported =  HKeys -- SupAlgos,
1489    AvailableAndSupported = HKeys -- NonSupported,
1490    AvailableAndSupported.
1491
1492
1493send_msg(Msg, State=#data{ssh_params=Ssh0}) when is_tuple(Msg) ->
1494    {Bytes, Ssh} = ssh_transport:ssh_packet(Msg, Ssh0),
1495    send_bytes(Bytes, State),
1496    State#data{ssh_params=Ssh}.
1497
1498send_bytes("", _D) ->
1499    ok;
1500send_bytes(Bytes, #data{socket = Socket, transport_cb = Transport}) ->
1501    _ = Transport:send(Socket, Bytes),
1502    ok.
1503
1504handle_version({2, 0} = NumVsn, StrVsn, Ssh0) ->
1505    Ssh = counterpart_versions(NumVsn, StrVsn, Ssh0),
1506    {ok, Ssh};
1507handle_version(_,_,_) ->
1508    not_supported.
1509
1510string_version(#ssh{role = client, c_version = Vsn}) ->
1511    Vsn;
1512string_version(#ssh{role = server, s_version = Vsn}) ->
1513    Vsn.
1514
1515
1516cast(FsmPid, Event) ->
1517    gen_statem:cast(FsmPid, Event).
1518
1519call(FsmPid, Event) ->
1520    call(FsmPid, Event, infinity).
1521
1522call(FsmPid, Event, Timeout) ->
1523    try gen_statem:call(FsmPid, Event, Timeout) of
1524	{closed, _R} ->
1525	    {error, closed};
1526	{killed, _R} ->
1527	    {error, closed};
1528	Result ->
1529	    Result
1530    catch
1531	exit:{noproc, _R} ->
1532	    {error, closed};
1533	exit:{normal, _R} ->
1534	    {error, closed};
1535	exit:{{shutdown, _R},_} ->
1536	    {error, closed};
1537	exit:{shutdown, _R} ->
1538	    {error, closed}
1539    end.
1540
1541
1542set_kex_overload_prefix(Msg = <<?BYTE(Op),_/binary>>, #data{ssh_params=SshParams})
1543  when Op == 30;
1544       Op == 31
1545       ->
1546    case catch atom_to_list(kex(SshParams)) of
1547	"ecdh-sha2-" ++ _ ->
1548	    <<"ecdh",Msg/binary>>;
1549        "curve25519-" ++ _ ->
1550	    <<"ecdh",Msg/binary>>;
1551        "curve448-" ++ _ ->
1552	    <<"ecdh",Msg/binary>>;
1553	"diffie-hellman-group-exchange-" ++ _ ->
1554	    <<"dh_gex",Msg/binary>>;
1555	"diffie-hellman-group" ++ _ ->
1556	    <<"dh",Msg/binary>>;
1557	_ ->
1558	    Msg
1559    end;
1560set_kex_overload_prefix(Msg, _) ->
1561    Msg.
1562
1563kex(#ssh{algorithms=#alg{kex=Kex}}) -> Kex;
1564kex(_) -> undefined.
1565
1566cache(#data{connection_state=C}) -> C#connection.channel_cache.
1567
1568
1569%%%----------------------------------------------------------------
1570handle_ssh_msg_ext_info(#ssh_msg_ext_info{}, D=#data{ssh_params = #ssh{recv_ext_info=false}} ) ->
1571    % The peer sent this although we didn't allow it!
1572    D;
1573
1574handle_ssh_msg_ext_info(#ssh_msg_ext_info{data=Data}, D0) ->
1575    lists:foldl(fun ext_info/2, D0, Data).
1576
1577
1578ext_info({"server-sig-algs",SigAlgsStr},
1579         D0 = #data{ssh_params=#ssh{role=client,
1580                                    userauth_pubkeys=ClientSigAlgs}=Ssh0}) ->
1581    %% ClientSigAlgs are the pub_key algortithms that:
1582    %%  1) is usable, that is, the user has such a public key and
1583    %%  2) is either the default list or set by the caller
1584    %%     with the client option 'pref_public_key_algs'
1585    %%
1586    %% The list is already checked for duplicates.
1587
1588    SigAlgs = [A || Astr <- string:tokens(SigAlgsStr, ","),
1589                    A <- try [list_to_existing_atom(Astr)]
1590                              %% list_to_existing_atom will fail for unknown algorithms
1591                         catch _:_ -> []
1592                         end],
1593
1594    CommonAlgs = [A || A <- SigAlgs,
1595                       lists:member(A, ClientSigAlgs)],
1596
1597    %% Re-arrange the client supported public-key algorithms so that the server
1598    %% preferred ones are tried first.
1599    %% Trying algorithms not mentioned by the server is ok, since the server can't know
1600    %% if the client supports 'server-sig-algs' or not.
1601
1602    D0#data{
1603      ssh_params =
1604          Ssh0#ssh{
1605            userauth_pubkeys =
1606                CommonAlgs ++ (ClientSigAlgs -- CommonAlgs)
1607           }};
1608
1609ext_info(_, D0) ->
1610    %% Not implemented
1611    D0.
1612
1613%%%----------------------------------------------------------------
1614is_usable_user_pubkey(Alg, Ssh) ->
1615    try ssh_auth:get_public_key(Alg, Ssh) of
1616        {ok,_} -> true;
1617        _ -> false
1618    catch
1619        _:_ -> false
1620    end.
1621
1622%%%----------------------------------------------------------------
1623is_usable_host_key(Alg, Opts) ->
1624    try ssh_transport:get_host_key(Alg, Opts)
1625    of
1626        _PrivHostKey -> true
1627    catch
1628        _:_ -> false
1629    end.
1630
1631%%%----------------------------------------------------------------
1632handle_request(ChannelPid, ChannelId, Type, Data, WantReply, From, D) ->
1633    case ssh_client_channel:cache_lookup(cache(D), ChannelId) of
1634	#channel{remote_id = Id,
1635                 sent_close = false} = Channel ->
1636	    update_sys(cache(D), Channel, Type, ChannelPid),
1637	    send_msg(ssh_connection:channel_request_msg(Id, Type, WantReply, Data),
1638		     add_request(WantReply, ChannelId, From, D));
1639
1640        _ when WantReply==true ->
1641            {error,closed};
1642
1643        _ ->
1644            D
1645    end.
1646
1647handle_request(ChannelId, Type, Data, WantReply, From, D) ->
1648    case ssh_client_channel:cache_lookup(cache(D), ChannelId) of
1649	#channel{remote_id = Id,
1650                 sent_close = false} ->
1651	    send_msg(ssh_connection:channel_request_msg(Id, Type, WantReply, Data),
1652		     add_request(WantReply, ChannelId, From, D));
1653
1654	_ when WantReply==true ->
1655            {error,closed};
1656
1657        _ ->
1658            D
1659    end.
1660
1661%%%----------------------------------------------------------------
1662update_sys(Cache, Channel, Type, ChannelPid) ->
1663    ssh_client_channel:cache_update(Cache,
1664			     Channel#channel{sys = Type, user = ChannelPid}).
1665
1666add_request(false, _ChannelId, _From, State) ->
1667    State;
1668add_request(true, ChannelId, From, #data{connection_state =
1669					     #connection{requests = Requests0} =
1670					     Connection} = State) ->
1671    Requests = [{ChannelId, From} | Requests0],
1672    State#data{connection_state = Connection#connection{requests = Requests}};
1673add_request(Fun, ChannelId, From, #data{connection_state =
1674                                            #connection{requests = Requests0} =
1675                                            Connection} = State) when is_function(Fun) ->
1676    Requests = [{ChannelId, From, Fun} | Requests0],
1677    State#data{connection_state = Connection#connection{requests = Requests}}.
1678
1679new_channel_id(#data{connection_state = #connection{channel_id_seed = Id} =
1680			 Connection}
1681	       = State) ->
1682    {Id, State#data{connection_state =
1683			Connection#connection{channel_id_seed = Id + 1}}}.
1684
1685
1686%%%----------------------------------------------------------------
1687start_rekeying(Role, D0) ->
1688    {KeyInitMsg, SshPacket, Ssh} = ssh_transport:key_exchange_init_msg(D0#data.ssh_params),
1689    send_bytes(SshPacket, D0),
1690    D = D0#data{ssh_params = Ssh,
1691                key_exchange_init_msg = KeyInitMsg},
1692    {next_state, {kexinit,Role,renegotiate}, D, {change_callback_module,ssh_fsm_kexinit}}.
1693
1694
1695init_renegotiate_timers(_OldState, NewState, D) ->
1696    {RekeyTimeout,_MaxSent} = ?GET_OPT(rekey_limit, (D#data.ssh_params)#ssh.opts),
1697    {next_state, NewState, D, [{{timeout,renegotiate},     RekeyTimeout,       none},
1698                               {{timeout,check_data_size}, ?REKEY_DATA_TIMOUT, none} ]}.
1699
1700
1701pause_renegotiate_timers(_OldState, NewState, D) ->
1702    {next_state, NewState, D, [{{timeout,renegotiate},     infinity, none},
1703                               {{timeout,check_data_size}, infinity, none} ]}.
1704
1705check_data_rekeying(Role, D) ->
1706    case inet:getstat(D#data.socket, [send_oct]) of
1707        {ok, [{send_oct,SocketSentTotal}]} ->
1708            SentSinceRekey = SocketSentTotal - D#data.last_size_rekey,
1709            {_RekeyTimeout,MaxSent} = ?GET_OPT(rekey_limit, (D#data.ssh_params)#ssh.opts),
1710            case check_data_rekeying_dbg(SentSinceRekey, MaxSent) of
1711                true ->
1712                    start_rekeying(Role, D#data{last_size_rekey = SocketSentTotal});
1713                _ ->
1714                    %% Not enough data sent for a re-negotiation. Restart timer.
1715                    {keep_state, D, {{timeout,check_data_size}, ?REKEY_DATA_TIMOUT, none}}
1716            end;
1717        {error,_} ->
1718            %% Socket closed, but before this module has handled that. Maybe
1719            %% it is in the message queue.
1720            %% Just go on like if there was not enough data transmitted to start re-keying:
1721            {keep_state, D, {{timeout,check_data_size}, ?REKEY_DATA_TIMOUT, none}}
1722    end.
1723
1724check_data_rekeying_dbg(SentSinceRekey, MaxSent) ->
1725    %% This function is for the ssh_dbg to trace on. See dbg_trace/3 at the end.
1726    SentSinceRekey >= MaxSent.
1727
1728%%%----------------------------------------------------------------
1729%%% This server/client has decided to disconnect via the state machine:
1730%%% The unused arguments are for debugging.
1731
1732send_disconnect(Code, DetailedText, Module, Line, StateName, D) ->
1733    send_disconnect(Code, default_text(Code), DetailedText, Module, Line, StateName, D).
1734
1735send_disconnect(Code, Reason, DetailedText, Module, Line, StateName, D0) ->
1736    Msg = #ssh_msg_disconnect{code = Code,
1737                              description = Reason},
1738    D = send_msg(Msg, D0),
1739    LogMsg = io_lib:format("Disconnects with code = ~p [RFC4253 11.1]: ~s",[Code,Reason]),
1740    call_disconnectfun_and_log_cond(LogMsg, DetailedText, Module, Line, StateName, D),
1741    {{shutdown,Reason}, D}.
1742
1743call_disconnectfun_and_log_cond(LogMsg, DetailedText, Module, Line, StateName, D) ->
1744    case disconnect_fun(LogMsg, D) of
1745        void ->
1746            log(info, D,
1747                "~s~n"
1748                "State = ~p~n"
1749                "Module = ~p, Line = ~p.~n"
1750                "Details:~n  ~s~n",
1751                [LogMsg, StateName, Module, Line, DetailedText]);
1752        _ ->
1753            ok
1754    end.
1755
1756
1757default_text(?SSH_DISCONNECT_HOST_NOT_ALLOWED_TO_CONNECT) -> "Host not allowed to connect";
1758default_text(?SSH_DISCONNECT_PROTOCOL_ERROR) -> "Protocol error";
1759default_text(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED) -> "Key exchange failed";
1760default_text(?SSH_DISCONNECT_RESERVED) -> "Reserved";
1761default_text(?SSH_DISCONNECT_MAC_ERROR) -> "Mac error";
1762default_text(?SSH_DISCONNECT_COMPRESSION_ERROR) -> "Compression error";
1763default_text(?SSH_DISCONNECT_SERVICE_NOT_AVAILABLE) -> "Service not available";
1764default_text(?SSH_DISCONNECT_PROTOCOL_VERSION_NOT_SUPPORTED) -> "Protocol version not supported";
1765default_text(?SSH_DISCONNECT_HOST_KEY_NOT_VERIFIABLE) -> "Host key not verifiable";
1766default_text(?SSH_DISCONNECT_CONNECTION_LOST) -> "Connection lost";
1767default_text(?SSH_DISCONNECT_BY_APPLICATION) -> "By application";
1768default_text(?SSH_DISCONNECT_TOO_MANY_CONNECTIONS) -> "Too many connections";
1769default_text(?SSH_DISCONNECT_AUTH_CANCELLED_BY_USER) -> "Auth cancelled by user";
1770default_text(?SSH_DISCONNECT_NO_MORE_AUTH_METHODS_AVAILABLE) -> "Unable to connect using the available authentication methods";
1771default_text(?SSH_DISCONNECT_ILLEGAL_USER_NAME) -> "Illegal user name".
1772
1773%%%----------------------------------------------------------------
1774counterpart_versions(NumVsn, StrVsn, #ssh{role = server} = Ssh) ->
1775    Ssh#ssh{c_vsn = NumVsn , c_version = StrVsn};
1776counterpart_versions(NumVsn, StrVsn, #ssh{role = client} = Ssh) ->
1777    Ssh#ssh{s_vsn = NumVsn , s_version = StrVsn}.
1778
1779%%%----------------------------------------------------------------
1780conn_info_keys() ->
1781    [client_version,
1782     server_version,
1783     peer,
1784     user,
1785     sockname,
1786     options,
1787     algorithms,
1788     channels
1789    ].
1790
1791conn_info(client_version, #data{ssh_params=S}) -> {S#ssh.c_vsn, S#ssh.c_version};
1792conn_info(server_version, #data{ssh_params=S}) -> {S#ssh.s_vsn, S#ssh.s_version};
1793conn_info(peer,           #data{ssh_params=S}) -> S#ssh.peer;
1794conn_info(user,                             D) -> D#data.auth_user;
1795conn_info(sockname,       #data{ssh_params=S}) -> S#ssh.local;
1796conn_info(options,        #data{ssh_params=#ssh{opts=Opts}})    -> lists:sort(
1797                                                                     maps:to_list(
1798                                                                       ssh_options:keep_set_options(
1799                                                                         client,
1800                                                                         ssh_options:keep_user_options(client,Opts))));
1801conn_info(algorithms,     #data{ssh_params=#ssh{algorithms=A}}) -> conn_info_alg(A);
1802conn_info(channels, D) -> try conn_info_chans(ets:tab2list(cache(D)))
1803                          catch _:_ -> undefined
1804                          end;
1805%% dbg options ( = not documented):
1806conn_info(socket, D) ->   D#data.socket;
1807conn_info(chan_ids, D) ->
1808    ssh_client_channel:cache_foldl(fun(#channel{local_id=Id}, Acc) ->
1809				    [Id | Acc]
1810			    end, [], cache(D)).
1811
1812conn_info_chans(Chs) ->
1813    Fs = record_info(fields, channel),
1814    [lists:zip(Fs, tl(tuple_to_list(Ch))) || Ch=#channel{} <- Chs].
1815
1816conn_info_alg(AlgTup) ->
1817    [alg|Vs] = tuple_to_list(AlgTup),
1818    Fs = record_info(fields, alg),
1819    [{K,V} || {K,V} <- lists:zip(Fs,Vs),
1820              lists:member(K,[kex,
1821                              hkey,
1822                              encrypt,
1823                              decrypt,
1824                              send_mac,
1825                              recv_mac,
1826                              compress,
1827                              decompress,
1828                              send_ext_info,
1829                              recv_ext_info])].
1830
1831%%%----------------------------------------------------------------
1832chann_info(recv_window, C) ->
1833    {{win_size,    C#channel.recv_window_size},
1834     {packet_size, C#channel.recv_packet_size}};
1835chann_info(send_window, C) ->
1836    {{win_size,    C#channel.send_window_size},
1837     {packet_size, C#channel.send_packet_size}};
1838%% dbg options ( = not documented):
1839chann_info(pid, C) ->
1840    C#channel.user.
1841
1842%%%----------------------------------------------------------------
1843%% Assisting meta function for the *_info functions
1844fold_keys(Keys, Fun, Extra) ->
1845    lists:foldr(fun(Key, Acc) ->
1846			try Fun(Key, Extra) of
1847			    Value -> [{Key,Value}|Acc]
1848			catch
1849			    _:_ -> Acc
1850			end
1851		end, [], Keys).
1852
1853%%%----------------------------------------------------------------
1854log(Tag, D, Format, Args) ->
1855    log(Tag, D, io_lib:format(Format,Args)).
1856
1857log(Tag, D, Reason) ->
1858    case atom_to_list(Tag) of                   % Dialyzer-technical reasons...
1859        "error"   -> do_log(error_msg,   Reason, D);
1860        "warning" -> do_log(warning_msg, Reason, D);
1861        "info"    -> do_log(info_msg,    Reason, D)
1862    end.
1863
1864
1865do_log(F, Reason0, #data{ssh_params = S}) ->
1866    Reason =
1867        try io_lib:format("~s",[Reason0])
1868        of _ -> Reason0
1869        catch
1870            _:_ -> io_lib:format("~p",[Reason0])
1871        end,
1872    case S of
1873        #ssh{role = Role} when Role==server ;
1874                               Role==client ->
1875            {PeerRole,PeerVersion} =
1876                case Role of
1877                    server -> {"Peer client", S#ssh.c_version};
1878                    client -> {"Peer server", S#ssh.s_version}
1879                end,
1880            error_logger:F("Erlang SSH ~p version: ~s ~s.~n"
1881                           "Address: ~s~n"
1882                           "~s version: ~p~n"
1883                           "Peer address: ~s~n"
1884                           "~s~n",
1885                           [Role, ssh_log_version(), crypto_log_info(),
1886                            ssh_lib:format_address_port(S#ssh.local),
1887                            PeerRole, PeerVersion,
1888                            ssh_lib:format_address_port(element(2,S#ssh.peer)),
1889                            Reason]);
1890        _ ->
1891            error_logger:F("Erlang SSH ~s ~s.~n"
1892                           "~s~n",
1893                           [ssh_log_version(), crypto_log_info(),
1894                            Reason])
1895    end.
1896
1897crypto_log_info() ->
1898    try
1899        [{_,_,CI}] = crypto:info_lib(),
1900        case crypto:info_fips() of
1901            enabled ->
1902                <<"(",CI/binary,". FIPS enabled)">>;
1903            not_enabled ->
1904                <<"(",CI/binary,". FIPS available but not enabled)">>;
1905            _ ->
1906                <<"(",CI/binary,")">>
1907        end
1908    catch
1909        _:_ -> ""
1910    end.
1911
1912ssh_log_version() ->
1913    case application:get_key(ssh,vsn) of
1914        {ok,Vsn} -> Vsn;
1915        undefined -> ""
1916    end.
1917
1918%%%----------------------------------------------------------------
1919not_connected_filter({connection_reply, _Data}) -> true;
1920not_connected_filter(_) -> false.
1921
1922%%%----------------------------------------------------------------
1923
1924send_replies({Repls,C = #connection{}}, D) when is_list(Repls) ->
1925    send_replies(Repls, D#data{connection_state=C});
1926send_replies(Repls, State) ->
1927    lists:foldl(fun get_repl/2, {[],State}, Repls).
1928
1929get_repl({connection_reply,Msg}, {CallRepls,S}) ->
1930    if is_record(Msg, ssh_msg_channel_success) ->
1931	    update_inet_buffers(S#data.socket);
1932       true ->
1933	    ok
1934    end,
1935    {CallRepls, send_msg(Msg,S)};
1936get_repl({channel_data,undefined,_Data}, Acc) ->
1937    Acc;
1938get_repl({channel_data,Pid,Data}, Acc) ->
1939    Pid ! {ssh_cm, self(), Data},
1940    Acc;
1941get_repl({channel_request_reply,From,Data}, {CallRepls,S}) ->
1942    {[{reply,From,Data}|CallRepls], S};
1943get_repl({flow_control,Cache,Channel,From,Msg}, {CallRepls,S}) ->
1944    ssh_client_channel:cache_update(Cache, Channel#channel{flow_control = undefined}),
1945    {[{reply,From,Msg}|CallRepls], S};
1946get_repl({flow_control,From,Msg}, {CallRepls,S}) ->
1947    {[{reply,From,Msg}|CallRepls], S};
1948%% get_repl(noreply, Acc) ->
1949%%     Acc;
1950%% get_repl([], Acc) ->
1951%%     Acc;
1952get_repl(X, Acc) ->
1953    exit({get_repl,X,Acc}).
1954
1955%%%----------------------------------------------------------------
1956%%disconnect_fun({disconnect,Msg}, D) -> ?CALL_FUN(disconnectfun,D)(Msg);
1957disconnect_fun(Reason, D)           -> ?CALL_FUN(disconnectfun,D)(Reason).
1958
1959unexpected_fun(UnexpectedMessage, #data{ssh_params = #ssh{peer = {_,Peer} }} = D) ->
1960    ?CALL_FUN(unexpectedfun,D)(UnexpectedMessage, Peer).
1961
1962debug_fun(#ssh_msg_debug{always_display = Display,
1963			 message = DbgMsg,
1964			 language = Lang},
1965	  D) ->
1966    ?CALL_FUN(ssh_msg_debug_fun,D)(self(), Display, DbgMsg, Lang).
1967
1968
1969%%%----------------------------------------------------------------
1970%%% Cache idle timer that closes the connection if there are no
1971%%% channels open for a while.
1972
1973cond_set_idle_timer(D) ->
1974    case ssh_client_channel:cache_info(num_entries, cache(D)) of
1975        0 -> {{timeout,idle_time}, ?GET_OPT(idle_time, (D#data.ssh_params)#ssh.opts), none};
1976        _ -> {{timeout,idle_time}, infinity, none}
1977    end.
1978
1979%%%----------------------------------------------------------------
1980start_channel_request_timer(_,_, infinity) ->
1981    ok;
1982start_channel_request_timer(Channel, From, Time) ->
1983    erlang:send_after(Time, self(), {timeout, {Channel, From}}).
1984
1985%%%----------------------------------------------------------------
1986
1987init_inet_buffers_window(Socket) ->
1988    %% Initialize the inet buffer handling. First try to increase the buffers:
1989    update_inet_buffers(Socket),
1990    %% then get good start values for the window handling:
1991    {ok,SockOpts} = inet:getopts(Socket, [buffer,recbuf]),
1992    WinSz = proplists:get_value(recbuf, SockOpts, ?DEFAULT_WINDOW_SIZE),
1993    PktSz = min(proplists:get_value(buffer, SockOpts, ?DEFAULT_PACKET_SIZE),
1994                ?DEFAULT_PACKET_SIZE),  % Too large packet size might cause deadlock
1995                                        % between sending and receiving
1996    {WinSz, PktSz}.
1997
1998update_inet_buffers(Socket) ->
1999    try
2000        {ok, BufSzs0} = inet:getopts(Socket, [sndbuf,recbuf]),
2001        MinVal = 655360,
2002        [{Tag,MinVal} || {Tag,Val} <- BufSzs0,
2003                         Val < MinVal]
2004    of
2005	[] -> ok;
2006	NewOpts ->
2007            inet:setopts(Socket, NewOpts),
2008            %% Note that buffers might be of different size than we just requested,
2009            %% the OS has the last word.
2010            ok
2011    catch
2012        _:_ -> ok
2013    end.
2014
2015%%%################################################################
2016%%%#
2017%%%# Tracing
2018%%%#
2019
2020ssh_dbg_trace_points() -> [terminate, disconnect, connections, connection_events, renegotiation,
2021                           tcp].
2022
2023ssh_dbg_flags(connections) -> [c | ssh_dbg_flags(terminate)];
2024ssh_dbg_flags(renegotiation) -> [c];
2025ssh_dbg_flags(connection_events) -> [c];
2026ssh_dbg_flags(terminate) -> [c];
2027ssh_dbg_flags(tcp) -> [c];
2028ssh_dbg_flags(disconnect) -> [c].
2029
2030ssh_dbg_on(connections) -> dbg:tp(?MODULE,  init, 1, x),
2031                           ssh_dbg_on(terminate);
2032ssh_dbg_on(connection_events) -> dbg:tp(?MODULE,   handle_event, 4, x);
2033ssh_dbg_on(renegotiation) -> dbg:tpl(?MODULE,   init_renegotiate_timers, 3, x),
2034                             dbg:tpl(?MODULE,   pause_renegotiate_timers, 3, x),
2035                             dbg:tpl(?MODULE,   check_data_rekeying_dbg, 2, x),
2036                             dbg:tpl(?MODULE,   start_rekeying, 2, x),
2037                             dbg:tp(?MODULE,   renegotiate, 1, x);
2038ssh_dbg_on(terminate) -> dbg:tp(?MODULE,  terminate, 3, x);
2039ssh_dbg_on(tcp) -> dbg:tp(?MODULE, handle_event, 4,
2040                          [{[info, {tcp,'_','_'},       '_', '_'], [], []},
2041                           {[info, {tcp_error,'_','_'}, '_', '_'], [], []},
2042                           {[info, {tcp_closed,'_'},    '_', '_'], [], []}
2043                          ]),
2044                   dbg:tp(?MODULE, send_bytes, 2, x),
2045                   dbg:tpl(?MODULE, close_transport, 1, x);
2046
2047ssh_dbg_on(disconnect) -> dbg:tpl(?MODULE,  send_disconnect, 7, x).
2048
2049
2050ssh_dbg_off(disconnect) -> dbg:ctpl(?MODULE, send_disconnect, 7);
2051ssh_dbg_off(terminate) -> dbg:ctpg(?MODULE, terminate, 3);
2052ssh_dbg_off(tcp) -> dbg:ctpg(?MODULE, handle_event, 4), % How to avoid cancelling 'connection_events' ?
2053                    dbg:ctpl(?MODULE, send_bytes, 2),
2054                    dbg:ctpg(?MODULE, close_transport, 1);
2055ssh_dbg_off(renegotiation) -> dbg:ctpl(?MODULE,   init_renegotiate_timers, 3),
2056                              dbg:ctpl(?MODULE,   pause_renegotiate_timers, 3),
2057                              dbg:ctpl(?MODULE,   check_data_rekeying_dbg, 2),
2058                              dbg:ctpl(?MODULE,   start_rekeying, 2),
2059                              dbg:ctpg(?MODULE,   renegotiate, 1);
2060ssh_dbg_off(connection_events) -> dbg:ctpg(?MODULE, handle_event, 4);
2061ssh_dbg_off(connections) -> dbg:ctpg(?MODULE, init, 1),
2062                            ssh_dbg_off(terminate).
2063
2064
2065ssh_dbg_format(connections, {call, {?MODULE,init, [[Role, Sock, Opts]]}}) ->
2066    DefaultOpts = ssh_options:handle_options(Role,[]),
2067    ExcludedKeys = [internal_options, user_options],
2068    NonDefaultOpts =
2069        maps:filter(fun(K,V) ->
2070                            case lists:member(K,ExcludedKeys) of
2071                                true ->
2072                                    false;
2073                                false ->
2074                                    V =/= (catch maps:get(K,DefaultOpts))
2075                            end
2076                    end,
2077                    Opts),
2078    {ok, {IPp,Portp}} = inet:peername(Sock),
2079    {ok, {IPs,Ports}} = inet:sockname(Sock),
2080    [io_lib:format("Starting ~p connection:\n",[Role]),
2081     io_lib:format("Socket = ~p, Peer = ~s, Local = ~s,~n"
2082                   "Non-default options:~n~p",
2083                   [Sock,
2084                    ssh_lib:format_address_port(IPp,Portp),
2085                    ssh_lib:format_address_port(IPs,Ports),
2086                    NonDefaultOpts])
2087    ];
2088ssh_dbg_format(connections, F) ->
2089    ssh_dbg_format(terminate, F);
2090
2091ssh_dbg_format(connection_events, {call, {?MODULE,handle_event, [EventType, EventContent, State, _Data]}}) ->
2092    ["Connection event\n",
2093     io_lib:format("EventType: ~p~nEventContent: ~p~nState: ~p~n", [EventType, EventContent, State])
2094    ];
2095ssh_dbg_format(connection_events, {return_from, {?MODULE,handle_event,4}, Ret}) ->
2096    ["Connection event result\n",
2097     io_lib:format("~p~n", [ssh_dbg:reduce_state(Ret, #data{})])
2098    ];
2099
2100ssh_dbg_format(tcp, {call, {?MODULE,handle_event, [info, {tcp,Sock,TcpData}, State, _Data]}}) ->
2101    ["TCP stream data arrived\n",
2102     io_lib:format("State: ~p~n"
2103                   "Socket: ~p~n"
2104                   "TcpData:~n~s", [State, Sock, ssh_dbg:hex_dump(TcpData, [{max_bytes,48}])])
2105    ];
2106ssh_dbg_format(tcp, {call, {?MODULE,handle_event, [info, {tcp_error,Sock,Msg}, State, _Data]}}) ->
2107    ["TCP stream data ERROR arrived\n",
2108     io_lib:format("State: ~p~n"
2109                   "Socket: ~p~n"
2110                   "ErrorMsg:~p~n", [State, Sock, Msg])
2111    ];
2112ssh_dbg_format(tcp, {call, {?MODULE,handle_event, [info, {tcp_closed,Sock}, State, _Data]}}) ->
2113    ["TCP stream closed\n",
2114     io_lib:format("State: ~p~n"
2115                   "Socket: ~p~n", [State, Sock])
2116    ];
2117ssh_dbg_format(tcp, {return_from, {?MODULE,handle_event,4}, _Ret}) ->
2118    skip;
2119
2120ssh_dbg_format(tcp, {call, {?MODULE, send_bytes, ["",_D]}}) ->
2121    skip;
2122ssh_dbg_format(tcp, {call, {?MODULE, send_bytes, [TcpData, #data{socket=Sock}]}}) ->
2123    ["TCP send stream data\n",
2124     io_lib:format("Socket: ~p~n"
2125                   "TcpData:~n~s", [Sock, ssh_dbg:hex_dump(TcpData, [{max_bytes,48}])])
2126    ];
2127ssh_dbg_format(tcp, {return_from, {?MODULE,send_bytes,2}, _R}) ->
2128    skip;
2129
2130ssh_dbg_format(tcp, {call, {?MODULE, close_transport, [#data{socket=Sock}]}}) ->
2131    ["TCP close stream\n",
2132     io_lib:format("Socket: ~p~n", [Sock])
2133    ];
2134ssh_dbg_format(tcp, {return_from, {?MODULE,close_transport,1}, _R}) ->
2135    skip;
2136
2137ssh_dbg_format(renegotiation, {call, {?MODULE,init_renegotiate_timers,[OldState,NewState,D]}}) ->
2138    ["Renegotiation: start timer (init_renegotiate_timers)\n",
2139     io_lib:format("State: ~p  -->  ~p~n"
2140                   "rekey_limit: ~p ({ms,bytes})~n"
2141                   "check_data_size: ~p (ms)~n",
2142                   [OldState, NewState,
2143                    ?GET_OPT(rekey_limit, (D#data.ssh_params)#ssh.opts),
2144                    ?REKEY_DATA_TIMOUT])
2145    ];
2146ssh_dbg_format(renegotiation, {return_from, {?MODULE,init_renegotiate_timers,3}, _Ret}) ->
2147    skip;
2148
2149ssh_dbg_format(renegotiation, {call, {?MODULE,renegotiate,[ConnectionHandler]}}) ->
2150    ["Renegotiation: renegotiation forced\n",
2151     io_lib:format("~p:renegotiate(~p) called~n",
2152                   [?MODULE,ConnectionHandler])
2153    ];
2154ssh_dbg_format(renegotiation, {return_from, {?MODULE,renegotiate,1}, _Ret}) ->
2155    skip;
2156
2157ssh_dbg_format(renegotiation, {call, {?MODULE,pause_renegotiate_timers,[OldState,NewState,_D]}}) ->
2158    ["Renegotiation: pause timers\n",
2159     io_lib:format("State: ~p  -->  ~p~n",
2160                   [OldState, NewState])
2161    ];
2162ssh_dbg_format(renegotiation, {return_from, {?MODULE,pause_renegotiate_timers,3}, _Ret}) ->
2163    skip;
2164
2165ssh_dbg_format(renegotiation, {call, {?MODULE,start_rekeying,[_Role,_D]}}) ->
2166    ["Renegotiation: start rekeying\n"];
2167ssh_dbg_format(renegotiation, {return_from, {?MODULE,start_rekeying,2}, _Ret}) ->
2168    skip;
2169
2170ssh_dbg_format(renegotiation, {call, {?MODULE,check_data_rekeying_dbg,[SentSinceRekey, MaxSent]}}) ->
2171    ["Renegotiation: check size of data sent\n",
2172     io_lib:format("TotalSentSinceRekey: ~p~nMaxBeforeRekey: ~p~nStartRekey: ~p~n",
2173                   [SentSinceRekey, MaxSent, SentSinceRekey >= MaxSent])
2174    ];
2175ssh_dbg_format(renegotiation, {return_from, {?MODULE,check_data_rekeying_dbg,2}, _Ret}) ->
2176    skip;
2177
2178
2179ssh_dbg_format(terminate, {call, {?MODULE,terminate, [Reason, StateName, D]}}) ->
2180    ExtraInfo =
2181        try
2182            {conn_info(peer,D),
2183             conn_info(user,D),
2184             conn_info(sockname,D)}
2185        of
2186            {{_,{IPp,Portp}}, Usr, {IPs,Ports}} when is_tuple(IPp), is_tuple(IPs),
2187                                                     is_integer(Portp), is_integer(Ports) ->
2188                io_lib:format("Peer=~s:~p, Local=~s:~p, User=~p",
2189                              [inet:ntoa(IPp),Portp,inet:ntoa(IPs),Ports,Usr]);
2190            {Peer,Usr,Sockname} ->
2191                io_lib:format("Peer=~p, Local=~p, User=~p",[Peer,Sockname,Usr])
2192        catch
2193            _:_ ->
2194                ""
2195        end,
2196    if
2197        Reason == normal ;
2198        Reason == shutdown ;
2199        element(1,Reason) == shutdown
2200        ->
2201            ["Connection Terminating:\n",
2202             io_lib:format("Reason: ~p, StateName: ~p~n~s", [Reason, StateName, ExtraInfo])
2203            ];
2204
2205        true ->
2206            ["Connection Terminating:\n",
2207             io_lib:format("Reason: ~p, StateName: ~p~n~s~nStateData = ~p",
2208                           [Reason, StateName, ExtraInfo, clean(D)])
2209            ]
2210    end;
2211ssh_dbg_format(renegotiation, {return_from, {?MODULE,terminate,3}, _Ret}) ->
2212    skip;
2213
2214ssh_dbg_format(disconnect, {call,{?MODULE,send_disconnect,
2215                                     [Code, Reason, DetailedText, Module, Line, StateName, _D]}}) ->
2216    ["Disconnecting:\n",
2217     io_lib:format(" Module = ~p, Line = ~p, StateName = ~p,~n"
2218                   " Code = ~p, Reason = ~p,~n"
2219                   " DetailedText =~n"
2220                   " ~p",
2221                   [Module, Line, StateName, Code, Reason, lists:flatten(DetailedText)])
2222    ];
2223ssh_dbg_format(renegotiation, {return_from, {?MODULE,send_disconnect,7}, _Ret}) ->
2224    skip.
2225
2226