~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/ssh/src/ssh_connection.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%<copyright>
 
2
%% <year>2008-2008</year>
 
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
 
4
%%</copyright>
 
5
%%<legalnotice>
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%%----------------------------------------------------------------------
 
18
%% Purpose: Details of connection protocol
 
19
%%----------------------------------------------------------------------
 
20
 
 
21
-module(ssh_connection).
 
22
 
 
23
-include("ssh.hrl").
 
24
-include("ssh_connect.hrl").
 
25
-include("ssh_transport.hrl").
 
26
 
 
27
-export([session_channel/2, session_channel/4,
 
28
         exec/4, shell/2, subsystem/4, send/3, send/4, send/5, 
 
29
         send_eof/2, adjust_window/3, open_pty/3, open_pty/7,
 
30
         open_pty/9, setenv/5, window_change/4, window_change/6,
 
31
         direct_tcpip/6, direct_tcpip/8, tcpip_forward/3,
 
32
         cancel_tcpip_forward/3, signal/3, encode_ip/1, close/2,
 
33
         reply_request/4]).
 
34
 
 
35
-export([channel_data/6, handle_msg/4, channel_eof_msg/1,
 
36
         channel_close_msg/1, channel_success_msg/1, channel_failure_msg/1, 
 
37
         channel_adjust_window_msg/2, channel_data_msg/3,
 
38
         channel_open_msg/5, channel_open_confirmation_msg/4,
 
39
         channel_open_failure_msg/4, channel_request_msg/4,
 
40
         global_request_msg/3, request_failure_msg/0, 
 
41
         request_success_msg/1, bind/4, unbind/3, unbind_channel/2, 
 
42
         bound_channel/3, messages/0]).
 
43
 
 
44
%%--------------------------------------------------------------------
 
45
%%% API
 
46
%%--------------------------------------------------------------------
 
47
 
 
48
%%--------------------------------------------------------------------
 
49
%% Function: session_channel(ConnectionManager 
 
50
%%                           [, InitialWindowSize, MaxPacketSize], 
 
51
%%                           Timeout) -> {ok, }
 
52
%%   ConnectionManager = pid() 
 
53
%%   InitialWindowSize = integer()
 
54
%%   MaxPacketSize = integer() 
 
55
%%
 
56
%% Description: Opens a channel for a ssh session. A session is a
 
57
%% remote execution of a program. The program may be a shell, an
 
58
%% application, a system command, or some built-in subsystem.
 
59
%% --------------------------------------------------------------------
 
60
session_channel(ConnectionManager, Timeout) ->
 
61
    session_channel(ConnectionManager, 
 
62
                    ?DEFAULT_WINDOW_SIZE, ?DEFAULT_PACKET_SIZE,
 
63
                    Timeout).
 
64
session_channel(ConnectionManager, InitialWindowSize, 
 
65
                MaxPacketSize, Timeout) ->
 
66
    ssh_connection_manager:open_channel(ConnectionManager, "session", <<>>,
 
67
                                        InitialWindowSize,
 
68
                                        MaxPacketSize, Timeout).
 
69
%%--------------------------------------------------------------------
 
70
%% Function: exec(ConnectionManager, ChannelId, Command, Timeout) -> 
 
71
%%
 
72
%%   ConnectionManager = pid() 
 
73
%%   ChannelId = integer()
 
74
%%   Cmd = string()
 
75
%%   Timeout = integer() 
 
76
%%
 
77
%% Description: Will request that the server start the
 
78
%% execution of the given command. 
 
79
%%--------------------------------------------------------------------
 
80
exec(ConnectionManager, ChannelId, Command, TimeOut) ->
 
81
    ssh_connection_manager:request(ConnectionManager, ChannelId, "exec", 
 
82
                                   true, [?string(Command)], TimeOut).
 
83
%%--------------------------------------------------------------------
 
84
%% Function: shell(ConnectionManager, ChannelId) -> 
 
85
%%
 
86
%%   ConnectionManager = pid() 
 
87
%%   ChannelId = integer()
 
88
%%
 
89
%% Description: Will request that the user's default shell (typically
 
90
%% defined in /etc/passwd in UNIX systems) be started at the other
 
91
%% end.
 
92
%%--------------------------------------------------------------------
 
93
shell(ConnectionManager, ChannelId) ->
 
94
    ssh_connection_manager:request(ConnectionManager, ChannelId, 
 
95
                                   "shell", false, <<>>, 0).
 
96
%%--------------------------------------------------------------------
 
97
%% Function: subsystem(ConnectionManager, ChannelId, SubSystem, TimeOut) -> 
 
98
%%
 
99
%% ConnectionManager = pid() 
 
100
%% ChannelId = integer()
 
101
%% SubSystem = string()
 
102
%% TimeOut = integer() 
 
103
%%
 
104
%%
 
105
%% Description: Executes a predefined subsystem.
 
106
%%--------------------------------------------------------------------
 
107
subsystem(ConnectionManager, ChannelId, SubSystem, TimeOut) ->
 
108
     ssh_connection_manager:request(ConnectionManager, ChannelId, "subsystem", 
 
109
                                    true, [?string(SubSystem)], TimeOut).
 
110
%%--------------------------------------------------------------------
 
111
%% Function: send(ConnectionManager, ChannelId, Type, Data, [TimeOut]) ->
 
112
%%
 
113
%%
 
114
%% Description: Sends channel data.
 
115
%%--------------------------------------------------------------------
 
116
send(ConnectionManager, ChannelId, Data) ->
 
117
    send(ConnectionManager, ChannelId, 0, Data, infinity).
 
118
send(ConnectionManager, ChannelId, Data, TimeOut) when integer(TimeOut) ->
 
119
    send(ConnectionManager, ChannelId, 0, Data, TimeOut);
 
120
send(ConnectionManager, ChannelId, Type, Data) ->
 
121
    send(ConnectionManager, ChannelId, Type, Data, infinity).
 
122
send(ConnectionManager, ChannelId, Type, Data, TimeOut) ->
 
123
    ssh_connection_manager:send(ConnectionManager, ChannelId, 
 
124
                                Type, Data, TimeOut).
 
125
%%--------------------------------------------------------------------
 
126
%% Function: send_eof(ConnectionManager, ChannelId) ->
 
127
%%
 
128
%%
 
129
%% Description: Sends eof on the channel <ChannelId>.
 
130
%%--------------------------------------------------------------------
 
131
send_eof(ConnectionManager, Channel) ->
 
132
    ssh_connection_manager:send_eof(ConnectionManager, Channel).
 
133
 
 
134
%%--------------------------------------------------------------------
 
135
%% Function: adjust_window(ConnectionManager, Channel, Bytes) -> 
 
136
%%
 
137
%%
 
138
%% Description: Adjusts the ssh flowcontrol window.
 
139
%%--------------------------------------------------------------------
 
140
adjust_window(ConnectionManager, Channel, Bytes) ->
 
141
    ssh_connection_manager:adjust_window(ConnectionManager, Channel, Bytes).
 
142
 
 
143
%%--------------------------------------------------------------------
 
144
%% Function: setenv(ConnectionManager, ChannelId, Var, Value, TimeOut) ->
 
145
%%
 
146
%%
 
147
%% Description: Environment variables may be passed to the shell/command to be
 
148
%% started later.
 
149
%%--------------------------------------------------------------------
 
150
setenv(ConnectionManager, ChannelId, Var, Value, TimeOut) ->
 
151
    ssh_connection_manager:request(ConnectionManager, ChannelId, 
 
152
            "env", true, [?string(Var), ?string(Value)], TimeOut).
 
153
 
 
154
 
 
155
%%--------------------------------------------------------------------
 
156
%% Function: close(ConnectionManager, ChannelId) ->
 
157
%%
 
158
%%
 
159
%% Description: Sends a close message on the channel <ChannelId>.
 
160
%%--------------------------------------------------------------------
 
161
close(ConnectionManager, ChannelId) ->
 
162
    ssh_connection_manager:close(ConnectionManager, ChannelId).
 
163
 
 
164
 
 
165
%%--------------------------------------------------------------------
 
166
%% Function: reply_request(ConnectionManager, WantReply, Status, CannelId) ->_
 
167
%%
 
168
%%
 
169
%% Description: Send status replies to requests that want such replies.
 
170
%%--------------------------------------------------------------------
 
171
reply_request(ConnectionManager, true, Status, ChannelId) ->
 
172
    ConnectionManager ! {ssh_cm, self(), {Status, ChannelId}},
 
173
    ok;
 
174
reply_request(_,false, _, _) ->
 
175
    ok.
 
176
 
 
177
 
 
178
%%--------------------------------------------------------------------
 
179
%% Function: window_change(ConnectionManager, Channel, Width, Height) ->
 
180
%%
 
181
%%
 
182
%% Description: Not yet officialy supported.
 
183
%%--------------------------------------------------------------------
 
184
window_change(ConnectionManager, Channel, Width, Height) ->
 
185
    window_change(ConnectionManager, Channel, Width, Height, 0, 0).
 
186
window_change(ConnectionManager, Channel, Width, Height, 
 
187
              PixWidth, PixHeight) ->
 
188
    ssh_connection_manager:request(ConnectionManager, Channel, 
 
189
                                   "window-change", false, 
 
190
                                   [?uint32(Width), ?uint32(Height),
 
191
                                    ?uint32(PixWidth), ?uint32(PixHeight)], 0).
 
192
%%--------------------------------------------------------------------
 
193
%% Function: signal(ConnectionManager, Channel, Sig) ->
 
194
%%
 
195
%%
 
196
%% Description:  Not yet officialy supported.
 
197
%%--------------------------------------------------------------------
 
198
signal(ConnectionManager, Channel, Sig) ->
 
199
    ssh_connection_manager:request(ConnectionManager, Channel, "signal", false,
 
200
                                   [?string(Sig)], 0).
 
201
%%--------------------------------------------------------------------
 
202
%% Function: open_pty(ConnectionManager, Channel, TimeOut) ->
 
203
%%
 
204
%%
 
205
%% Description:  Not yet officialy supported.
 
206
%%--------------------------------------------------------------------
 
207
open_pty(ConnectionManager, Channel, TimeOut) ->
 
208
    open_pty(ConnectionManager, Channel, 
 
209
             os:getenv("TERM"), 80, 24, [], TimeOut).
 
210
 
 
211
open_pty(ConnectionManager, Channel, Term, Width, Height, PtyOpts, TimeOut) ->
 
212
    open_pty(ConnectionManager, Channel, Term, Width, 
 
213
             Height, 0, 0, PtyOpts, TimeOut).
 
214
 
 
215
open_pty(ConnectionManager, Channel, Term, Width, Height, 
 
216
         PixWidth, PixHeight, PtyOpts, TimeOut) ->
 
217
    ssh_connection_manager:request(ConnectionManager, 
 
218
                                   Channel, "pty-req", true, 
 
219
                                   [?string(Term),
 
220
                                    ?uint32(Width), ?uint32(Height),
 
221
                                    ?uint32(PixWidth),?uint32(PixHeight),
 
222
                                    encode_pty_opts(PtyOpts)], TimeOut).
 
223
 
 
224
 
 
225
%%--------------------------------------------------------------------
 
226
%% Function: direct_tcpip(ConnectionManager, RemoteHost,  
 
227
%%                        RemotePort, OrigIP, OrigPort, Timeout) ->
 
228
%%
 
229
%%
 
230
%% Description: Not yet officialy supported.
 
231
%%--------------------------------------------------------------------
 
232
direct_tcpip(ConnectionManager, RemoteHost, 
 
233
             RemotePort, OrigIP, OrigPort, Timeout) ->
 
234
    direct_tcpip(ConnectionManager, RemoteHost, RemotePort, OrigIP, OrigPort,
 
235
                 ?DEFAULT_WINDOW_SIZE, ?DEFAULT_PACKET_SIZE, Timeout).
 
236
 
 
237
direct_tcpip(ConnectionManager, RemoteIP, RemotePort, OrigIP, OrigPort,
 
238
             InitialWindowSize, MaxPacketSize, Timeout) ->
 
239
    case {encode_ip(RemoteIP), encode_ip(OrigIP)} of
 
240
        {false, _} -> 
 
241
            {error, einval};
 
242
        {_, false} -> 
 
243
            {error, einval};
 
244
        {RIP, OIP} ->
 
245
            ssh_connection_manager:open_channel(ConnectionManager,
 
246
                                                "direct-tcpip",
 
247
                                                [?string(RIP), 
 
248
                                                 ?uint32(RemotePort),
 
249
                                                 ?string(OIP),
 
250
                                                 ?uint32(OrigPort)],
 
251
                                                InitialWindowSize, 
 
252
                                                MaxPacketSize,
 
253
                                                Timeout)
 
254
    end.
 
255
%%--------------------------------------------------------------------
 
256
%% Function: tcpip_forward(ConnectionManager, BindIP, BindPort) ->
 
257
%%
 
258
%%
 
259
%% Description: Not yet officialy supported.
 
260
%%--------------------------------------------------------------------
 
261
tcpip_forward(ConnectionManager, BindIP, BindPort) ->
 
262
    case encode_ip(BindIP) of
 
263
        false -> 
 
264
            {error, einval};
 
265
        IPStr ->
 
266
            ssh_connection_manager:global_request(ConnectionManager, 
 
267
                                                  "tcpip-forward", true,
 
268
                                                  [?string(IPStr),
 
269
                                                   ?uint32(BindPort)])
 
270
    end.
 
271
%%--------------------------------------------------------------------
 
272
%% Function: cancel_tcpip_forward(ConnectionManager, BindIP, Port) ->
 
273
%%
 
274
%%
 
275
%% Description: Not yet officialy supported.
 
276
%%--------------------------------------------------------------------
 
277
cancel_tcpip_forward(ConnectionManager, BindIP, Port) ->
 
278
    case encode_ip(BindIP) of
 
279
        false -> 
 
280
            {error, einval};
 
281
        IPStr ->
 
282
            ssh_connection_manager:global_request(ConnectionManager, 
 
283
                                                  "cancel-tcpip-forward", true,
 
284
                                                  [?string(IPStr),
 
285
                                                   ?uint32(Port)])
 
286
    end.
 
287
 
 
288
%%--------------------------------------------------------------------
 
289
%%% Internal API
 
290
%%--------------------------------------------------------------------
 
291
channel_data(ChannelId, DataType, Data, Connection, ConnectionPid, From) 
 
292
  when is_list(Data)->
 
293
    channel_data(ChannelId, DataType, 
 
294
                 list_to_binary(Data), Connection, ConnectionPid, From);
 
295
 
 
296
channel_data(ChannelId, DataType, Data, 
 
297
             #connection{channel_cache = Cache} = Connection, ConnectionPid,
 
298
             From) ->
 
299
    
 
300
    case ssh_channel:cache_lookup(Cache, ChannelId) of
 
301
        #channel{} = Channel ->
 
302
            SendList = update_send_window(Channel, DataType, Data, Connection),
 
303
            Replies = 
 
304
                lists:map(fun({SendDataType, SendData}) -> 
 
305
                                      {connection_reply, ConnectionPid, 
 
306
                                       channel_data_msg(ChannelId, 
 
307
                                                        SendDataType, 
 
308
                                                        SendData)}
 
309
                          end, SendList),
 
310
            FlowCtrlMsgs = flow_control(Replies, 
 
311
                                        Channel#channel{flow_control = From}, 
 
312
                                        Cache),
 
313
            {{replies, Replies ++ FlowCtrlMsgs}, Connection};
 
314
        undefined ->
 
315
            {noreply, Connection}
 
316
    end.
 
317
 
 
318
handle_msg(#ssh_msg_channel_open_confirmation{recipient_channel = ChannelId, 
 
319
                                              sender_channel = RID,
 
320
                                              initial_window_size = WindowSz,
 
321
                                              maximum_packet_size = PacketSz}, 
 
322
           #connection{channel_cache = Cache} = Connection0, _, _) ->
 
323
    
 
324
    #channel{remote_id = undefined} = Channel =
 
325
        ssh_channel:cache_lookup(Cache, ChannelId), 
 
326
    
 
327
    ssh_channel:cache_update(Cache, Channel#channel{
 
328
                                     remote_id = RID,
 
329
                                     send_window_size = WindowSz,
 
330
                                     send_packet_size = PacketSz}),
 
331
    {Reply, Connection} = reply_msg(Channel, Connection0, {open, ChannelId}),
 
332
    {{replies, [Reply]}, Connection};
 
333
 
 
334
handle_msg(#ssh_msg_channel_open_failure{recipient_channel = ChannelId,
 
335
                                         reason = Reason,
 
336
                                         description = Descr,
 
337
                                         lang = Lang},  
 
338
           #connection{channel_cache = Cache} = Connection0, _, _) ->
 
339
    Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
340
    ssh_channel:cache_delete(Cache, ChannelId),
 
341
    {Reply, Connection} = 
 
342
        reply_msg(Channel, Connection0, {open_error, Reason, Descr, Lang}),
 
343
    {{replies, [Reply]}, Connection};
 
344
 
 
345
handle_msg(#ssh_msg_channel_success{recipient_channel = ChannelId},
 
346
           #connection{channel_cache = Cache} = Connection0, _, _) ->
 
347
    Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
348
    {Reply, Connection} = reply_msg(Channel, Connection0, success),
 
349
    {{replies, [Reply]}, Connection};
 
350
 
 
351
handle_msg(#ssh_msg_channel_failure{recipient_channel = ChannelId},
 
352
           #connection{channel_cache = Cache} = Connection0, _, _) ->
 
353
    Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
354
    {Reply, Connection} = reply_msg(Channel, Connection0, failure),
 
355
    {{replies, [Reply]}, Connection};
 
356
 
 
357
handle_msg(#ssh_msg_channel_eof{recipient_channel = ChannelId}, 
 
358
            #connection{channel_cache = Cache} = Connection0, _, _) ->
 
359
    Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
360
    {Reply, Connection} = reply_msg(Channel, Connection0, {eof, ChannelId}),
 
361
    {{replies, [Reply]}, Connection};
 
362
   
 
363
handle_msg(#ssh_msg_channel_close{recipient_channel = ChannelId},   
 
364
           #connection{channel_cache = Cache} = Connection0, 
 
365
           ConnectionPid, _) ->
 
366
    Replies = 
 
367
        case ssh_channel:cache_lookup(Cache, ChannelId) of
 
368
            #channel{sent_close = Closed, remote_id = RemoteId} = Channel ->
 
369
                ssh_channel:cache_delete(Cache, ChannelId),
 
370
                {CloseMsg, Connection} = 
 
371
                    reply_msg(Channel, Connection0, {closed, ChannelId}),
 
372
                case Closed of
 
373
                    true ->
 
374
                        {{replies, [CloseMsg]}, Connection};
 
375
                    false ->
 
376
                        RemoteCloseMsg = channel_close_msg(RemoteId),
 
377
                        {{replies, 
 
378
                          [{connection_reply, 
 
379
                                      ConnectionPid, RemoteCloseMsg},
 
380
                           CloseMsg]}, Connection}
 
381
                end;
 
382
            undefined ->
 
383
                {{replies, []}, Connection0}
 
384
        end,
 
385
    case ssh_channel:is_empty(Cache) of
 
386
        true ->
 
387
            {disconnect, {undefined, "No channels left to handle"}, Replies};
 
388
        false  ->
 
389
            Replies
 
390
    end;
 
391
 
 
392
handle_msg(#ssh_msg_channel_data{recipient_channel = ChannelId,
 
393
                                 data = Data}, 
 
394
           #connection{channel_cache = Cache} = Connection0, _, _) ->
 
395
    
 
396
    #channel{recv_window_size = Size} = Channel =
 
397
        ssh_channel:cache_lookup(Cache, ChannelId), 
 
398
    WantedSize = Size - size(Data),
 
399
    ssh_channel:cache_update(Cache, Channel#channel{
 
400
                                      recv_window_size = WantedSize}),
 
401
    {Replies, Connection} = 
 
402
        channel_data_reply(Cache, Channel, Connection0, 0, Data),
 
403
    {{replies, Replies}, Connection};
 
404
 
 
405
handle_msg(#ssh_msg_channel_extended_data{recipient_channel = ChannelId,
 
406
                                          data_type_code = DataType,
 
407
                                          data = Data}, 
 
408
           #connection{channel_cache = Cache} = Connection0, _, _) ->
 
409
    
 
410
    #channel{recv_window_size = Size} = Channel =
 
411
        ssh_channel:cache_lookup(Cache, ChannelId), 
 
412
    WantedSize = Size - size(Data),
 
413
    ssh_channel:cache_update(Cache, Channel#channel{
 
414
                                      recv_window_size = WantedSize}),
 
415
    {Replies, Connection} = 
 
416
        channel_data_reply(Cache, Channel, Connection0, DataType, Data),
 
417
    {{replies, Replies}, Connection};
 
418
 
 
419
handle_msg(#ssh_msg_channel_window_adjust{recipient_channel = ChannelId,
 
420
                                          bytes_to_add = Add}, 
 
421
           #connection{channel_cache = Cache} = Connection, 
 
422
           ConnectionPid, _) ->
 
423
    
 
424
    #channel{send_window_size = Size} = 
 
425
        Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
426
    SendData =  %% TODO: Datatype 0 ?
 
427
        update_send_window(Channel#channel{send_window_size = Size + Add},
 
428
                           0, <<>>, Connection),
 
429
    
 
430
    Replies = lists:map(fun({Type, Data}) -> 
 
431
                                {connection_reply, ConnectionPid,
 
432
                                 channel_data_msg(Channel, Type, Data)}
 
433
                        end, SendData),
 
434
    FlowCtrlMsgs = flow_control(Channel, Cache),
 
435
    {{replies, Replies ++ FlowCtrlMsgs}, Connection};
 
436
 
 
437
handle_msg(#ssh_msg_channel_open{channel_type = "session" = Type,
 
438
                                 sender_channel = RID,
 
439
                                 initial_window_size = RWindowSz,
 
440
                                 maximum_packet_size = RPacketSz}, 
 
441
           #connection{channel_pids = Processes,
 
442
                       channel_cache = Cache} = Connection0, 
 
443
           ConnectionPid, server) ->
 
444
   
 
445
    case Processes of %% TODO ?
 
446
        [{ChannelProcess,_}|_] ->
 
447
            {ChannelId, Connection1} = new_channel_id(Connection0),
 
448
            LWindowSz = ?DEFAULT_WINDOW_SIZE,
 
449
            LPacketSz = ?DEFAULT_PACKET_SIZE,
 
450
            Channel = #channel{type = Type,
 
451
                               sys = "ssh",
 
452
                               user = ChannelProcess,
 
453
                               local_id = ChannelId,
 
454
                               recv_window_size = LWindowSz,
 
455
                               recv_packet_size = LPacketSz,
 
456
                               send_window_size = RWindowSz,
 
457
                               send_packet_size = RPacketSz,
 
458
                               remote_id = RID,
 
459
                               passive_subsys = true,
 
460
                               subsys_queue = queue:new()
 
461
                              },
 
462
            ssh_channel:cache_update(Cache, Channel),
 
463
            OpenConfMsg = channel_open_confirmation_msg(RID, ChannelId,
 
464
                                                        LWindowSz, LPacketSz),
 
465
            {OpenMsg, Connection} = 
 
466
                reply_msg(Channel, Connection1, 
 
467
                          {open, ChannelId, RID, {session}}),
 
468
            {{replies, [{connection_reply, ConnectionPid, OpenConfMsg},
 
469
                        OpenMsg]}, Connection};
 
470
        _ ->
 
471
            FailMsg = channel_open_failure_msg(RID, 
 
472
                                               ?SSH_OPEN_CONNECT_FAILED,
 
473
                                               "Connection refused", "en"),
 
474
            {{replies, [{connection_reply, ConnectionPid, FailMsg}]}, 
 
475
             Connection0}
 
476
    end;
 
477
 
 
478
handle_msg(#ssh_msg_channel_open{channel_type = "session",
 
479
                                 sender_channel = RID}, 
 
480
           Connection, ConnectionPid, client) ->
 
481
    %% Client implementations SHOULD reject any session channel open
 
482
    %% requests to make it more difficult for a corrupt server to attack the
 
483
    %% client. See See RFC 4254 6.1.
 
484
    FailMsg = channel_open_failure_msg(RID, 
 
485
                                       ?SSH_OPEN_CONNECT_FAILED,
 
486
                                       "Connection refused", "en"),
 
487
    {{replies, [{connection_reply, ConnectionPid, FailMsg}]}, 
 
488
     Connection};
 
489
 
 
490
handle_msg(#ssh_msg_channel_open{channel_type = "forwarded-tcpip" = Type,
 
491
                                 sender_channel = RID,
 
492
                                 initial_window_size = RWindowSz,
 
493
                                 maximum_packet_size = RPacketSz,
 
494
                                 data = Data}, 
 
495
           #connection{channel_cache = Cache} = Connection0, 
 
496
           ConnectionPid, server) ->
 
497
    <<?UINT32(ALen), Address:ALen/binary, ?UINT32(Port),
 
498
     ?UINT32(OLen), Orig:OLen/binary, ?UINT32(OrigPort)>> = Data,
 
499
    
 
500
    case bound_channel(Address, Port, Connection0) of
 
501
        undefined ->
 
502
            FailMsg = channel_open_failure_msg(RID, 
 
503
                                               ?SSH_OPEN_CONNECT_FAILED,
 
504
                                               "Connection refused", "en"),
 
505
            {{replies, 
 
506
              [{connection_reply, ConnectionPid, FailMsg}]}, Connection0};
 
507
        ChannelPid ->
 
508
            {ChannelId, Connection1} = new_channel_id(Connection0),
 
509
            LWindowSz = ?DEFAULT_WINDOW_SIZE,
 
510
            LPacketSz = ?DEFAULT_PACKET_SIZE,
 
511
            Channel = #channel{type = Type,
 
512
                               sys = "none",
 
513
                               user = ChannelPid,
 
514
                               local_id = ChannelId,
 
515
                               recv_window_size = LWindowSz,
 
516
                               recv_packet_size = LPacketSz,
 
517
                               send_window_size = RWindowSz,
 
518
                               send_packet_size = RPacketSz},
 
519
            ssh_channel:cache_update(Cache, Channel),
 
520
            OpenConfMsg = channel_open_confirmation_msg(RID, ChannelId,
 
521
                                                        LWindowSz, LPacketSz),
 
522
            {OpenMsg, Connection} = 
 
523
                reply_msg(Channel, Connection1, 
 
524
                          {open,  Channel, {forwarded_tcpip,
 
525
                                            decode_ip(Address), Port,
 
526
                                            decode_ip(Orig), OrigPort}}),
 
527
            {{replies, [{connection_reply, ConnectionPid, OpenConfMsg},
 
528
                        OpenMsg]}, Connection}
 
529
    end;
 
530
 
 
531
handle_msg(#ssh_msg_channel_open{channel_type = "forwarded-tcpip",
 
532
                                 sender_channel = RID}, 
 
533
           Connection, ConnectionPid, client) ->
 
534
    %% Client implementations SHOULD reject direct TCP/IP open requests for
 
535
    %% security reasons. See RFC 4254 7.2.
 
536
    FailMsg = channel_open_failure_msg(RID, 
 
537
                                       ?SSH_OPEN_CONNECT_FAILED,
 
538
                                       "Connection refused", "en"),
 
539
    {{replies, [{connection_reply, ConnectionPid, FailMsg}]}, Connection};
 
540
 
 
541
 
 
542
handle_msg(#ssh_msg_channel_open{sender_channel = ChannelId}, Connection, 
 
543
           ConnectionPid, _) ->
 
544
    FailMsg = channel_open_failure_msg(ChannelId, 
 
545
                                       ?SSH_OPEN_ADMINISTRATIVELY_PROHIBITED,
 
546
                                       "Not allowed", "en"),
 
547
    {replies, [{connection_reply, ConnectionPid, FailMsg}], Connection};
 
548
 
 
549
handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
 
550
                                    request_type = "exit-status",
 
551
                                    data = Data},
 
552
           #connection{channel_cache = Cache} = Connection, _, _) ->
 
553
    <<?UINT32(Status)>> = Data,
 
554
    Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
555
    {Reply, Connection} = 
 
556
        reply_msg(Channel, Connection, {exit_status, ChannelId, Status}),
 
557
    {{replies, [Reply]}, Connection};
 
558
 
 
559
handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
 
560
                                    request_type = "exit-signal",
 
561
                                    want_reply = false,
 
562
                                    data = Data},  
 
563
           #connection{channel_cache = Cache} = Connection0, 
 
564
           ConnectionPid, _) ->
 
565
    <<?UINT32(SigLen), SigName:SigLen/binary,
 
566
     ?BOOLEAN(_Core), 
 
567
     ?UINT32(ErrLen), Err:ErrLen/binary,
 
568
     ?UINT32(LangLen), Lang:LangLen/binary>> = Data,
 
569
    Channel = ssh_channel:cache_lookup(Cache, ChannelId),
 
570
    RID =  Channel#channel.remote_id,
 
571
    {Reply, Connection} =  reply_msg(Channel, Connection0, 
 
572
                                     {exit_signal, ChannelId,
 
573
                                      binary_to_list(SigName),
 
574
                                      binary_to_list(Err),
 
575
                                      binary_to_list(Lang)}),
 
576
    CloseMsg = channel_close_msg(RID),
 
577
    {{replies, [{connection_reply, ConnectionPid, CloseMsg}, Reply]},
 
578
     Connection};
 
579
 
 
580
handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
 
581
                                    request_type = "xon-xoff",
 
582
                                    want_reply = false,
 
583
                                    data = Data},
 
584
           #connection{channel_cache = Cache} = Connection, _, _) ->
 
585
    <<?BOOLEAN(CDo)>> = Data,
 
586
    Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
587
    {Reply, Connection} = 
 
588
        reply_msg(Channel, Connection, {xon_xoff, ChannelId, CDo=/= 0}),
 
589
    {{replies, [Reply]}, Connection};
 
590
 
 
591
handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
 
592
                                    request_type = "window-change",
 
593
                                    want_reply = false,
 
594
                                    data = Data}, 
 
595
           #connection{channel_cache = Cache} = Connection0, _, _) ->
 
596
    <<?UINT32(Width),?UINT32(Height),
 
597
     ?UINT32(PixWidth), ?UINT32(PixHeight)>> = Data,
 
598
    Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
599
    {Reply, Connection} = 
 
600
        reply_msg(Channel, Connection0, {window_change, ChannelId,
 
601
                                         Width, Height,
 
602
                                         PixWidth, PixHeight}),
 
603
    {{replies, [Reply]}, Connection};
 
604
 
 
605
handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
 
606
                                    request_type = "signal",
 
607
                                    data = Data}, 
 
608
           #connection{channel_cache = Cache} = Connection0, _, _) ->
 
609
    <<?UINT32(SigLen), SigName:SigLen/binary>> = Data,
 
610
    
 
611
    Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
612
    {Reply, Connection} = 
 
613
        reply_msg(Channel, Connection0, {signal, ChannelId,
 
614
                                         binary_to_list(SigName)}),
 
615
    {{replies, [Reply]}, Connection};
 
616
 
 
617
handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
 
618
                                    request_type = "subsystem",
 
619
                                    want_reply = WantReply,
 
620
                                    data = Data},
 
621
           #connection{channel_cache = Cache} = Connection0, _, _) ->
 
622
    <<?UINT32(SsLen), SsName:SsLen/binary>> = Data,
 
623
    Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
624
    {Reply, Connection} =  reply_msg(Channel, Connection0, 
 
625
                                     {subsystem, ChannelId, WantReply,   
 
626
                                      binary_to_list(SsName)}),
 
627
    {{replies, [Reply]}, Connection};
 
628
 
 
629
handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
 
630
                                    request_type = "pty-req",
 
631
                                    want_reply = WantReply,
 
632
                                    data = Data}, 
 
633
           #connection{channel_cache = Cache} = Connection0, _, server) ->
 
634
    <<?UINT32(TermLen), BTermName:TermLen/binary,
 
635
     ?UINT32(Width),?UINT32(Height),
 
636
     ?UINT32(PixWidth), ?UINT32(PixHeight),
 
637
     Modes/binary>> = Data,
 
638
    TermName = binary_to_list(BTermName),
 
639
    Pty = #ssh_pty{term = TermName,
 
640
                   width = not_zero(Width, 80),
 
641
                   height = not_zero(Height, 24),
 
642
                   pixel_width = PixWidth,
 
643
                   pixel_height = PixHeight,
 
644
                   modes = decode_pty_opts(Modes)},
 
645
 
 
646
    Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
647
    {Reply, Connection} = reply_msg(Channel, Connection0, 
 
648
                                     {pty, Channel, WantReply, Pty}),
 
649
    {{replies, [Reply]}, Connection};
 
650
 
 
651
handle_msg(#ssh_msg_channel_request{request_type = "pty-req"},
 
652
           Connection, _, client) ->
 
653
    %% The client SHOULD ignore pty requests. See RFC 4254 6.2.
 
654
    {{replies, []}, Connection};
 
655
 
 
656
handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
 
657
                                    request_type = "shell",
 
658
                                    want_reply = WantReply},
 
659
           #connection{channel_cache = Cache} = Connection0, _, _) ->
 
660
    Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
661
    {Reply, Connection} =  reply_msg(Channel, Connection0, 
 
662
                                     {shell, WantReply}),
 
663
    {{replies, [Reply]}, Connection};
 
664
 
 
665
handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
 
666
                                    request_type = "exec",
 
667
                                    data = Data}, 
 
668
           #connection{channel_cache = Cache} = Connection0, _, _) ->
 
669
    <<?UINT32(Len), Command:Len/binary>> = Data,
 
670
    Channel = ssh_channel:cache_lookup(Cache, ChannelId), 
 
671
    {Reply, Connection} =  reply_msg(Channel, Connection0, 
 
672
                                     {exec, binary_to_list(Command)}),
 
673
    {{replies, [Reply]}, Connection};
 
674
   
 
675
 
 
676
handle_msg(#ssh_msg_channel_request{recipient_channel = ChannelId,
 
677
                                    request_type = _Other,
 
678
                                    want_reply = WantReply}, Connection,
 
679
           ConnectionPid, _) ->
 
680
    ?dbg(true, "ssh_msg ssh_msg_channel_request: Other=~p\n",
 
681
         [_Other]),
 
682
    if WantReply == true ->
 
683
            FailMsg = channel_failure_msg(ChannelId),
 
684
            {{replies, [{connection_reply, ConnectionPid, FailMsg}]}, 
 
685
             Connection};
 
686
       true ->
 
687
            {noreply, Connection}
 
688
    end;
 
689
 
 
690
handle_msg(#ssh_msg_global_request{name = _Type,
 
691
                                   want_reply = WantReply,
 
692
                                   data = _Data}, Connection,
 
693
           ConnectionPid, _) ->
 
694
    if WantReply == true ->
 
695
            FailMsg = request_failure_msg(),
 
696
            {{replies, [{connection_reply, ConnectionPid, FailMsg}]}, 
 
697
             Connection};
 
698
       true ->
 
699
            {noreply, Connection}  
 
700
    end;
 
701
 
 
702
%%% This transport message will also be handled at the connection level
 
703
handle_msg(#ssh_msg_disconnect{code = Code,
 
704
                              description = Description,
 
705
                              language = _Lang }, 
 
706
           #connection{channel_cache = Cache} = Connection0, _, _) ->
 
707
    {Connection, Replies} = 
 
708
        ssh_channel:cache_foldl(fun({Channel, {Connection1, Acc}}) ->
 
709
                                        {Reply, Connection2} =  
 
710
                                            reply_msg(
 
711
                                              Channel#channel.local_id,
 
712
                                              Connection1, closed),
 
713
                                        {Connection2, [Reply | Acc]}
 
714
                                end, {Connection0, []}, Cache),
 
715
    
 
716
    ssh_channel:cache_delete(Cache),
 
717
    {disconnect, {Code, Description}, {{replies, Replies}, Connection}}.
 
718
 
 
719
 
 
720
channel_eof_msg(ChannelId) ->
 
721
    #ssh_msg_channel_eof{recipient_channel = ChannelId}.
 
722
 
 
723
channel_close_msg(ChannelId) ->
 
724
    #ssh_msg_channel_close {recipient_channel = ChannelId}.
 
725
 
 
726
channel_success_msg(ChannelId) ->
 
727
    #ssh_msg_channel_success{recipient_channel = ChannelId}.
 
728
 
 
729
channel_failure_msg(ChannelId) ->
 
730
    #ssh_msg_channel_failure{recipient_channel = ChannelId}.
 
731
 
 
732
channel_adjust_window_msg(ChannelId, Bytes) ->
 
733
    #ssh_msg_channel_window_adjust{recipient_channel = ChannelId,
 
734
                                   bytes_to_add = Bytes}.
 
735
 
 
736
channel_data_msg(ChannelId, 0, Data) ->
 
737
    #ssh_msg_channel_data{recipient_channel = ChannelId,
 
738
                          data = Data};
 
739
channel_data_msg(ChannelId, Type, Data) ->
 
740
    #ssh_msg_channel_extended_data{recipient_channel = ChannelId,
 
741
                                    data_type_code = Type,
 
742
                                    data = Data}.
 
743
 
 
744
channel_open_msg(Type, ChannelId, WindowSize, MaxPacketSize, Data) ->
 
745
    #ssh_msg_channel_open{channel_type = Type,
 
746
                          sender_channel = ChannelId,
 
747
                          initial_window_size = WindowSize,
 
748
                          maximum_packet_size = MaxPacketSize,
 
749
                          data = Data
 
750
                         }.
 
751
 
 
752
channel_open_confirmation_msg(RID, LID, WindowSize, PacketSize) ->
 
753
    #ssh_msg_channel_open_confirmation{recipient_channel = RID,
 
754
                                       sender_channel = LID,
 
755
                                       initial_window_size = WindowSize,
 
756
                                       maximum_packet_size = PacketSize}.
 
757
 
 
758
channel_open_failure_msg(RID, Reason, Description, Lang) ->
 
759
    #ssh_msg_channel_open_failure{recipient_channel = RID,
 
760
                                  reason = Reason,
 
761
                                  description = Description,
 
762
                                  lang = Lang}.
 
763
 
 
764
channel_request_msg(ChannelId, Type, WantReply, Data) ->
 
765
    #ssh_msg_channel_request{recipient_channel = ChannelId,
 
766
                             request_type = Type,
 
767
                             want_reply = WantReply,
 
768
                             data = Data}.
 
769
 
 
770
global_request_msg(Type, WantReply, Data) ->
 
771
    #ssh_msg_global_request{name = Type,
 
772
                            want_reply = WantReply,
 
773
                            data = Data}.
 
774
request_failure_msg() ->
 
775
    #ssh_msg_request_failure{}.
 
776
 
 
777
request_success_msg(Data) ->
 
778
    #ssh_msg_request_success{data = Data}.
 
779
 
 
780
bind(IP, Port, ChannelPid, Connection) ->
 
781
    Binds = [{{IP, Port}, ChannelPid}
 
782
             | lists:keydelete({IP, Port}, 1, 
 
783
                               Connection#connection.port_bindings)],
 
784
    Connection#connection{port_bindings = Binds}.
 
785
 
 
786
unbind(IP, Port, Connection) ->
 
787
    Connection#connection{
 
788
      port_bindings = 
 
789
      lists:keydelete({IP, Port}, 1,
 
790
                      Connection#connection.port_bindings)}.
 
791
unbind_channel(ChannelPid, Connection) ->
 
792
    Binds = [{Bind, ChannelP} || {Bind, ChannelP} 
 
793
                                     <- Connection#connection.port_bindings, 
 
794
                                 ChannelP =/= ChannelPid],
 
795
    Connection#connection{port_bindings = Binds}.
 
796
 
 
797
bound_channel(IP, Port, Connection) ->
 
798
    case lists:keysearch({IP, Port}, 1, Connection#connection.port_bindings) of
 
799
        {value, {{IP, Port}, ChannelPid}} -> ChannelPid;
 
800
        _ -> undefined
 
801
    end.
 
802
 
 
803
messages() ->
 
804
    [ {ssh_msg_global_request, ?SSH_MSG_GLOBAL_REQUEST,
 
805
       [string, 
 
806
        boolean,
 
807
        '...']},
 
808
      
 
809
      {ssh_msg_request_success, ?SSH_MSG_REQUEST_SUCCESS,
 
810
       ['...']},
 
811
      
 
812
      {ssh_msg_request_failure, ?SSH_MSG_REQUEST_FAILURE,
 
813
       []},
 
814
      
 
815
      {ssh_msg_channel_open, ?SSH_MSG_CHANNEL_OPEN,
 
816
       [string,
 
817
        uint32,
 
818
        uint32,
 
819
        uint32,
 
820
        '...']},
 
821
 
 
822
      {ssh_msg_channel_open_confirmation, ?SSH_MSG_CHANNEL_OPEN_CONFIRMATION,
 
823
       [uint32,
 
824
        uint32,
 
825
        uint32,
 
826
        uint32,
 
827
        '...']},
 
828
 
 
829
      {ssh_msg_channel_open_failure, ?SSH_MSG_CHANNEL_OPEN_FAILURE,
 
830
       [uint32,
 
831
        uint32,
 
832
        string,
 
833
        string]},
 
834
 
 
835
      {ssh_msg_channel_window_adjust, ?SSH_MSG_CHANNEL_WINDOW_ADJUST,
 
836
       [uint32,
 
837
        uint32]},
 
838
 
 
839
      {ssh_msg_channel_data, ?SSH_MSG_CHANNEL_DATA,
 
840
       [uint32,
 
841
        binary]},
 
842
 
 
843
      {ssh_msg_channel_extended_data, ?SSH_MSG_CHANNEL_EXTENDED_DATA,
 
844
       [uint32,
 
845
        uint32,
 
846
        binary]},
 
847
 
 
848
      {ssh_msg_channel_eof, ?SSH_MSG_CHANNEL_EOF,
 
849
       [uint32]},
 
850
 
 
851
      {ssh_msg_channel_close, ?SSH_MSG_CHANNEL_CLOSE,
 
852
       [uint32]},
 
853
 
 
854
      {ssh_msg_channel_request, ?SSH_MSG_CHANNEL_REQUEST,
 
855
       [uint32,
 
856
        string,
 
857
        boolean,
 
858
        '...']},
 
859
 
 
860
      {ssh_msg_channel_success, ?SSH_MSG_CHANNEL_SUCCESS,
 
861
       [uint32]},
 
862
 
 
863
      {ssh_msg_channel_failure, ?SSH_MSG_CHANNEL_FAILURE,
 
864
       [uint32]}
 
865
     ].
 
866
 
 
867
encode_ip(Addr) when is_tuple(Addr) ->
 
868
    case catch inet_parse:ntoa(Addr) of
 
869
        {'EXIT',_} -> false;
 
870
        A -> A
 
871
    end;
 
872
encode_ip(Addr) when is_list(Addr) ->
 
873
    case inet_parse:address(Addr) of
 
874
        {ok, _} -> Addr;
 
875
        Error ->
 
876
            case inet:getaddr(Addr, inet) of
 
877
                {ok, A} ->
 
878
                    inet_parse:ntoa(A);
 
879
                Error -> false
 
880
            end
 
881
    end.
 
882
 
 
883
%%--------------------------------------------------------------------
 
884
%%% Internal functions
 
885
%%--------------------------------------------------------------------
 
886
channel_data_reply(Cache, #channel{sys = "subsystem",
 
887
                                   passive_subsys = true, local_id = ChannelId,
 
888
                                   subsys_queue = Queue} = Channel, 
 
889
                   Connection, Datatype, Data) ->
 
890
    NewQueue = queue:in({data, ChannelId, Datatype, Data}, Queue),
 
891
    ssh_channel:cache_update(Cache, Channel#channel{subsys_queue = NewQueue}),
 
892
    {[], Connection};
 
893
 
 
894
channel_data_reply(_, #channel{local_id = ChannelId} = Channel, 
 
895
                   Connection0, DataType, Data) ->
 
896
    {Reply, Connection} =
 
897
        reply_msg(Channel, Connection0, {data, ChannelId, DataType, Data}),
 
898
    {[Reply], Connection}.
 
899
 
 
900
new_channel_id(Connection) ->
 
901
    ID = Connection#connection.channel_id_seed,
 
902
    {ID, Connection#connection{channel_id_seed = ID + 1}}.
 
903
 
 
904
reply_msg(Channel, Connection, {open, _} = Reply) ->
 
905
    request_reply_or_data(Channel, Connection, Reply);
 
906
reply_msg(Channel, Connection, {open_error, _, _, _} = Reply) ->
 
907
    request_reply_or_data(Channel, Connection, Reply);
 
908
reply_msg(Channel, Connection, success = Reply) ->
 
909
    request_reply_or_data(Channel, Connection, Reply);
 
910
reply_msg(Channel, Connection, failure = Reply) ->
 
911
    request_reply_or_data(Channel, Connection, Reply);
 
912
reply_msg(Channel, Connection, closed = Reply) ->
 
913
    request_reply_or_data(Channel, Connection, Reply);
 
914
reply_msg(#channel{user = ChannelPid}, Connection, Reply) ->
 
915
    {{channel_data, ChannelPid, Reply}, Connection}.
 
916
 
 
917
request_reply_or_data(#channel{local_id = ChannelId, user = ChannelPid}, 
 
918
                      #connection{requests = Requests} = 
 
919
                      Connection, Reply) -> 
 
920
    case lists:keysearch(ChannelId, 1, Requests) of
 
921
        {value, {ChannelId, From}} ->
 
922
            {{channel_requst_reply, From, Reply}, 
 
923
             Connection#connection{requests = 
 
924
                                   lists:keydelete(ChannelId, 1, Requests)}};
 
925
        false ->
 
926
            {{channel_data, ChannelPid, Reply}, Connection}
 
927
    end.
 
928
 
 
929
update_send_window(Channel, DataType, Data,  
 
930
                        #connection{channel_cache = Cache}) ->
 
931
    Buf0 = if Data == <<>> ->
 
932
                   Channel#channel.send_buf;
 
933
              true ->
 
934
                   Channel#channel.send_buf ++ [{DataType, Data}]
 
935
           end,
 
936
    {Buf1, NewSz, Buf2} = get_window(Buf0, 
 
937
                                     Channel#channel.send_packet_size,
 
938
                                     Channel#channel.send_window_size),
 
939
    ssh_channel:cache_update(Cache, Channel#channel{send_window_size = NewSz,
 
940
                                                    send_buf = Buf2}),
 
941
    Buf1.
 
942
 
 
943
get_window(Bs, PSz, WSz) ->
 
944
    get_window(Bs, PSz, WSz, []).
 
945
 
 
946
get_window(Bs, _PSz, 0, Acc) ->
 
947
    {lists:reverse(Acc), 0, Bs};
 
948
get_window([B0 = {DataType, Bin} | Bs], PSz, WSz, Acc) ->
 
949
    BSz = size(Bin),
 
950
    if BSz =< WSz ->  %% will fit into window
 
951
            if BSz =< PSz ->  %% will fit into a packet
 
952
                    get_window(Bs, PSz, WSz-BSz, [B0|Acc]);
 
953
               true -> %% split into packet size
 
954
                    <<Bin1:PSz/binary, Bin2/binary>> = Bin,
 
955
                    get_window([setelement(2, B0, Bin2) | Bs],
 
956
                               PSz, WSz-PSz, 
 
957
                               [{DataType, Bin1}|Acc])
 
958
            end;
 
959
       WSz =< PSz ->  %% use rest of window
 
960
            <<Bin1:WSz/binary, Bin2/binary>> = Bin,
 
961
            get_window([setelement(2, B0, Bin2) | Bs],
 
962
                       PSz, WSz-WSz, 
 
963
                       [{DataType, Bin1}|Acc]);
 
964
       true -> %% use packet size
 
965
            <<Bin1:PSz/binary, Bin2/binary>> = Bin,
 
966
            get_window([setelement(2, B0, Bin2) | Bs],
 
967
                       PSz, WSz-PSz, 
 
968
                       [{DataType, Bin1}|Acc])
 
969
    end;
 
970
get_window([], _PSz, WSz, Acc) ->
 
971
    {lists:reverse(Acc), WSz, []}.
 
972
 
 
973
flow_control(Channel, Cache) ->
 
974
    flow_control([window_adjusted], Channel, Cache).
 
975
                                    
 
976
flow_control([], Channel, Cache) ->
 
977
    ssh_channel:cache_update(Cache, Channel),
 
978
    [];
 
979
flow_control([_|_], #channel{flow_control = From} = Channel, Cache) ->
 
980
    case From of
 
981
        undefined ->
 
982
            [];
 
983
        _ ->
 
984
            [{flow_control, Cache,  Channel, From, ok}]
 
985
    end.
 
986
 
 
987
not_zero(0, B) -> B;
 
988
not_zero(A, _) -> A.
 
989
 
 
990
encode_pty_opts(Opts) ->
 
991
    Bin = list_to_binary(encode_pty_opts2(Opts)),
 
992
    Len = size(Bin),
 
993
    <<?UINT32(Len), Bin/binary>>.
 
994
 
 
995
encode_pty_opts2([]) -> 
 
996
    [?TTY_OP_END];
 
997
encode_pty_opts2([{vintr,Value} | Opts]) ->
 
998
    [?VINTR, ?uint32(Value) | encode_pty_opts2(Opts)];
 
999
encode_pty_opts2([{vquit,Value} | Opts]) ->
 
1000
    [?VQUIT, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1001
encode_pty_opts2([{verase,Value} | Opts]) ->
 
1002
    [?VERASE, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1003
encode_pty_opts2([{vkill,Value} | Opts]) ->
 
1004
    [?VKILL, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1005
encode_pty_opts2([{veof,Value} | Opts]) ->
 
1006
    [?VEOF, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1007
encode_pty_opts2([{veol,Value} | Opts]) ->
 
1008
    [?VEOL, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1009
encode_pty_opts2([{veol2,Value} | Opts]) ->
 
1010
    [?VEOL2, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1011
encode_pty_opts2([{vstart,Value} | Opts]) ->
 
1012
    [?VSTART, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1013
encode_pty_opts2([{vstop,Value} | Opts]) ->
 
1014
    [?VSTOP, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1015
encode_pty_opts2([{vsusp,Value} | Opts]) ->
 
1016
    [?VSUSP, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1017
encode_pty_opts2([{vdsusp,Value} | Opts]) ->
 
1018
    [?VDSUSP, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1019
encode_pty_opts2([{vreprint,Value} | Opts]) ->
 
1020
    [?VREPRINT, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1021
encode_pty_opts2([{vwerase,Value} | Opts]) ->
 
1022
    [ ?VWERASE, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1023
encode_pty_opts2([{vlnext,Value} | Opts]) ->
 
1024
    [?VLNEXT, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1025
encode_pty_opts2([{vflush,Value} | Opts]) ->
 
1026
    [?VFLUSH, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1027
encode_pty_opts2([{vswtch,Value} | Opts]) ->
 
1028
    [?VSWTCH, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1029
encode_pty_opts2([{vstatus,Value} | Opts]) ->
 
1030
    [?VSTATUS, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1031
encode_pty_opts2([{vdiscard,Value} | Opts]) ->
 
1032
    [?VDISCARD, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1033
encode_pty_opts2([{ignpar,Value} | Opts]) ->
 
1034
    [?IGNPAR, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1035
encode_pty_opts2([{parmrk,Value} | Opts]) ->
 
1036
    [?PARMRK, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1037
encode_pty_opts2([{inpck,Value} | Opts]) ->
 
1038
    [?INPCK, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1039
encode_pty_opts2([{istrip,Value} | Opts]) ->
 
1040
    [?ISTRIP, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1041
encode_pty_opts2([{inlcr,Value} | Opts]) ->
 
1042
    [?INLCR, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1043
encode_pty_opts2([{igncr,Value} | Opts]) ->
 
1044
    [?IGNCR, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1045
encode_pty_opts2([{icrnl,Value} | Opts]) ->
 
1046
    [?ICRNL, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1047
encode_pty_opts2([{iuclc,Value} | Opts]) ->
 
1048
    [?IUCLC, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1049
encode_pty_opts2([{ixon,Value} | Opts]) ->
 
1050
    [?IXON, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1051
encode_pty_opts2([{ixany,Value} | Opts]) ->
 
1052
    [?IXANY, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1053
encode_pty_opts2([{ixoff,Value} | Opts]) ->
 
1054
    [?IXOFF, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1055
encode_pty_opts2([{imaxbel,Value} | Opts]) ->
 
1056
    [?IMAXBEL, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1057
encode_pty_opts2([{isig,Value} | Opts]) ->
 
1058
    [?ISIG, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1059
encode_pty_opts2([{icanon,Value} | Opts]) ->
 
1060
    [?ICANON, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1061
encode_pty_opts2([{xcase,Value} | Opts]) ->
 
1062
    [?XCASE, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1063
encode_pty_opts2([{echo,Value} | Opts]) ->
 
1064
    [?ECHO, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1065
encode_pty_opts2([{echoe,Value} | Opts]) ->
 
1066
    [?ECHOE, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1067
encode_pty_opts2([{echok,Value} | Opts]) ->
 
1068
    [?ECHOK, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1069
encode_pty_opts2([{echonl,Value} | Opts]) ->
 
1070
    [?ECHONL, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1071
encode_pty_opts2([{noflsh,Value} | Opts]) ->
 
1072
    [?NOFLSH, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1073
encode_pty_opts2([{tostop,Value} | Opts]) ->
 
1074
    [?TOSTOP, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1075
encode_pty_opts2([{iexten,Value} | Opts]) ->
 
1076
    [?IEXTEN, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1077
encode_pty_opts2([{echoctl,Value} | Opts]) ->
 
1078
    [?ECHOCTL, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1079
encode_pty_opts2([{echoke,Value} | Opts]) ->
 
1080
    [?ECHOKE, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1081
encode_pty_opts2([{pendin,Value} | Opts]) ->
 
1082
    [?PENDIN, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1083
encode_pty_opts2([{opost,Value} | Opts]) ->
 
1084
    [?OPOST, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1085
encode_pty_opts2([{olcuc,Value} | Opts]) ->
 
1086
    [?OLCUC, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1087
encode_pty_opts2([{onlcr,Value} | Opts]) ->
 
1088
    [?ONLCR, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1089
encode_pty_opts2([{ocrnl,Value} | Opts]) ->
 
1090
    [?OCRNL, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1091
encode_pty_opts2([{onocr,Value} | Opts]) ->
 
1092
    [?ONOCR, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1093
encode_pty_opts2([{onlret,Value} | Opts]) ->
 
1094
    [?ONLRET, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1095
encode_pty_opts2([{cs7,Value} | Opts]) ->
 
1096
    [?CS7, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1097
encode_pty_opts2([{cs8,Value} | Opts]) ->
 
1098
    [?CS8, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1099
encode_pty_opts2([{parenb,Value} | Opts]) ->
 
1100
    [?PARENB, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1101
encode_pty_opts2([{parodd,Value} | Opts]) ->
 
1102
    [?PARODD, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1103
encode_pty_opts2([{tty_op_ispeed,Value} | Opts]) ->
 
1104
    [?TTY_OP_ISPEED, ?uint32(Value) | encode_pty_opts2(Opts)];
 
1105
encode_pty_opts2([{tty_op_ospeed,Value} | Opts]) ->
 
1106
    [?TTY_OP_OSPEED, ?uint32(Value) | encode_pty_opts2(Opts)].
 
1107
 
 
1108
decode_pty_opts(<<>>) ->                     
 
1109
    [];
 
1110
decode_pty_opts(<<0, 0, 0, 0>>) ->
 
1111
    [];
 
1112
decode_pty_opts(<<?UINT32(Len), Modes:Len/binary>>) ->
 
1113
    decode_pty_opts2(Modes);
 
1114
decode_pty_opts(Binary) ->
 
1115
    decode_pty_opts2(Binary).
 
1116
 
 
1117
decode_pty_opts2(<<?TTY_OP_END>>) ->                 
 
1118
    [];
 
1119
decode_pty_opts2(<<Code, ?UINT32(Value), Tail/binary>>) ->
 
1120
    Op = case Code of
 
1121
             ?VINTR -> vintr;
 
1122
             ?VQUIT -> vquit;
 
1123
             ?VERASE -> verase;
 
1124
             ?VKILL -> vkill;
 
1125
             ?VEOF -> veof;
 
1126
             ?VEOL -> veol;
 
1127
             ?VEOL2 -> veol2;
 
1128
             ?VSTART -> vstart;
 
1129
             ?VSTOP -> vstop;
 
1130
             ?VSUSP -> vsusp;
 
1131
             ?VDSUSP -> vdsusp;
 
1132
             ?VREPRINT -> vreprint;
 
1133
             ?VWERASE -> vwerase;
 
1134
             ?VLNEXT -> vlnext;
 
1135
             ?VFLUSH -> vflush;
 
1136
             ?VSWTCH -> vswtch;
 
1137
             ?VSTATUS -> vstatus;
 
1138
             ?VDISCARD -> vdiscard;
 
1139
             ?IGNPAR -> ignpar;
 
1140
             ?PARMRK -> parmrk;
 
1141
             ?INPCK -> inpck;
 
1142
             ?ISTRIP -> istrip;
 
1143
             ?INLCR -> inlcr;
 
1144
             ?IGNCR -> igncr;
 
1145
             ?ICRNL -> icrnl;
 
1146
             ?IUCLC -> iuclc;
 
1147
             ?IXON -> ixon;
 
1148
             ?IXANY -> ixany;
 
1149
             ?IXOFF -> ixoff;
 
1150
             ?IMAXBEL -> imaxbel;
 
1151
             ?ISIG -> isig;
 
1152
             ?ICANON -> icanon;
 
1153
             ?XCASE -> xcase;
 
1154
             ?ECHO -> echo;
 
1155
             ?ECHOE -> echoe;
 
1156
             ?ECHOK -> echok;
 
1157
             ?ECHONL -> echonl;
 
1158
             ?NOFLSH -> noflsh;
 
1159
             ?TOSTOP -> tostop;
 
1160
             ?IEXTEN -> iexten;
 
1161
             ?ECHOCTL -> echoctl;
 
1162
             ?ECHOKE -> echoke;
 
1163
             ?PENDIN -> pendin;
 
1164
             ?OPOST -> opost;
 
1165
             ?OLCUC -> olcuc;
 
1166
             ?ONLCR -> onlcr;
 
1167
             ?OCRNL -> ocrnl;
 
1168
             ?ONOCR -> onocr;
 
1169
             ?ONLRET -> onlret;
 
1170
             ?CS7 -> cs7;
 
1171
             ?CS8 -> cs8;
 
1172
             ?PARENB -> parenb;
 
1173
             ?PARODD -> parodd;
 
1174
             ?TTY_OP_ISPEED -> tty_op_ispeed;
 
1175
             ?TTY_OP_OSPEED -> tty_op_ospeed
 
1176
         end,    
 
1177
    [{Op, Value} | decode_pty_opts2(Tail)].
 
1178
 
 
1179
decode_ip(Addr) when is_binary(Addr) ->
 
1180
    case inet_parse:address(binary_to_list(Addr)) of
 
1181
        {error,_} -> Addr;
 
1182
        {ok,A}    -> A
 
1183
    end.