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
23%%----------------------------------------------------------------------
24%% Purpose: Details of connection protocol
25%%----------------------------------------------------------------------
26
27-module(ssh_connection).
28
29-include("ssh.hrl").
30-include("ssh_connect.hrl").
31-include("ssh_transport.hrl").
32
33%% API
34-export([session_channel/2, session_channel/4,
35	 exec/4, shell/2, subsystem/4, send/3, send/4, send/5,
36	 send_eof/2, adjust_window/3, setenv/5, close/2, reply_request/4,
37	 ptty_alloc/3, ptty_alloc/4]).
38
39%% Potential API currently unsupported and not tested
40-export([window_change/4, window_change/6,
41	 signal/3, exit_status/3]).
42
43%% Internal SSH application API
44-export([channel_data/5,
45         handle_msg/4,
46         handle_stop/1,
47
48         open_channel/4,
49
50	 channel_adjust_window_msg/2,
51	 channel_close_msg/1,
52	 channel_open_failure_msg/4,
53	 channel_open_msg/5,
54	 channel_status_msg/1,
55         channel_data_msg/3,
56         channel_eof_msg/1,
57         channel_failure_msg/1,
58         channel_open_confirmation_msg/4,
59         channel_request_msg/4,
60         channel_success_msg/1,
61
62         request_global_msg/3,
63	 request_failure_msg/0,
64	 request_success_msg/1,
65
66         send_environment_vars/3,
67
68	 encode_ip/1
69        ]).
70
71%% For testing only
72-export([encode_pty_opts/1, decode_pty_opts/1]).
73
74-type connection_ref() :: ssh:connection_ref().
75-type channel_id()     :: ssh:channel_id().
76
77-type req_status() :: success | failure .
78-type reason() :: closed | timeout .
79
80-type result() :: req_status() | {error, reason()} .
81
82-type ssh_data_type_code() :: non_neg_integer(). % Only 0 and 1 are used
83
84
85%%% The SSH Connection Protocol
86
87-export_type([event/0,
88              channel_msg/0,
89              want_reply/0,
90              data_ch_msg/0,
91              eof_ch_msg/0,
92              signal_ch_msg/0,
93              exit_signal_ch_msg/0,
94              exit_status_ch_msg/0,
95              closed_ch_msg/0,
96              env_ch_msg/0,
97              pty_ch_msg/0,
98              shell_ch_msg/0,
99              window_change_ch_msg/0,
100              exec_ch_msg/0
101             ]).
102
103-type event() :: {ssh_cm, ssh:connection_ref(), channel_msg()}.
104-type channel_msg() ::  data_ch_msg()
105                      | eof_ch_msg()
106                      | closed_ch_msg()
107                      | pty_ch_msg()
108                      | env_ch_msg()
109                      | shell_ch_msg()
110                      | exec_ch_msg()
111                      | signal_ch_msg()
112                      | window_change_ch_msg()
113                      | exit_status_ch_msg()
114                      | exit_signal_ch_msg()
115                        .
116
117-type want_reply() :: boolean().
118
119-type data_ch_msg() :: {data,
120                        ssh:channel_id(),
121                        ssh_data_type_code(),
122                        Data :: binary()
123                       } .
124-type eof_ch_msg() :: {eof,
125                       ssh:channel_id()
126                      } .
127-type signal_ch_msg() :: {signal,
128                          ssh:channel_id(),
129                          SignalName :: string()
130                         } .
131-type exit_signal_ch_msg() :: {exit_signal, ssh:channel_id(),
132                               ExitSignal :: string(),
133                               ErrorMsg :: string(),
134                               LanguageString :: string()} .
135-type exit_status_ch_msg() :: {exit_status,
136                               ssh:channel_id(),
137                               ExitStatus :: non_neg_integer()
138                              } .
139-type closed_ch_msg() :: {closed,
140                          ssh:channel_id()
141                         } .
142-type env_ch_msg() :: {env,
143                       ssh:channel_id(),
144                       want_reply(),
145                       Var :: string(),
146                       Value :: string()
147                      } .
148-type pty_ch_msg() :: {pty,
149                       ssh:channel_id(),
150                       want_reply(),
151                       {Terminal :: string(),
152                        CharWidth :: non_neg_integer(),
153                        RowHeight :: non_neg_integer(),
154                        PixelWidth :: non_neg_integer(),
155                        PixelHeight :: non_neg_integer(),
156                        TerminalModes :: [term_mode()]
157                       }
158                      } .
159
160-type term_mode() :: {Opcode :: atom() | byte(),
161                      Value :: non_neg_integer()} .
162
163-type shell_ch_msg() :: {shell,
164                         ssh:channel_id(),
165                         want_reply()
166                        } .
167-type window_change_ch_msg() :: {window_change,
168                                 ssh:channel_id(),
169                                 CharWidth :: non_neg_integer(),
170                                 RowHeight :: non_neg_integer(),
171                                 PixelWidth :: non_neg_integer(),
172                                 PixelHeight :: non_neg_integer()
173                                } .
174-type exec_ch_msg() :: {exec,
175                        ssh:channel_id(),
176                        want_reply(),
177                        Command :: string()
178                       } .
179
180%%% This function is soley to convince all
181%%% checks that the type event() exists...
182-export([dummy/1]).
183-spec dummy(event()) -> false.
184dummy(_) -> false.
185
186%%--------------------------------------------------------------------
187%%% API
188%%--------------------------------------------------------------------
189
190%%--------------------------------------------------------------------
191%% Description: Opens a channel for a ssh session. A session is a
192%% remote execution of a program. The program may be a shell, an
193%% application, a system command, or some built-in subsystem.
194%% --------------------------------------------------------------------
195
196-spec session_channel(ConnectionRef, Timeout) -> Result when
197      ConnectionRef :: ssh:connection_ref(),
198      Timeout :: timeout(),
199      Result :: {ok, ssh:channel_id()} | {error, reason()} .
200
201session_channel(ConnectionHandler, Timeout) ->
202    session_channel(ConnectionHandler, undefined, undefined, Timeout).
203
204
205-spec session_channel(ConnectionRef, InitialWindowSize, MaxPacketSize, Timeout) -> Result when
206      ConnectionRef :: ssh:connection_ref(),
207      InitialWindowSize :: pos_integer() | undefined,
208      MaxPacketSize :: pos_integer() | undefined,
209      Timeout :: timeout(),
210      Result :: {ok, ssh:channel_id()} | {error, reason()} .
211
212session_channel(ConnectionHandler, InitialWindowSize, MaxPacketSize, Timeout) ->
213    open_channel(ConnectionHandler, "session", <<>>,
214                 InitialWindowSize,
215                 MaxPacketSize,
216                 Timeout).
217
218%%--------------------------------------------------------------------
219%% Description: Opens a channel for the given type.
220%% --------------------------------------------------------------------
221open_channel(ConnectionHandler, Type, ChanData, Timeout) ->
222    open_channel(ConnectionHandler, Type, ChanData, undefined, undefined, Timeout).
223
224open_channel(ConnectionHandler, Type, ChanData, InitialWindowSize, MaxPacketSize, Timeout) ->
225    case ssh_connection_handler:open_channel(ConnectionHandler, Type, ChanData,
226                                             InitialWindowSize, MaxPacketSize,
227                                             Timeout) of
228        {open, Channel} ->
229	    {ok, Channel};
230	Error ->
231	    Error
232    end.
233
234%%--------------------------------------------------------------------
235%% Description: Will request that the server start the
236%% execution of the given command.
237%%--------------------------------------------------------------------
238-spec exec(ConnectionRef, ChannelId, Command, Timeout) -> result() when
239      ConnectionRef :: ssh:connection_ref(),
240      ChannelId :: ssh:channel_id(),
241      Command :: string(),
242      Timeout :: timeout().
243
244exec(ConnectionHandler, ChannelId, Command, TimeOut) ->
245    ssh_connection_handler:request(ConnectionHandler, self(), ChannelId, "exec",
246				   true, [?string(Command)], TimeOut).
247
248%%--------------------------------------------------------------------
249%% Description: Will request that the user's default shell (typically
250%% defined in /etc/passwd in UNIX systems) be started at the other
251%% end.
252%%--------------------------------------------------------------------
253-spec shell(ConnectionRef, ChannelId) -> Result when
254      ConnectionRef :: ssh:connection_ref(),
255      ChannelId :: ssh:channel_id(),
256      Result :: ok | success | failure | {error, timeout} .
257
258shell(ConnectionHandler, ChannelId) ->
259    ssh_connection_handler:request(ConnectionHandler, self(), ChannelId,
260 				   "shell", false, <<>>, 0).
261%%--------------------------------------------------------------------
262%%
263%% Description: Executes a predefined subsystem.
264%%--------------------------------------------------------------------
265-spec subsystem(ConnectionRef, ChannelId, Subsystem, Timeout) -> result() when
266      ConnectionRef :: ssh:connection_ref(),
267      ChannelId :: ssh:channel_id(),
268      Subsystem  :: string(),
269      Timeout :: timeout().
270
271subsystem(ConnectionHandler, ChannelId, SubSystem, TimeOut) ->
272     ssh_connection_handler:request(ConnectionHandler, self(),
273				    ChannelId, "subsystem",
274				    true, [?string(SubSystem)], TimeOut).
275%%--------------------------------------------------------------------
276%% Description: Sends channel data.
277%%--------------------------------------------------------------------
278-spec send(connection_ref(), channel_id(), iodata()) ->
279		  ok | {error, timeout | closed}.
280
281send(ConnectionHandler, ChannelId, Data) ->
282    send(ConnectionHandler, ChannelId, 0, Data, infinity).
283
284
285-spec send(connection_ref(), channel_id(), iodata(), timeout()) -> ok |  {error, reason()};
286          (connection_ref(), channel_id(), ssh_data_type_code(), iodata()) -> ok |  {error, reason()}.
287
288send(ConnectionHandler, ChannelId, Data, TimeOut) when is_integer(TimeOut) ->
289    send(ConnectionHandler, ChannelId, 0, Data, TimeOut);
290
291send(ConnectionHandler, ChannelId, Data, infinity) ->
292    send(ConnectionHandler, ChannelId, 0, Data, infinity);
293
294send(ConnectionHandler, ChannelId, Type, Data) ->
295    send(ConnectionHandler, ChannelId, Type, Data, infinity).
296
297
298-spec send(connection_ref(), channel_id(), ssh_data_type_code(), iodata(), timeout()) -> ok |  {error, reason()}.
299
300send(ConnectionHandler, ChannelId, Type, Data, TimeOut) ->
301    ssh_connection_handler:send(ConnectionHandler, ChannelId,
302				Type, Data, TimeOut).
303%%--------------------------------------------------------------------
304-spec send_eof(ConnectionRef, ChannelId) -> ok  | {error, closed} when
305      ConnectionRef :: ssh:connection_ref(),
306      ChannelId :: ssh:channel_id().
307%%
308%%
309%% Description: Sends eof on the channel <ChannelId>.
310%%--------------------------------------------------------------------
311send_eof(ConnectionHandler, Channel) ->
312    ssh_connection_handler:send_eof(ConnectionHandler, Channel).
313
314%%--------------------------------------------------------------------
315-spec adjust_window(ConnectionRef, ChannelId, NumOfBytes) -> ok when
316      ConnectionRef :: ssh:connection_ref(),
317      ChannelId :: ssh:channel_id(),
318      NumOfBytes  :: integer().
319%%
320%%
321%% Description: Adjusts the ssh flowcontrol window.
322%%--------------------------------------------------------------------
323adjust_window(ConnectionHandler, Channel, Bytes) ->
324    ssh_connection_handler:adjust_window(ConnectionHandler, Channel, Bytes).
325
326%%--------------------------------------------------------------------
327-spec setenv(ConnectionRef, ChannelId, Var, Value, Timeout) -> success when
328      ConnectionRef :: ssh:connection_ref(),
329      ChannelId :: ssh:channel_id(),
330      Var :: string(),
331      Value :: string(),
332      Timeout :: timeout().
333%%
334%%
335%% Description: Environment variables may be passed to the shell/command to be
336%% started later.
337setenv(ConnectionHandler, ChannelId, Var, Value, TimeOut) ->
338    setenv(ConnectionHandler, ChannelId, true, Var, Value, TimeOut).
339
340setenv(ConnectionHandler, ChannelId, WantReply, Var, Value, TimeOut) ->
341    case ssh_connection_handler:request(ConnectionHandler, ChannelId,
342                                        "env", WantReply,
343                                        [?string(Var), ?string(Value)], TimeOut) of
344        ok when WantReply == false ->
345            success;
346        Reply ->
347            Reply
348    end.
349%%--------------------------------------------------------------------
350-spec close(ConnectionRef, ChannelId) -> ok when
351      ConnectionRef :: ssh:connection_ref(),
352      ChannelId :: ssh:channel_id().
353%%
354%%
355%% Description: Sends a close message on the channel <ChannelId>.
356%%--------------------------------------------------------------------
357close(ConnectionHandler, ChannelId) ->
358    ssh_connection_handler:close(ConnectionHandler, ChannelId).
359
360%%--------------------------------------------------------------------
361-spec reply_request(ConnectionRef, WantReply, Status, ChannelId) -> ok when
362      ConnectionRef :: ssh:connection_ref(),
363      WantReply :: boolean(),
364      Status :: req_status(),
365      ChannelId :: ssh:channel_id().
366%%
367%%
368%% Description: Send status replies to requests that want such replies.
369%%--------------------------------------------------------------------
370reply_request(ConnectionHandler, true, Status, ChannelId) ->
371    ssh_connection_handler:reply_request(ConnectionHandler, Status, ChannelId);
372reply_request(_,false, _, _) ->
373    ok.
374
375%%--------------------------------------------------------------------
376%% Description: Sends a ssh connection protocol pty_req.
377%%--------------------------------------------------------------------
378-spec ptty_alloc(ConnectionRef, ChannelId, Options) -> result() when
379      ConnectionRef :: ssh:connection_ref(),
380      ChannelId :: ssh:channel_id(),
381      Options  :: proplists:proplist().
382
383ptty_alloc(ConnectionHandler, Channel, Options) ->
384    ptty_alloc(ConnectionHandler, Channel, Options, infinity).
385
386
387-spec ptty_alloc(ConnectionRef, ChannelId, Options, Timeout) -> result() when
388      ConnectionRef :: ssh:connection_ref(),
389      ChannelId :: ssh:channel_id(),
390      Options  :: proplists:proplist(),
391      Timeout :: timeout().
392
393ptty_alloc(ConnectionHandler, Channel, Options0, TimeOut) ->
394    TermData = backwards_compatible(Options0, []), % FIXME
395    {Width, PixWidth} = pty_default_dimensions(width, TermData),
396    {Height, PixHeight} = pty_default_dimensions(height, TermData),
397    pty_req(ConnectionHandler, Channel,
398	    proplists:get_value(term, TermData, os:getenv("TERM", ?DEFAULT_TERMINAL)),
399	    proplists:get_value(width, TermData, Width),
400	    proplists:get_value(height, TermData, Height),
401	    proplists:get_value(pixel_widh, TermData, PixWidth),
402	    proplists:get_value(pixel_height, TermData, PixHeight),
403	    proplists:get_value(pty_opts, TermData, []), TimeOut
404	   ).
405
406%%--------------------------------------------------------------------
407%% Not yet officialy supported! The following functions are part of the
408%% initial contributed ssh application. They are untested. Do we want them?
409%% Should they be documented and tested?
410%%--------------------------------------------------------------------
411window_change(ConnectionHandler, Channel, Width, Height) ->
412    window_change(ConnectionHandler, Channel, Width, Height, 0, 0).
413window_change(ConnectionHandler, Channel, Width, Height,
414	      PixWidth, PixHeight) ->
415    ssh_connection_handler:request(ConnectionHandler, Channel,
416				   "window-change", false,
417				   [?uint32(Width), ?uint32(Height),
418				    ?uint32(PixWidth), ?uint32(PixHeight)], 0).
419
420signal(ConnectionHandler, Channel, Sig) ->
421    ssh_connection_handler:request(ConnectionHandler, Channel,
422				   "signal", false, [?string(Sig)], 0).
423
424
425-spec exit_status(ConnectionRef, ChannelId, Status) -> ok when
426      ConnectionRef :: ssh:connection_ref(),
427      ChannelId :: ssh:channel_id(),
428      Status  :: integer().
429exit_status(ConnectionHandler, Channel, Status) ->
430    ssh_connection_handler:request(ConnectionHandler, Channel,
431				   "exit-status", false, [?uint32(Status)], 0).
432
433%%--------------------------------------------------------------------
434%%% Internal, that is, ssh application internal API
435%%--------------------------------------------------------------------
436
437%%%----------------------------------------------------------------
438%%% Send data on a channel/connection as result of for example
439%%% ssh_connection:send (executed in the ssh_connection_state machine)
440%%%
441
442channel_data(ChannelId, DataType, Data0,
443	     #connection{channel_cache = Cache} = Connection,
444	     From) ->
445    case ssh_client_channel:cache_lookup(Cache, ChannelId) of
446	#channel{remote_id = Id, sent_close = false} = Channel0 ->
447            Data = ?to_binary(Data0),
448	    {SendList, Channel} =
449		update_send_window(Channel0#channel{flow_control = From}, DataType,
450				   Data, Connection),
451	    Replies =
452		lists:map(fun({SendDataType, SendData}) ->
453				  {connection_reply,
454				   channel_data_msg(Id,
455						    SendDataType,
456						    SendData)}
457			  end, SendList),
458	    FlowCtrlMsgs = flow_control(Replies, Channel, Cache),
459	    {Replies ++ FlowCtrlMsgs, Connection};
460	_ ->
461	    {[{channel_request_reply,From,{error,closed}}], Connection}
462    end.
463
464%%%----------------------------------------------------------------
465%%% Handle the channel messages on behalf of the ssh_connection_handler
466%%% state machine.
467%%%
468%%% Replies {Reply, UpdatedConnection}
469%%%
470
471handle_msg(#ssh_msg_channel_open_confirmation{recipient_channel = ChannelId,
472					      sender_channel = RemoteId,
473					      initial_window_size = WindowSz,
474					      maximum_packet_size = PacketSz},
475	   #connection{channel_cache = Cache} = Connection0, _, _SSH) ->
476
477    #channel{remote_id = undefined} = Channel =
478	ssh_client_channel:cache_lookup(Cache, ChannelId),
479
480    ssh_client_channel:cache_update(Cache, Channel#channel{
481				     remote_id = RemoteId,
482				     recv_packet_size = max(32768, % rfc4254/5.2
483							    min(PacketSz, Channel#channel.recv_packet_size)
484							   ),
485				     send_window_size = WindowSz,
486				     send_packet_size = PacketSz}),
487    reply_msg(Channel, Connection0, {open, ChannelId});
488
489handle_msg(#ssh_msg_channel_open_failure{recipient_channel = ChannelId,
490					 reason = Reason,
491					 description = Descr,
492					 lang = Lang},
493	   #connection{channel_cache = Cache} = Connection0, _, _SSH) ->
494    Channel = ssh_client_channel:cache_lookup(Cache, ChannelId),
495    ssh_client_channel:cache_delete(Cache, ChannelId),
496    reply_msg(Channel, Connection0, {open_error, Reason, Descr, Lang});
497
498handle_msg(#ssh_msg_channel_success{recipient_channel = ChannelId}, Connection, _, _SSH) ->
499    reply_msg(ChannelId, Connection, success);
500
501handle_msg(#ssh_msg_channel_failure{recipient_channel = ChannelId}, Connection, _, _SSH) ->
502    reply_msg(ChannelId, Connection, failure);
503
504handle_msg(#ssh_msg_channel_eof{recipient_channel = ChannelId}, Connection, _, _SSH) ->
505    reply_msg(ChannelId, Connection, {eof, ChannelId});
506
507handle_msg(#ssh_msg_channel_close{recipient_channel = ChannelId},
508	   #connection{channel_cache = Cache} = Connection0, _, _SSH) ->
509
510	case ssh_client_channel:cache_lookup(Cache, ChannelId) of
511		#channel{sent_close = Closed, remote_id = RemoteId,
512			 flow_control = FlowControl} = Channel ->
513		ssh_client_channel:cache_delete(Cache, ChannelId),
514		{CloseMsg, Connection} =
515		    reply_msg(Channel, Connection0, {closed, ChannelId}),
516		ConnReplyMsgs =
517		    case Closed of
518			true -> [];
519			false ->
520			    RemoteCloseMsg = channel_close_msg(RemoteId),
521			    [{connection_reply, RemoteCloseMsg}]
522		    end,
523
524		%% if there was a send() in progress, make it fail
525		SendReplyMsgs =
526		    case FlowControl of
527			undefined -> [];
528			From ->
529			    [{flow_control, From, {error, closed}}]
530		    end,
531
532		Replies = ConnReplyMsgs ++ CloseMsg ++ SendReplyMsgs,
533		{Replies, Connection};
534
535	    undefined ->
536		{[], Connection0}
537	end;
538
539handle_msg(#ssh_msg_channel_data{recipient_channel = ChannelId,
540				 data = Data},
541	   Connection, _, _SSH) ->
542    channel_data_reply_msg(ChannelId, Connection, 0, Data);
543
544handle_msg(#ssh_msg_channel_extended_data{recipient_channel = ChannelId,
545					  data_type_code = DataType,
546					  data = Data},
547	   Connection, _, _SSH) ->
548    channel_data_reply_msg(ChannelId, Connection, DataType, Data);
549
550handle_msg(#ssh_msg_channel_window_adjust{recipient_channel = ChannelId,
551					  bytes_to_add = Add},
552	   #connection{channel_cache = Cache} = Connection, _, _SSH) ->
553    #channel{send_window_size = Size, remote_id = RemoteId} =
554	Channel0 = ssh_client_channel:cache_lookup(Cache, ChannelId),
555
556    {SendList, Channel} =  %% TODO: Datatype 0 ?
557	update_send_window(Channel0#channel{send_window_size = Size + Add},
558			   0, undefined, Connection),
559
560    Replies = lists:map(fun({Type, Data}) ->
561				{connection_reply, channel_data_msg(RemoteId, Type, Data)}
562			end, SendList),
563    FlowCtrlMsgs = flow_control(Channel, Cache),
564    {Replies ++ FlowCtrlMsgs, Connection};
565
566handle_msg(#ssh_msg_channel_open{channel_type = "session" = Type,
567				 sender_channel = RemoteId,
568				 initial_window_size = WindowSz,
569				 maximum_packet_size = PacketSz},
570	   #connection{options = SSHopts} = Connection0,
571	   server, _SSH) ->
572    MinAcceptedPackSz =
573        ?GET_OPT(minimal_remote_max_packet_size, SSHopts),
574
575    if
576	MinAcceptedPackSz =< PacketSz ->
577	    try setup_session(Connection0, RemoteId,
578			      Type, WindowSz, PacketSz) of
579		Result ->
580		    Result
581	    catch _:_ ->
582		    FailMsg = channel_open_failure_msg(RemoteId,
583						       ?SSH_OPEN_CONNECT_FAILED,
584						       "Connection refused", "en"),
585		    {[{connection_reply, FailMsg}], Connection0}
586	    end;
587
588	MinAcceptedPackSz > PacketSz ->
589	    FailMsg = channel_open_failure_msg(RemoteId,
590					       ?SSH_OPEN_ADMINISTRATIVELY_PROHIBITED,
591					       lists:concat(["Maximum packet size below ",MinAcceptedPackSz,
592							      " not supported"]), "en"),
593	    {[{connection_reply, FailMsg}], Connection0}
594    end;
595
596handle_msg(#ssh_msg_channel_open{channel_type = "forwarded-tcpip",
597				 sender_channel = RemoteId,
598                                 initial_window_size = WindowSize,
599                                 maximum_packet_size = PacketSize,
600                                 data = <<?DEC_BIN(ConnectedHost,_L1), ?UINT32(ConnectedPort),
601                                          ?DEC_BIN(_OriginHost,_L2), ?UINT32(_OriginPort)
602                                        >>
603                                },
604           #connection{channel_cache = Cache,
605                       channel_id_seed = ChId,
606                       suggest_window_size = WinSz,
607                       suggest_packet_size = PktSz,
608                       options = Options,
609                       sub_system_supervisor = SubSysSup
610                      } = C,
611	   client, _SSH) ->
612    {ReplyMsg, NextChId} =
613        case ssh_connection_handler:retrieve(C, {tcpip_forward,ConnectedHost,ConnectedPort}) of
614            {ok, {ConnectToHost,ConnectToPort}} ->
615                case gen_tcp:connect(ConnectToHost, ConnectToPort, [{active,false}, binary]) of
616                    {ok,Sock} ->
617                        {ok,Pid} = ssh_subsystem_sup:start_channel(client, SubSysSup, self(),
618                                                                   ssh_tcpip_forward_client, ChId,
619                                                                   [Sock], undefined, Options),
620                        ssh_client_channel:cache_update(Cache,
621                                                        #channel{type = "forwarded-tcpip",
622                                                                 sys = "none",
623                                                                 local_id = ChId,
624                                                                 remote_id = RemoteId,
625                                                                 user = Pid,
626                                                                 recv_window_size = WinSz,
627                                                                 recv_packet_size = PktSz,
628                                                                 send_window_size = WindowSize,
629                                                                 send_packet_size = PacketSize,
630                                                                 send_buf = queue:new()
631                                                                }),
632                        gen_tcp:controlling_process(Sock, Pid),
633                        inet:setopts(Sock, [{active,once}]),
634                        {channel_open_confirmation_msg(RemoteId, ChId, WinSz, PktSz),
635                         ChId + 1};
636
637                    {error,Error} ->
638                        {channel_open_failure_msg(RemoteId,
639                                                  ?SSH_OPEN_CONNECT_FAILED,
640                                                  io_lib:format("Forwarded connection refused: ~p",[Error]),
641                                                  "en"),
642                         ChId}
643                end;
644
645            undefined ->
646                {channel_open_failure_msg(RemoteId,
647                                          ?SSH_OPEN_CONNECT_FAILED,
648                                          io_lib:format("No forwarding ordered",[]),
649                                          "en"),
650                 ChId}
651        end,
652    {[{connection_reply, ReplyMsg}], C#connection{channel_id_seed = NextChId}};
653
654handle_msg(#ssh_msg_channel_open{channel_type = "direct-tcpip",
655				 sender_channel = RemoteId,
656                                 initial_window_size = WindowSize,
657                                 maximum_packet_size = PacketSize,
658                                 data = <<?DEC_BIN(HostToConnect,_L1),        ?UINT32(PortToConnect),
659                                          ?DEC_BIN(_OriginatorIPaddress,_L2), ?UINT32(_OrignatorPort)
660                                        >>
661                                },
662	   #connection{channel_cache = Cache,
663                       channel_id_seed = ChId,
664                       suggest_window_size = WinSz,
665                       suggest_packet_size = PktSz,
666                       options = Options,
667                       sub_system_supervisor = SubSysSup
668                      } = C,
669	   server, _SSH) ->
670    {ReplyMsg, NextChId} =
671        case ?GET_OPT(tcpip_tunnel_in, Options) of
672            %% May add more to the option, like allowed ip/port pairs to connect to
673            false ->
674                {channel_open_failure_msg(RemoteId,
675                                          ?SSH_OPEN_CONNECT_FAILED,
676                                          "Forwarding disabled", "en"),
677                 ChId};
678
679            true ->
680                case gen_tcp:connect(binary_to_list(HostToConnect), PortToConnect,
681                                     [{active,false}, binary]) of
682                    {ok,Sock} ->
683                        {ok,Pid} = ssh_subsystem_sup:start_channel(server, SubSysSup, self(),
684                                                                   ssh_tcpip_forward_srv, ChId,
685                                                                   [Sock], undefined, Options),
686                        ssh_client_channel:cache_update(Cache,
687                                                        #channel{type = "direct-tcpip",
688                                                                 sys = "none",
689                                                                 local_id = ChId,
690                                                                 remote_id = RemoteId,
691                                                                 user = Pid,
692                                                                 recv_window_size = WinSz,
693                                                                 recv_packet_size = PktSz,
694                                                                 send_window_size = WindowSize,
695                                                                 send_packet_size = PacketSize,
696                                                                 send_buf = queue:new()
697                                                                }),
698                        gen_tcp:controlling_process(Sock, Pid),
699                        inet:setopts(Sock, [{active,once}]),
700
701                        {channel_open_confirmation_msg(RemoteId, ChId, WinSz, PktSz),
702                         ChId + 1};
703
704                    {error,Error} ->
705                        {channel_open_failure_msg(RemoteId,
706                                                  ?SSH_OPEN_CONNECT_FAILED,
707                                                  io_lib:format("Forwarded connection refused: ~p",[Error]),
708                                                  "en"),
709                         ChId}
710                end
711        end,
712    {[{connection_reply, ReplyMsg}], C#connection{channel_id_seed = NextChId}};
713
714handle_msg(#ssh_msg_channel_open{channel_type = "session",
715				 sender_channel = RemoteId},
716	   Connection,
717	   client, _SSH) ->
718    %% Client implementations SHOULD reject any session channel open
719    %% requests to make it more difficult for a corrupt server to attack the
720    %% client. See See RFC 4254 6.1.
721    FailMsg = channel_open_failure_msg(RemoteId,
722				       ?SSH_OPEN_CONNECT_FAILED,
723				       "Connection refused", "en"),
724    {[{connection_reply, FailMsg}], Connection};
725
726handle_msg(#ssh_msg_channel_open{sender_channel = RemoteId}, Connection, _, _SSH) ->
727    FailMsg = channel_open_failure_msg(RemoteId,
728				       ?SSH_OPEN_ADMINISTRATIVELY_PROHIBITED,
729				       "Not allowed", "en"),
730    {[{connection_reply, FailMsg}], Connection};
731
732handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
733				    request_type = "exit-status",
734				    data = Data},
735           Connection, _, _SSH) ->
736    <<?UINT32(Status)>> = Data,
737    reply_msg(ChannelId, Connection, {exit_status, ChannelId, Status});
738
739handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
740				    request_type = "exit-signal",
741				    want_reply = false,
742				    data = Data},
743           #connection{channel_cache = Cache} = Connection0, _, _SSH) ->
744    <<?DEC_BIN(SigName, _SigLen),
745      ?BOOLEAN(_Core),
746      ?DEC_BIN(Err, _ErrLen),
747      ?DEC_BIN(Lang, _LangLen)>> = Data,
748    Channel = ssh_client_channel:cache_lookup(Cache, ChannelId),
749    RemoteId =  Channel#channel.remote_id,
750    {Reply, Connection} =  reply_msg(Channel, Connection0,
751				     {exit_signal, ChannelId,
752				      binary_to_list(SigName),
753				      binary_to_list(Err),
754				      binary_to_list(Lang)}),
755    CloseMsg = channel_close_msg(RemoteId),
756    {[{connection_reply, CloseMsg}|Reply], Connection};
757
758handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
759				    request_type = "xon-xoff",
760				    want_reply = false,
761				    data = Data},
762           Connection, _, _SSH) ->
763    <<?BOOLEAN(CDo)>> = Data,
764    reply_msg(ChannelId, Connection, {xon_xoff, ChannelId, CDo=/= 0});
765
766handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
767				    request_type = "window-change",
768				    want_reply = false,
769				    data = Data},
770           Connection0, _, _SSH) ->
771    <<?UINT32(Width),?UINT32(Height),
772      ?UINT32(PixWidth), ?UINT32(PixHeight)>> = Data,
773    reply_msg(ChannelId, Connection0, {window_change, ChannelId,
774                                       Width, Height,
775                                       PixWidth, PixHeight});
776
777handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
778				    request_type = "signal",
779				    data = Data},
780           Connection0, _, _SSH) ->
781    <<?DEC_BIN(SigName, _SigLen)>> = Data,
782    reply_msg(ChannelId, Connection0, {signal, ChannelId,
783                                       binary_to_list(SigName)});
784
785handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
786				    request_type = "subsystem",
787				    want_reply = WantReply,
788				    data = Data},
789	   #connection{channel_cache = Cache} = Connection, server, _SSH) ->
790    <<?DEC_BIN(SsName,_SsLen)>> = Data,
791    #channel{remote_id=RemoteId} = Channel =
792	ssh_client_channel:cache_lookup(Cache, ChannelId),
793    Reply =
794        case start_subsystem(SsName, Connection, Channel,
795                             {subsystem, ChannelId, WantReply, binary_to_list(SsName)}) of
796            {ok, Pid} ->
797                erlang:monitor(process, Pid),
798                ssh_client_channel:cache_update(Cache, Channel#channel{user=Pid}),
799                channel_success_msg(RemoteId);
800            {error,_Error} ->
801                channel_failure_msg(RemoteId)
802        end,
803    {[{connection_reply,Reply}], Connection};
804
805handle_msg(#ssh_msg_channel_request{request_type = "subsystem"},
806	   Connection, client, _SSH) ->
807    %% The client SHOULD ignore subsystem requests. See RFC 4254 6.5.
808    {[], Connection};
809
810handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
811				    request_type = "pty-req",
812				    want_reply = WantReply,
813				    data = Data},
814	   Connection, server, SSH) ->
815    <<?DEC_BIN(BTermName,_TermLen),
816      ?UINT32(Width),?UINT32(Height),
817      ?UINT32(PixWidth), ?UINT32(PixHeight),
818      Modes/binary>> = Data,
819    TermName = binary_to_list(BTermName),
820    PtyOpts0 = decode_pty_opts(Modes),
821    PtyOpts = case SSH#ssh.c_version of
822                  "SSH-2.0-PuTTY"++_ ->
823                      %% If - peer client is PuTTY
824                      %%    - it asked for pty
825                      %%    - did not tell if LF->CRLF expansion is wanted
826                      %% then
827                      %%    - do LF->CRLF expansion
828                      case  proplists:get_value(onlcr, PtyOpts0, undefined) of
829                          undefined ->
830                              [{onlcr,1} | PtyOpts0];
831                          _ ->
832                              PtyOpts0
833                      end;
834                  _ ->
835                      PtyOpts0
836              end,
837    PtyRequest = {TermName, Width, Height,
838		  PixWidth, PixHeight, PtyOpts},
839    handle_cli_msg(Connection, ChannelId,
840		   {pty, ChannelId, WantReply, PtyRequest});
841
842handle_msg(#ssh_msg_channel_request{request_type = "pty-req"},
843	   Connection, client, _SSH) ->
844    %% The client SHOULD ignore pty requests. See RFC 4254 6.2.
845    {[], Connection};
846
847handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
848				    request_type = "shell",
849				    want_reply = WantReply},
850	   Connection, server, _SSH) ->
851    handle_cli_msg(Connection, ChannelId,
852		   {shell, ChannelId, WantReply});
853
854handle_msg(#ssh_msg_channel_request{request_type = "shell"},
855	   Connection, client, _SSH) ->
856    %% The client SHOULD ignore shell requests. See RFC 4254 6.5.
857    {[], Connection};
858
859handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
860				    request_type = "exec",
861				    want_reply = WantReply,
862				    data = Data},
863	   Connection, server, _SSH) ->
864    <<?DEC_BIN(Command, _Len)>> = Data,
865    handle_cli_msg(Connection, ChannelId,
866		   {exec, ChannelId, WantReply, binary_to_list(Command)});
867
868handle_msg(#ssh_msg_channel_request{request_type = "exec"},
869	   Connection, client, _SSH) ->
870    %% The client SHOULD ignore exec requests. See RFC 4254 6.5.
871    {[], Connection};
872
873handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
874  				    request_type = "env",
875  				    want_reply = WantReply,
876  				    data = Data},
877	   Connection, server, _SSH) ->
878    <<?DEC_BIN(Var,_VarLen), ?DEC_BIN(Value,_ValLen)>> = Data,
879    handle_cli_msg(Connection, ChannelId,
880 		   {env, ChannelId, WantReply, Var, Value});
881
882handle_msg(#ssh_msg_channel_request{request_type = "env"},
883	   Connection, client, _SSH) ->
884    %% The client SHOULD ignore env requests.
885    {[], Connection};
886
887handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
888                                    want_reply = WantReply},
889	   #connection{channel_cache = Cache} = Connection, _, _SSH) ->
890    %% Not a valid request_type. All valid types are handling the
891    %% parameter checking in their own clauses above.
892    %%
893    %% The special ReqType faulty_msg signals that something went
894    %% wrong found during decoding.
895    %%
896    %% RFC4254 5.4 says:
897    %% "If 'want reply' is FALSE, no response will be sent to the request.
898    %%  Otherwise, the recipient responds with either
899    %%  SSH_MSG_CHANNEL_SUCCESS, SSH_MSG_CHANNEL_FAILURE, or request-specific
900    %%  continuation messages.  If the request is not recognized or is not
901    %%  supported for the channel, SSH_MSG_CHANNEL_FAILURE is returned."
902    %%
903    case ssh_client_channel:cache_lookup(Cache, ChannelId) of
904        #channel{remote_id = RemoteId} when WantReply==true ->
905            FailMsg = channel_failure_msg(RemoteId),
906            {[{connection_reply, FailMsg}], Connection};
907        _ -> %% Channel has been closed or no reply is wanted
908            {[], Connection}
909    end;
910
911handle_msg(#ssh_msg_global_request{name = <<"tcpip-forward">>,
912				   want_reply = WantReply,
913				   data = <<?DEC_BIN(ListenAddrStr,_Len),?UINT32(ListenPort)>>},
914           #connection{options = Opts} = Connection, server, _SSH) ->
915    case ?GET_OPT(tcpip_tunnel_out, Opts) of
916        false ->
917            %% This daemon instance has not enabled tcpip_forwarding
918            {[{connection_reply, request_failure_msg()}], Connection};
919
920        true ->
921            SubSysSup = ?GET_INTERNAL_OPT(subsystem_sup, Opts),
922            FwdSup = ssh_subsystem_sup:tcpip_fwd_supervisor(SubSysSup),
923            ConnPid = self(),
924            case ssh_tcpip_forward_acceptor:supervised_start(FwdSup,
925                                                             {ListenAddrStr, ListenPort},
926                                                             undefined,
927                                                             "forwarded-tcpip", ssh_tcpip_forward_srv,
928                                                             ConnPid) of
929                {ok,ListenPort} when WantReply==true ->
930                    {[{connection_reply, request_success_msg(<<>>)}], Connection};
931
932                {ok,LPort} when WantReply==true ->
933                    {[{connection_reply, request_success_msg(<<?UINT32(LPort)>>)}], Connection};
934
935                {error,_} when WantReply==true ->
936                    {[{connection_reply, request_failure_msg()}], Connection};
937
938                _ when WantReply==true ->
939                    {[{connection_reply, request_failure_msg()}], Connection};
940
941                _ ->
942                    {[], Connection}
943            end
944    end;
945
946handle_msg(#ssh_msg_global_request{name = _Type,
947				   want_reply = WantReply,
948				   data = _Data}, Connection, _Role, _SSH) ->
949    if WantReply == true ->
950	    FailMsg = request_failure_msg(),
951	    {[{connection_reply, FailMsg}], Connection};
952       true ->
953	    {[], Connection}
954    end;
955
956handle_msg(#ssh_msg_request_failure{},
957	   #connection{requests = [{_, From} | Rest]} = Connection, _, _SSH) ->
958    {[{channel_request_reply, From, {failure, <<>>}}],
959     Connection#connection{requests = Rest}};
960
961handle_msg(#ssh_msg_request_failure{},
962	   #connection{requests = [{_, From,_} | Rest]} = Connection, _, _SSH) ->
963    {[{channel_request_reply, From, {failure, <<>>}}],
964     Connection#connection{requests = Rest}};
965
966handle_msg(#ssh_msg_request_success{data = Data},
967	   #connection{requests = [{_, From} | Rest]} = Connection, _, _SSH) ->
968    {[{channel_request_reply, From, {success, Data}}],
969     Connection#connection{requests = Rest}};
970
971handle_msg(#ssh_msg_request_success{data = Data},
972	   #connection{requests = [{_, From, Fun} | Rest]} = Connection0, _, _SSH) ->
973    Connection = Fun({success,Data}, Connection0),
974    {[{channel_request_reply, From, {success, Data}}],
975     Connection#connection{requests = Rest}};
976
977handle_msg(#ssh_msg_disconnect{code = Code,
978			       description = Description},
979	   Connection, _, _SSH) ->
980    {disconnect, {Code, Description}, handle_stop(Connection)}.
981
982
983%%%----------------------------------------------------------------
984%%% Returns pending responses to be delivered to the peer when a
985%%% Channel/Connection closes
986%%%
987handle_stop(#connection{channel_cache = Cache} = Connection0) ->
988    {Connection, Replies} =
989	ssh_client_channel:cache_foldl(
990          fun(Channel, {Connection1, Acc}) ->
991                  {Reply, Connection2} =
992                      reply_msg(Channel, Connection1,
993                                {closed, Channel#channel.local_id}),
994                  {Connection2, Reply ++ Acc}
995          end, {Connection0, []}, Cache),
996    ssh_client_channel:cache_delete(Cache),
997    {Replies, Connection}.
998
999%%%----------------------------------------------------------------
1000%%% channel_*_msg(...)
1001%%% Returns a #ssh_msg_....{} for channel operations.
1002%%%
1003channel_adjust_window_msg(ChannelId, Bytes) ->
1004    #ssh_msg_channel_window_adjust{recipient_channel = ChannelId,
1005				   bytes_to_add = Bytes}.
1006
1007channel_close_msg(ChannelId) ->
1008    #ssh_msg_channel_close {recipient_channel = ChannelId}.
1009
1010channel_data_msg(ChannelId, 0, Data) ->
1011    #ssh_msg_channel_data{recipient_channel = ChannelId,
1012			  data = Data};
1013channel_data_msg(ChannelId, Type, Data) ->
1014    #ssh_msg_channel_extended_data{recipient_channel = ChannelId,
1015				    data_type_code = Type,
1016				    data = Data}.
1017
1018channel_eof_msg(ChannelId) ->
1019    #ssh_msg_channel_eof{recipient_channel = ChannelId}.
1020
1021channel_failure_msg(ChannelId) ->
1022    #ssh_msg_channel_failure{recipient_channel = ChannelId}.
1023
1024channel_open_msg(Type, ChannelId, WindowSize, MaxPacketSize, Data) ->
1025    #ssh_msg_channel_open{channel_type = Type,
1026			  sender_channel = ChannelId,
1027			  initial_window_size = WindowSize,
1028			  maximum_packet_size = MaxPacketSize,
1029			  data = Data
1030			 }.
1031
1032channel_open_confirmation_msg(RemoteId, LID, WindowSize, PacketSize) ->
1033    #ssh_msg_channel_open_confirmation{recipient_channel = RemoteId,
1034				       sender_channel = LID,
1035				       initial_window_size = WindowSize,
1036				       maximum_packet_size = PacketSize}.
1037
1038channel_open_failure_msg(RemoteId, Reason, Description, Lang) ->
1039    #ssh_msg_channel_open_failure{recipient_channel = RemoteId,
1040				  reason = Reason,
1041				  description = Description,
1042				  lang = Lang}.
1043
1044channel_status_msg({success, ChannelId}) ->
1045    channel_success_msg(ChannelId);
1046
1047channel_status_msg({failure, ChannelId}) ->
1048    channel_failure_msg(ChannelId).
1049
1050channel_request_msg(ChannelId, Type, WantReply, Data) ->
1051    #ssh_msg_channel_request{recipient_channel = ChannelId,
1052			     request_type = Type,
1053			     want_reply = WantReply,
1054			     data = Data}.
1055
1056channel_success_msg(ChannelId) ->
1057    #ssh_msg_channel_success{recipient_channel = ChannelId}.
1058
1059%%%----------------------------------------------------------------
1060%%% request_*_msg(...)
1061%%% Returns a #ssh_msg_....{}
1062%%%
1063request_global_msg(Name, WantReply, Data) ->
1064    #ssh_msg_global_request{name = Name,
1065                            want_reply = WantReply,
1066                            data = Data}.
1067
1068request_failure_msg() ->
1069    #ssh_msg_request_failure{}.
1070
1071request_success_msg(Data) ->
1072    #ssh_msg_request_success{data = Data}.
1073
1074%%%----------------------------------------------------------------
1075%%%
1076%%%
1077encode_ip(Addr) when is_tuple(Addr) ->
1078    case catch inet_parse:ntoa(Addr) of
1079	{'EXIT',_} -> false;
1080	A -> A
1081    end;
1082encode_ip(Addr) when is_list(Addr) ->
1083    case inet_parse:address(Addr) of
1084	{ok, _} -> Addr;
1085	Error ->
1086	    case inet:getaddr(Addr, inet) of
1087		{ok, A} ->
1088		    inet_parse:ntoa(A);
1089		Error -> false
1090	    end
1091    end.
1092
1093%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1094%%%
1095%%% Internal functions
1096%%%
1097%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1098
1099%%%----------------------------------------------------------------
1100%%% Create the channel data when an ssh_msg_open_channel message
1101%%% of "session" typ is handled
1102%%%
1103setup_session(#connection{channel_cache = Cache,
1104                          channel_id_seed = NewChannelID,
1105                          suggest_window_size = WinSz,
1106                          suggest_packet_size = PktSz
1107			 } = C,
1108	      RemoteId, Type, WindowSize, PacketSize) when is_integer(WinSz),
1109                                                           is_integer(PktSz) ->
1110    NextChannelID = NewChannelID + 1,
1111    Channel =
1112        #channel{type = Type,
1113                 sys = "ssh",
1114                 local_id = NewChannelID,
1115                 recv_window_size = WinSz,
1116                 recv_packet_size = PktSz,
1117                 send_window_size = WindowSize,
1118                 send_packet_size = PacketSize,
1119                 send_buf = queue:new(),
1120                 remote_id = RemoteId
1121                },
1122    ssh_client_channel:cache_update(Cache, Channel),
1123    OpenConfMsg = channel_open_confirmation_msg(RemoteId, NewChannelID,
1124						WinSz,
1125						PktSz),
1126                Reply = {connection_reply, OpenConfMsg},
1127    {[Reply], C#connection{channel_id_seed = NextChannelID}}.
1128
1129
1130%%%----------------------------------------------------------------
1131%%% Start a cli or subsystem
1132%%%
1133start_cli(#connection{options = Options,
1134		      cli_spec = CliSpec,
1135		      exec = Exec,
1136		      sub_system_supervisor = SubSysSup}, ChannelId) ->
1137    case CliSpec of
1138        no_cli ->
1139            {error, cli_disabled};
1140        {CbModule, Args} ->
1141            ssh_subsystem_sup:start_channel(server, SubSysSup, self(), CbModule, ChannelId, Args, Exec, Options)
1142    end.
1143
1144
1145start_subsystem(BinName, #connection{options = Options,
1146                                     sub_system_supervisor = SubSysSup},
1147	       #channel{local_id = ChannelId}, _ReplyMsg) ->
1148    Name = binary_to_list(BinName),
1149    case check_subsystem(Name, Options) of
1150	{Callback, Opts} when is_atom(Callback), Callback =/= none ->
1151            ssh_subsystem_sup:start_channel(server, SubSysSup, self(), Callback, ChannelId, Opts, undefined, Options);
1152        {none, _} ->
1153            {error, bad_subsystem};
1154	{_, _} ->
1155	    {error, legacy_option_not_supported}
1156    end.
1157
1158
1159%%% Helpers for starting cli/subsystems
1160check_subsystem("sftp"= SsName, Options) ->
1161    case ?GET_OPT(subsystems, Options) of
1162	no_subsys -> 	% FIXME: Can 'no_subsys' ever be matched?
1163	    {SsName, {Cb, Opts}} = ssh_sftpd:subsystem_spec([]),
1164	    {Cb, Opts};
1165	SubSystems ->
1166	    proplists:get_value(SsName, SubSystems, {none, []})
1167    end;
1168
1169check_subsystem(SsName, Options) ->
1170    Subsystems = ?GET_OPT(subsystems, Options),
1171    case proplists:get_value(SsName, Subsystems, {none, []}) of
1172	Fun when is_function(Fun) ->
1173	    {Fun, []};
1174	{_, _} = Value ->
1175	    Value
1176    end.
1177
1178%%%----------------------------------------------------------------
1179%%%
1180%%% Send-window handling
1181%%%
1182
1183update_send_window(Channel, _, undefined,
1184		   #connection{channel_cache = Cache}) ->
1185    do_update_send_window(Channel, Cache);
1186
1187update_send_window(#channel{send_buf = SendBuffer} = Channel, DataType, Data,
1188		   #connection{channel_cache = Cache}) ->
1189    do_update_send_window(Channel#channel{send_buf = queue:in({DataType, Data}, SendBuffer)},
1190			  Cache).
1191
1192do_update_send_window(Channel0, Cache) ->
1193    {SendMsgs, Channel} = get_window(Channel0, []),
1194    ssh_client_channel:cache_update(Cache, Channel),
1195    {SendMsgs, Channel}.
1196
1197get_window(#channel{send_window_size = 0
1198		   } = Channel, Acc) ->
1199    {lists:reverse(Acc), Channel};
1200get_window(#channel{send_packet_size = 0
1201		   } = Channel, Acc) ->
1202    {lists:reverse(Acc), Channel};
1203get_window(#channel{send_buf = Buffer,
1204		    send_packet_size = PacketSize,
1205		    send_window_size = WindowSize0
1206		   } = Channel, Acc0) ->
1207    case queue:out(Buffer) of
1208	{{value, {_, Data} = Msg}, NewBuffer} ->
1209	    case handle_send_window(Msg, size(Data), PacketSize, WindowSize0, Acc0) of
1210		{WindowSize, Acc, {_, <<>>}} ->
1211		    {lists:reverse(Acc), Channel#channel{send_window_size = WindowSize,
1212							 send_buf = NewBuffer}};
1213		{WindowSize, Acc, Rest} ->
1214		    get_window(Channel#channel{send_window_size = WindowSize,
1215					       send_buf = queue:in_r(Rest, NewBuffer)}, Acc)
1216	    end;
1217	{empty, NewBuffer} ->
1218	    {[], Channel#channel{send_buf = NewBuffer}}
1219    end.
1220
1221handle_send_window(Msg = {Type, Data}, Size, PacketSize, WindowSize, Acc) when Size =< WindowSize ->
1222    case Size =< PacketSize of
1223	true ->
1224	    {WindowSize - Size, [Msg | Acc], {Type, <<>>}};
1225	false ->
1226	    <<Msg1:PacketSize/binary, Msg2/binary>> = Data,
1227	    {WindowSize - PacketSize, [{Type, Msg1} | Acc], {Type, Msg2}}
1228    end;
1229handle_send_window({Type, Data}, _, PacketSize, WindowSize, Acc) when WindowSize =< PacketSize ->
1230    <<Msg1:WindowSize/binary, Msg2/binary>> = Data,
1231    {WindowSize - WindowSize, [{Type, Msg1} | Acc], {Type, Msg2}};
1232handle_send_window({Type, Data}, _, PacketSize, WindowSize, Acc) ->
1233    <<Msg1:PacketSize/binary, Msg2/binary>> = Data,
1234    {WindowSize - PacketSize, [{Type, Msg1} | Acc], {Type, Msg2}}.
1235
1236%%%----------------------------------------------------------------
1237%%%
1238%%% Flow control
1239%%%
1240
1241flow_control(Channel, Cache) ->
1242    flow_control([window_adjusted], Channel, Cache).
1243
1244flow_control([], Channel, Cache) ->
1245    ssh_client_channel:cache_update(Cache, Channel),
1246    [];
1247flow_control([_|_], #channel{flow_control = From,
1248			     send_buf = Buffer} = Channel, Cache) when From =/= undefined ->
1249    case queue:is_empty(Buffer) of
1250	true ->
1251	    ssh_client_channel:cache_update(Cache, Channel#channel{flow_control = undefined}),
1252	    [{flow_control, Cache, Channel, From, ok}];
1253	false ->
1254	    []
1255    end;
1256flow_control(_,_,_) ->
1257    [].
1258
1259%%%----------------------------------------------------------------
1260%%%
1261%%% Pseudo terminal stuff
1262%%%
1263
1264pty_req(ConnectionHandler, Channel, Term, Width, Height,
1265	 PixWidth, PixHeight, PtyOpts, TimeOut) ->
1266    ssh_connection_handler:request(ConnectionHandler,
1267				   Channel, "pty-req", true,
1268				   [?string(Term),
1269				    ?uint32(Width), ?uint32(Height),
1270				    ?uint32(PixWidth),?uint32(PixHeight),
1271				    encode_pty_opts(PtyOpts)], TimeOut).
1272
1273pty_default_dimensions(Dimension, TermData) ->
1274    case proplists:get_value(Dimension, TermData, 0) of
1275	N when is_integer(N), N > 0 ->
1276	    {N, 0};
1277	_ ->
1278            PixelDim = list_to_atom("pixel_" ++ atom_to_list(Dimension)),
1279	    case proplists:get_value(PixelDim, TermData, 0) of
1280		N when is_integer(N), N > 0 ->
1281		    {0, N};
1282		_ ->
1283		    {?TERMINAL_WIDTH, 0}
1284	    end
1285    end.
1286
1287encode_pty_opts(Opts) ->
1288    Bin = list_to_binary(encode_pty_opts2(Opts)),
1289    <<?STRING(Bin)>>.
1290
1291encode_pty_opts2([]) ->
1292    [?TTY_OP_END];
1293encode_pty_opts2([{vintr,Value} | Opts]) ->
1294    [?VINTR, ?uint32(Value) | encode_pty_opts2(Opts)];
1295encode_pty_opts2([{vquit,Value} | Opts]) ->
1296    [?VQUIT, ?uint32(Value) | encode_pty_opts2(Opts)];
1297encode_pty_opts2([{verase,Value} | Opts]) ->
1298    [?VERASE, ?uint32(Value) | encode_pty_opts2(Opts)];
1299encode_pty_opts2([{vkill,Value} | Opts]) ->
1300    [?VKILL, ?uint32(Value) | encode_pty_opts2(Opts)];
1301encode_pty_opts2([{veof,Value} | Opts]) ->
1302    [?VEOF, ?uint32(Value) | encode_pty_opts2(Opts)];
1303encode_pty_opts2([{veol,Value} | Opts]) ->
1304    [?VEOL, ?uint32(Value) | encode_pty_opts2(Opts)];
1305encode_pty_opts2([{veol2,Value} | Opts]) ->
1306    [?VEOL2, ?uint32(Value) | encode_pty_opts2(Opts)];
1307encode_pty_opts2([{vstart,Value} | Opts]) ->
1308    [?VSTART, ?uint32(Value) | encode_pty_opts2(Opts)];
1309encode_pty_opts2([{vstop,Value} | Opts]) ->
1310    [?VSTOP, ?uint32(Value) | encode_pty_opts2(Opts)];
1311encode_pty_opts2([{vsusp,Value} | Opts]) ->
1312    [?VSUSP, ?uint32(Value) | encode_pty_opts2(Opts)];
1313encode_pty_opts2([{vdsusp,Value} | Opts]) ->
1314    [?VDSUSP, ?uint32(Value) | encode_pty_opts2(Opts)];
1315encode_pty_opts2([{vreprint,Value} | Opts]) ->
1316    [?VREPRINT, ?uint32(Value) | encode_pty_opts2(Opts)];
1317encode_pty_opts2([{vwerase,Value} | Opts]) ->
1318    [ ?VWERASE, ?uint32(Value) | encode_pty_opts2(Opts)];
1319encode_pty_opts2([{vlnext,Value} | Opts]) ->
1320    [?VLNEXT, ?uint32(Value) | encode_pty_opts2(Opts)];
1321encode_pty_opts2([{vflush,Value} | Opts]) ->
1322    [?VFLUSH, ?uint32(Value) | encode_pty_opts2(Opts)];
1323encode_pty_opts2([{vswtch,Value} | Opts]) ->
1324    [?VSWTCH, ?uint32(Value) | encode_pty_opts2(Opts)];
1325encode_pty_opts2([{vstatus,Value} | Opts]) ->
1326    [?VSTATUS, ?uint32(Value) | encode_pty_opts2(Opts)];
1327encode_pty_opts2([{vdiscard,Value} | Opts]) ->
1328    [?VDISCARD, ?uint32(Value) | encode_pty_opts2(Opts)];
1329encode_pty_opts2([{ignpar,Value} | Opts]) ->
1330    [?IGNPAR, ?uint32(Value) | encode_pty_opts2(Opts)];
1331encode_pty_opts2([{parmrk,Value} | Opts]) ->
1332    [?PARMRK, ?uint32(Value) | encode_pty_opts2(Opts)];
1333encode_pty_opts2([{inpck,Value} | Opts]) ->
1334    [?INPCK, ?uint32(Value) | encode_pty_opts2(Opts)];
1335encode_pty_opts2([{istrip,Value} | Opts]) ->
1336    [?ISTRIP, ?uint32(Value) | encode_pty_opts2(Opts)];
1337encode_pty_opts2([{inlcr,Value} | Opts]) ->
1338    [?INLCR, ?uint32(Value) | encode_pty_opts2(Opts)];
1339encode_pty_opts2([{igncr,Value} | Opts]) ->
1340    [?IGNCR, ?uint32(Value) | encode_pty_opts2(Opts)];
1341encode_pty_opts2([{icrnl,Value} | Opts]) ->
1342    [?ICRNL, ?uint32(Value) | encode_pty_opts2(Opts)];
1343encode_pty_opts2([{iuclc,Value} | Opts]) ->
1344    [?IUCLC, ?uint32(Value) | encode_pty_opts2(Opts)];
1345encode_pty_opts2([{ixon,Value} | Opts]) ->
1346    [?IXON, ?uint32(Value) | encode_pty_opts2(Opts)];
1347encode_pty_opts2([{ixany,Value} | Opts]) ->
1348    [?IXANY, ?uint32(Value) | encode_pty_opts2(Opts)];
1349encode_pty_opts2([{ixoff,Value} | Opts]) ->
1350    [?IXOFF, ?uint32(Value) | encode_pty_opts2(Opts)];
1351encode_pty_opts2([{imaxbel,Value} | Opts]) ->
1352    [?IMAXBEL, ?uint32(Value) | encode_pty_opts2(Opts)];
1353encode_pty_opts2([{iutf8,Value} | Opts]) ->
1354    [?IUTF8, ?uint32(Value) | encode_pty_opts2(Opts)];
1355encode_pty_opts2([{isig,Value} | Opts]) ->
1356    [?ISIG, ?uint32(Value) | encode_pty_opts2(Opts)];
1357encode_pty_opts2([{icanon,Value} | Opts]) ->
1358    [?ICANON, ?uint32(Value) | encode_pty_opts2(Opts)];
1359encode_pty_opts2([{xcase,Value} | Opts]) ->
1360    [?XCASE, ?uint32(Value) | encode_pty_opts2(Opts)];
1361encode_pty_opts2([{echo,Value} | Opts]) ->
1362    [?ECHO, ?uint32(Value) | encode_pty_opts2(Opts)];
1363encode_pty_opts2([{echoe,Value} | Opts]) ->
1364    [?ECHOE, ?uint32(Value) | encode_pty_opts2(Opts)];
1365encode_pty_opts2([{echok,Value} | Opts]) ->
1366    [?ECHOK, ?uint32(Value) | encode_pty_opts2(Opts)];
1367encode_pty_opts2([{echonl,Value} | Opts]) ->
1368    [?ECHONL, ?uint32(Value) | encode_pty_opts2(Opts)];
1369encode_pty_opts2([{noflsh,Value} | Opts]) ->
1370    [?NOFLSH, ?uint32(Value) | encode_pty_opts2(Opts)];
1371encode_pty_opts2([{tostop,Value} | Opts]) ->
1372    [?TOSTOP, ?uint32(Value) | encode_pty_opts2(Opts)];
1373encode_pty_opts2([{iexten,Value} | Opts]) ->
1374    [?IEXTEN, ?uint32(Value) | encode_pty_opts2(Opts)];
1375encode_pty_opts2([{echoctl,Value} | Opts]) ->
1376    [?ECHOCTL, ?uint32(Value) | encode_pty_opts2(Opts)];
1377encode_pty_opts2([{echoke,Value} | Opts]) ->
1378    [?ECHOKE, ?uint32(Value) | encode_pty_opts2(Opts)];
1379encode_pty_opts2([{pendin,Value} | Opts]) ->
1380    [?PENDIN, ?uint32(Value) | encode_pty_opts2(Opts)];
1381encode_pty_opts2([{opost,Value} | Opts]) ->
1382    [?OPOST, ?uint32(Value) | encode_pty_opts2(Opts)];
1383encode_pty_opts2([{olcuc,Value} | Opts]) ->
1384    [?OLCUC, ?uint32(Value) | encode_pty_opts2(Opts)];
1385encode_pty_opts2([{onlcr,Value} | Opts]) ->
1386    [?ONLCR, ?uint32(Value) | encode_pty_opts2(Opts)];
1387encode_pty_opts2([{ocrnl,Value} | Opts]) ->
1388    [?OCRNL, ?uint32(Value) | encode_pty_opts2(Opts)];
1389encode_pty_opts2([{onocr,Value} | Opts]) ->
1390    [?ONOCR, ?uint32(Value) | encode_pty_opts2(Opts)];
1391encode_pty_opts2([{onlret,Value} | Opts]) ->
1392    [?ONLRET, ?uint32(Value) | encode_pty_opts2(Opts)];
1393encode_pty_opts2([{cs7,Value} | Opts]) ->
1394    [?CS7, ?uint32(Value) | encode_pty_opts2(Opts)];
1395encode_pty_opts2([{cs8,Value} | Opts]) ->
1396    [?CS8, ?uint32(Value) | encode_pty_opts2(Opts)];
1397encode_pty_opts2([{parenb,Value} | Opts]) ->
1398    [?PARENB, ?uint32(Value) | encode_pty_opts2(Opts)];
1399encode_pty_opts2([{parodd,Value} | Opts]) ->
1400    [?PARODD, ?uint32(Value) | encode_pty_opts2(Opts)];
1401encode_pty_opts2([{tty_op_ispeed,Value} | Opts]) ->
1402    [?TTY_OP_ISPEED, ?uint32(Value) | encode_pty_opts2(Opts)];
1403encode_pty_opts2([{tty_op_ospeed,Value} | Opts]) ->
1404    [?TTY_OP_OSPEED, ?uint32(Value) | encode_pty_opts2(Opts)].
1405
1406decode_pty_opts(<<>>) ->
1407    [];
1408decode_pty_opts(<<0, 0, 0, 0>>) ->
1409    [];
1410decode_pty_opts(<<?DEC_BIN(Modes,_Len)>>) ->
1411    decode_pty_opts2(Modes);
1412decode_pty_opts(Binary) ->
1413    decode_pty_opts2(Binary).
1414
1415decode_pty_opts2(<<?TTY_OP_END>>) ->
1416    [];
1417decode_pty_opts2(<<Code, ?UINT32(Value), Tail/binary>>) ->
1418    Op = case Code of
1419	     ?VINTR -> vintr;
1420	     ?VQUIT -> vquit;
1421	     ?VERASE -> verase;
1422	     ?VKILL -> vkill;
1423	     ?VEOF -> veof;
1424	     ?VEOL -> veol;
1425	     ?VEOL2 -> veol2;
1426	     ?VSTART -> vstart;
1427	     ?VSTOP -> vstop;
1428	     ?VSUSP -> vsusp;
1429	     ?VDSUSP -> vdsusp;
1430	     ?VREPRINT -> vreprint;
1431	     ?VWERASE -> vwerase;
1432	     ?VLNEXT -> vlnext;
1433	     ?VFLUSH -> vflush;
1434	     ?VSWTCH -> vswtch;
1435	     ?VSTATUS -> vstatus;
1436	     ?VDISCARD -> vdiscard;
1437	     ?IGNPAR -> ignpar;
1438	     ?PARMRK -> parmrk;
1439	     ?INPCK -> inpck;
1440	     ?ISTRIP -> istrip;
1441	     ?INLCR -> inlcr;
1442	     ?IGNCR -> igncr;
1443	     ?ICRNL -> icrnl;
1444	     ?IUCLC -> iuclc;
1445	     ?IXON -> ixon;
1446	     ?IXANY -> ixany;
1447	     ?IXOFF -> ixoff;
1448	     ?IMAXBEL -> imaxbel;
1449             ?IUTF8 -> iutf8; % RFC 8160
1450	     ?ISIG -> isig;
1451	     ?ICANON -> icanon;
1452	     ?XCASE -> xcase;
1453	     ?ECHO -> echo;
1454	     ?ECHOE -> echoe;
1455	     ?ECHOK -> echok;
1456	     ?ECHONL -> echonl;
1457	     ?NOFLSH -> noflsh;
1458	     ?TOSTOP -> tostop;
1459	     ?IEXTEN -> iexten;
1460	     ?ECHOCTL -> echoctl;
1461	     ?ECHOKE -> echoke;
1462	     ?PENDIN -> pendin;
1463	     ?OPOST -> opost;
1464	     ?OLCUC -> olcuc;
1465	     ?ONLCR -> onlcr;
1466	     ?OCRNL -> ocrnl;
1467	     ?ONOCR -> onocr;
1468	     ?ONLRET -> onlret;
1469	     ?CS7 -> cs7;
1470	     ?CS8 -> cs8;
1471	     ?PARENB -> parenb;
1472	     ?PARODD -> parodd;
1473	     ?TTY_OP_ISPEED -> tty_op_ispeed;
1474	     ?TTY_OP_OSPEED -> tty_op_ospeed;
1475	     _ -> Code
1476	 end,
1477    [{Op, Value} | decode_pty_opts2(Tail)].
1478
1479
1480backwards_compatible([], Acc) ->
1481    Acc;
1482backwards_compatible([{hight, Value} | Rest], Acc) ->
1483    backwards_compatible(Rest, [{height, Value} | Acc]);
1484backwards_compatible([{pixel_hight, Value} | Rest], Acc) ->
1485    backwards_compatible(Rest, [{height, Value} | Acc]);
1486backwards_compatible([Value| Rest], Acc) ->
1487    backwards_compatible(Rest, [ Value | Acc]).
1488
1489
1490%%%----------------------------------------------------------------
1491%%%
1492%%% Common part of handling channel messages meant for a cli (like "env", "exec" etc)
1493%%% Called at the finnish of handle_msg(#ssh_msg_channel_request,...)
1494%%%
1495
1496handle_cli_msg(C0, ChId, Reply0) ->
1497    Cache = C0#connection.channel_cache,
1498    Ch0 = ssh_client_channel:cache_lookup(Cache, ChId),
1499    case Ch0#channel.user of
1500        undefined ->
1501            case start_cli(C0, ChId) of
1502                {ok, Pid} ->
1503                    erlang:monitor(process, Pid),
1504                    Ch = Ch0#channel{user = Pid},
1505                    ssh_client_channel:cache_update(Cache, Ch),
1506                    reply_msg(Ch, C0, Reply0);
1507                {error, _Error} ->
1508                    Reply = {connection_reply, channel_failure_msg(Ch0#channel.remote_id)},
1509                    {[Reply], C0}
1510            end;
1511
1512        _ ->
1513            reply_msg(Ch0, C0, Reply0)
1514    end.
1515
1516%%%----------------------------------------------------------------
1517%%%
1518%%% TCP/IP forwarding
1519
1520%%%----------------------------------------------------------------
1521%%%
1522%%% Request response handling on return to the calling ssh_connection_handler
1523%%% state machine.
1524%%%
1525
1526channel_data_reply_msg(ChannelId, Connection, DataType, Data) ->
1527    case ssh_client_channel:cache_lookup(Connection#connection.channel_cache, ChannelId) of
1528	#channel{recv_window_size = Size} = Channel ->
1529	    WantedSize = Size - size(Data),
1530	    ssh_client_channel:cache_update(Connection#connection.channel_cache,
1531                                     Channel#channel{recv_window_size = WantedSize}),
1532            reply_msg(Channel, Connection, {data, ChannelId, DataType, Data});
1533	undefined ->
1534	    {[], Connection}
1535    end.
1536
1537
1538reply_msg(ChId, C, Reply) when is_integer(ChId) ->
1539    reply_msg(ssh_client_channel:cache_lookup(C#connection.channel_cache, ChId), C, Reply);
1540
1541reply_msg(Channel, Connection, {open, _} = Reply) ->
1542    request_reply_or_data(Channel, Connection, Reply);
1543reply_msg(Channel, Connection, {open_error, _, _, _} = Reply) ->
1544    request_reply_or_data(Channel, Connection, Reply);
1545reply_msg(Channel, Connection, success = Reply) ->
1546    request_reply_or_data(Channel, Connection, Reply);
1547reply_msg(Channel, Connection, failure = Reply) ->
1548    request_reply_or_data(Channel, Connection, Reply);
1549reply_msg(Channel, Connection, {closed, _} = Reply) ->
1550    request_reply_or_data(Channel, Connection, Reply);
1551reply_msg(undefined, Connection, _Reply) ->
1552    {[], Connection};
1553reply_msg(#channel{user = ChannelPid}, Connection, Reply) ->
1554    {[{channel_data, ChannelPid, Reply}], Connection}.
1555
1556
1557request_reply_or_data(#channel{local_id = ChannelId, user = ChannelPid},
1558		      #connection{requests = Requests} =
1559		      Connection, Reply) ->
1560    case lists:keysearch(ChannelId, 1, Requests) of
1561	{value, {ChannelId, From}} ->
1562	    {[{channel_request_reply, From, Reply}],
1563	     Connection#connection{requests =
1564				       lists:keydelete(ChannelId, 1, Requests)}};
1565	false when (Reply == success) or (Reply == failure) ->
1566	    {[], Connection};
1567	false ->
1568	    {[{channel_data, ChannelPid, Reply}], Connection}
1569    end.
1570
1571%%%----------------------------------------------------------------
1572send_environment_vars(ConnectionHandler, Channel, VarNames) ->
1573    lists:foldl(
1574      fun(Var, success) ->
1575              case os:getenv(Var) of
1576                  false ->
1577                      success;
1578                  Value ->
1579                      setenv(ConnectionHandler, Channel, false,
1580                             Var, Value, infinity)
1581              end
1582      end, success, VarNames).
1583