~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id$
 
17
%%
 
18
 
 
19
%%% Description : SSH connection protocol manager
 
20
 
 
21
-module(ssh_cm).
 
22
 
 
23
-include("ssh.hrl").
 
24
-include("ssh_connect.hrl").
 
25
 
 
26
-define(DEFAULT_PACKET_SIZE, 32768).
 
27
-define(DEFAULT_WINDOW_SIZE, 2*?DEFAULT_PACKET_SIZE).
 
28
-define(DEFAULT_TIMEOUT, 5000).
 
29
 
 
30
-behaviour(gen_server).
 
31
 
 
32
-import(lists, [reverse/1, foreach/2]).
 
33
 
 
34
%% gen_server callbacks
 
35
-export([init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2,
 
36
         code_change/3]).
 
37
 
 
38
-export([connect/1, connect/2, connect/3]).
 
39
-export([listen/2, listen/3, listen/4, stop_listener/1]).
 
40
-export([stop/1]).
 
41
%%-export([dist_start/1, dist_start/2]).
 
42
-export([encode_ip/1]).
 
43
 
 
44
%% API
 
45
-export([adjust_window/3, attach/2, detach/2,
 
46
         tcpip_forward/3, cancel_tcpip_forward/3, direct_tcpip/6,
 
47
         direct_tcpip/8, 
 
48
         close/2,
 
49
         shell/2, exec/4, i/1, i/2, info/1, info/2, 
 
50
         recv_window/3, send/3, send/4, renegotiate/1, renegotiate/2,
 
51
         request_success/2, send_ack/3, send_ack/4, send_ack/5, send_eof/2,
 
52
         send_window/3, session_open/2, session_open/4, subsystem/4,
 
53
         open_pty/3, open_pty/7, open_pty/9,
 
54
         set_user_ack/4, set_user/4,
 
55
         setenv/5, signal/3, winch/4,
 
56
         get_authhandle/1,
 
57
         get_peer_addr/1]).
 
58
 
 
59
%% Special for ssh_userauth (and similar)
 
60
%%-export([set_ssh_msg_handler/2, reset_ssh_msg_handler/1]).
 
61
 
 
62
%% internal exports
 
63
%% -export([listen_init/7, connect_init/6]).
 
64
 
 
65
-define(DBG_SSHMSG, true).
 
66
-define(DBG_SSHCM,  true).
 
67
-define(DBG_USER,   true).
 
68
 
 
69
-record(channel,
 
70
        {
 
71
          type,          %% "session", "x11", "forwarded-tcpip", "direct-tcpip"
 
72
          sys,           %% "none", "shell", "exec" "subsystem"
 
73
          user,          %% "user" process id (default to cm user)
 
74
          user_ack = false,   %% user want ack packet when data is sent
 
75
 
 
76
          local_id,           %% local channel id
 
77
 
 
78
          recv_window_size,
 
79
          recv_packet_size,
 
80
          %%recv_eof = false,
 
81
          recv_close = false,
 
82
 
 
83
          remote_id,          %% remote channel id
 
84
          send_window_size,
 
85
          send_packet_size,
 
86
          %%sent_eof = false,
 
87
          sent_close = false,
 
88
          send_buf = []
 
89
         }).
 
90
 
 
91
-record(state,
 
92
        {
 
93
          role,
 
94
          %%ssh_msg_handler,
 
95
          ssh,
 
96
          ctab,
 
97
          binds = [],
 
98
          users = [],
 
99
          channel_id = 0,
 
100
          opts,
 
101
          requests = [], %% [{Channel, Pid}...] awaiting reply on request
 
102
          authhandle     %% for session termination
 
103
         }).
 
104
 
 
105
%%====================================================================
 
106
%% API
 
107
%%====================================================================
 
108
 
 
109
%%--------------------------------------------------------------------
 
110
%% Function: connect(...) -> {ok,Pid} | {error,Error}
 
111
%% Description: Starts the server (as an ssh-client)
 
112
%%--------------------------------------------------------------------
 
113
connect(Host) ->
 
114
    connect(Host, []).
 
115
connect(Host, Opts) ->
 
116
    connect(Host, ?SSH_DEFAULT_PORT, Opts).
 
117
connect(Host, Port, Opts) ->
 
118
    gen_server:start_link(?MODULE, [client, self(), Host, Port, Opts], []).
 
119
 
 
120
%%--------------------------------------------------------------------
 
121
%% Function: listen(...) -> Pid | {error,Error}
 
122
%% Description: Starts a listening server (as an ssh-server)
 
123
%%--------------------------------------------------------------------
 
124
listen(UserFun, Port) ->
 
125
    listen(UserFun, Port, []).
 
126
listen(UserFun, Port, Opts) ->
 
127
    listen(UserFun, any, Port, Opts).
 
128
listen(UserFun, Addr, Port, Opts) ->
 
129
    Self = self(),
 
130
    ssh_userauth:reg_user_auth_server(),
 
131
    ssh_transport:listen(
 
132
      fun(SSH) ->
 
133
              {ok, CM} =
 
134
                  gen_server:start_link(
 
135
                    ?MODULE, [server, Self, UserFun, SSH, Opts], []),
 
136
              CM
 
137
      end, Addr, Port, Opts).
 
138
 
 
139
%%--------------------------------------------------------------------
 
140
%% Function: stop_listener(Pid) -> ok
 
141
%% Description: Stops the listener
 
142
%%--------------------------------------------------------------------
 
143
stop_listener(Pid) ->
 
144
    ssh_transport:stop_listener(Pid).
 
145
 
 
146
%% %%
 
147
%% %% special ssh distribution version
 
148
%% %%
 
149
%% dist_start(Node) ->
 
150
%%     Opts1 = case init:get_argument('ssh_password') of
 
151
%%             {ok, [[Passwd]]} -> [{password, Passwd}];
 
152
%%             error -> []
 
153
%%         end,
 
154
%%     Opts2 = case init:get_argument('ssh_user') of
 
155
%%              {ok, [[User]]} -> [{user, User}];
 
156
%%              error -> []
 
157
%%          end,
 
158
%%     dist_start(Node, Opts1++Opts2).
 
159
    
 
160
%% dist_start(Node, Opts) when atom(Node), list(Opts) ->
 
161
%%     case string:tokens(atom_to_list(Node), "@") of
 
162
%%      [_, "ssh:"++Host] ->
 
163
%%          CMHost = list_to_atom(Host),
 
164
%%          case whereis(CMHost) of
 
165
%%              undefined ->
 
166
%%                  start(CMHost, Host, Opts);
 
167
%%              Pid when pid(Pid) ->
 
168
%%                  {ok,Pid};
 
169
%%              _ ->
 
170
%%                  {error, einval}
 
171
%%          end;
 
172
%%      _ ->
 
173
%%          {error, einval}
 
174
%%     end;
 
175
%% dist_start(_, _) ->
 
176
%%     {error, einval}.
 
177
 
 
178
 
 
179
%%====================================================================
 
180
%% gen_server callbacks
 
181
%%====================================================================
 
182
 
 
183
%%--------------------------------------------------------------------
 
184
%% Function: init(Args) -> {ok, State} |
 
185
%%                         {ok, State, Timeout} |
 
186
%%                         ignore               |
 
187
%%                         {stop, Reason}
 
188
%% Description: Initiates the server
 
189
%%--------------------------------------------------------------------
 
190
init([server, _Caller, UserFun, SSH, Opts]) ->
 
191
    SSH ! {ssh_install, connect_messages()},
 
192
    process_flag(trap_exit, true),
 
193
    User = UserFun(),
 
194
    %% Caller ! {self(), {ok, self()}},
 
195
    CTab = ets:new(cm_tab, [set,{keypos, #channel.local_id}]),
 
196
    State = #state{role = server, ctab = CTab, ssh = SSH, opts = Opts,
 
197
                   requests = []},
 
198
    NewState = add_user(User, State),  %% add inital user
 
199
    {ok, NewState};
 
200
init([client, User, Host, Port, Opts]) ->
 
201
    case ssh_transport:connect(Host, Port, Opts) of
 
202
        {ok, SSH} ->
 
203
            case user_auth(SSH, Opts) of
 
204
                ok ->
 
205
                    SSH ! {ssh_install, connect_messages()},
 
206
                    process_flag(trap_exit, true),
 
207
                    CTab = ets:new(cm_tab, [set,{keypos,#channel.local_id}]),
 
208
                    State = #state{role = client, ctab = CTab, ssh = SSH,
 
209
                                   opts = Opts, requests = []},
 
210
                    NewState = add_user(User, State),  %% add inital user
 
211
                    {ok, NewState};
 
212
                Error ->
 
213
                    ssh_transport:disconnect(
 
214
                      SSH, ?SSH_DISCONNECT_BY_APPLICATION),
 
215
                    {stop, Error}
 
216
            end;
 
217
        Error ->
 
218
            {stop, Error}
 
219
    end.
 
220
 
 
221
i(CM) ->
 
222
    i(CM, all).
 
223
 
 
224
i(CM, User) ->
 
225
    case info(CM, User) of
 
226
        {ok, Cs} ->
 
227
            Cs1 = lists:keysort(#channel.user, Cs),
 
228
            foreach(
 
229
              fun(C) ->
 
230
                      io:format("~10p ~w ~s/~s ~w/~w ~w/~w\n",
 
231
                                [C#channel.user,
 
232
                                 C#channel.local_id,
 
233
                                 C#channel.type, C#channel.sys,
 
234
                                 C#channel.recv_window_size,
 
235
                                 C#channel.recv_packet_size,
 
236
                                 C#channel.send_window_size,
 
237
                                 C#channel.send_packet_size])
 
238
              end, Cs1);
 
239
        Error ->
 
240
            Error
 
241
    end.    
 
242
 
 
243
info(CM) ->
 
244
    info(CM, all).
 
245
 
 
246
info(CM, User) ->
 
247
    gen_server:call(CM, {info, User}).
 
248
 
 
249
%% CM Client commands
 
250
session_open(CM, TMO) ->
 
251
    session_open(CM, ?DEFAULT_WINDOW_SIZE, ?DEFAULT_PACKET_SIZE, TMO).
 
252
 
 
253
session_open(CM, InitialWindowSize, MaxPacketSize, TMO) ->
 
254
    case gen_server:call(CM, {open, self(), "session",
 
255
                              InitialWindowSize, MaxPacketSize, <<>>}, TMO) of
 
256
        {open, C} -> {ok, C};
 
257
        Error -> Error
 
258
    end.
 
259
 
 
260
direct_tcpip(CM, RemoteHost, RemotePort, OrigIP, OrigPort, TMO) ->
 
261
    direct_tcpip(CM, RemoteHost, RemotePort, OrigIP, OrigPort,
 
262
                 ?DEFAULT_WINDOW_SIZE, ?DEFAULT_PACKET_SIZE, TMO).
 
263
 
 
264
direct_tcpip(CM, RemoteIP, RemotePort, OrigIP, OrigPort,
 
265
             InitialWindowSize, MaxPacketSize, TMO) ->
 
266
    case {encode_ip(RemoteIP), encode_ip(OrigIP)} of
 
267
        {false, _} -> {error, einval};
 
268
        {_, false} -> {error, einval};
 
269
        {RIP, OIP} ->
 
270
            gen_server:call(CM, {open, self(), "direct-tcpip", 
 
271
                                 InitialWindowSize, MaxPacketSize,
 
272
                                 [?string(RIP), ?uint32(RemotePort),
 
273
                                  ?string(OIP), ?uint32(OrigPort)] }, TMO)
 
274
%%%         receive
 
275
%%%             {ssh_cm, CM, {open, Channel}} ->
 
276
%%%                 {ok, Channel};
 
277
%%%             {ssh_cm, CM, {open_error, _Reason, Descr, _Lang}} ->
 
278
%%%                 {error, Descr}
 
279
%%%         end
 
280
    end.
 
281
 
 
282
tcpip_forward(CM, BindIP, BindPort)                                        ->
 
283
    case encode_ip(BindIP) of
 
284
        false -> {error, einval};
 
285
        IPStr ->
 
286
            global_request(CM, "tcpip-forward", true,
 
287
                           [?string(IPStr),
 
288
                            ?uint32(BindPort)])
 
289
    end.
 
290
 
 
291
cancel_tcpip_forward(CM, BindIP, Port) ->
 
292
    case encode_ip(BindIP) of
 
293
        false -> {error, einval};
 
294
        IPStr ->
 
295
            global_request(CM, "cancel-tcpip-forward", true,
 
296
                           [?string(IPStr),
 
297
                            ?uint32(Port)])
 
298
    end.
 
299
 
 
300
open_pty(CM, Channel, TMO) ->
 
301
    open_pty(CM, Channel, os:getenv("TERM"), 80, 24, [], TMO).
 
302
 
 
303
open_pty(CM, Channel, Term, Width, Height, PtyOpts, TMO) ->
 
304
    open_pty(CM, Channel, Term, Width, Height, 0, 0, PtyOpts, TMO).
 
305
 
 
306
 
 
307
open_pty(CM, Channel, Term, Width, Height, PixWidth, PixHeight, PtyOpts, TMO) ->
 
308
    request(CM, Channel, "pty-req", true, 
 
309
            [?string(Term),
 
310
             ?uint32(Width), ?uint32(Height),
 
311
             ?uint32(PixWidth),?uint32(PixHeight),
 
312
             encode_pty_opts(PtyOpts)], TMO).
 
313
 
 
314
setenv(CM, Channel, Var, Value, TMO) ->
 
315
    request(CM, Channel, "env", true, [?string(Var), ?string(Value)], TMO).
 
316
 
 
317
shell(CM, Channel) ->
 
318
    request(CM, Channel, "shell", false, <<>>, 0).
 
319
 
 
320
exec(CM, Channel, Command, TMO) ->
 
321
    request(CM, Channel, "exec", true, [?string(Command)], TMO).
 
322
 
 
323
subsystem(CM, Channel, SubSystem, TMO) ->
 
324
    request(CM, Channel, "subsystem", true, [?string(SubSystem)], TMO).
 
325
 
 
326
winch(CM, Channel, Width, Height) ->
 
327
    winch(CM, Channel, Width, Height, 0, 0).
 
328
winch(CM, Channel, Width, Height, PixWidth, PixHeight)                     ->
 
329
    request(CM, Channel, "window-change", false, 
 
330
            [?uint32(Width), ?uint32(Height),
 
331
             ?uint32(PixWidth), ?uint32(PixHeight)], 0).
 
332
 
 
333
signal(CM, Channel, Sig)                                                   ->
 
334
    request(CM, Channel, "signal", false,
 
335
            [?string(Sig)], 0).
 
336
 
 
337
attach(CM, TMO) ->
 
338
    gen_server:call(CM, {attach, self()}, TMO).
 
339
 
 
340
detach(CM, TMO) ->
 
341
    gen_server:call(CM, {detach, self()}, TMO).
 
342
 
 
343
 
 
344
renegotiate(CM) ->
 
345
    renegotiate(CM,[]).
 
346
renegotiate(CM,Opts) ->
 
347
    gen_server:cast(CM, {renegotiate,Opts}).
 
348
 
 
349
%% Setup user ack on data messages (i.e signal when the data has been sent)
 
350
set_user_ack(CM, Channel, Ack, TMO) ->
 
351
    gen_server:call(CM, {set_user_ack, Channel, Ack}, TMO).
 
352
 
 
353
get_authhandle(CM) ->
 
354
    gen_server:call(CM, get_authhandle).
 
355
 
 
356
get_peer_addr(CM) ->
 
357
    gen_server:call(CM, get_peer_addr).
 
358
 
 
359
set_user(CM, Channel, User, TMO) ->
 
360
    gen_server:call(CM, {set_user, Channel, User}, TMO).
 
361
 
 
362
send_window(CM, Channel, TMO) ->
 
363
    gen_server:call(CM, {send_window, Channel}, TMO).
 
364
 
 
365
recv_window(CM, Channel, TMO) ->
 
366
    gen_server:call(CM, {recv_window, Channel}, TMO).
 
367
 
 
368
adjust_window(CM, Channel, Bytes) ->
 
369
    gen_server:cast(CM, {adjust_window, Channel, Bytes}).
 
370
 
 
371
close(CM, Channel) ->
 
372
    gen_server:cast(CM, {close, Channel}).
 
373
 
 
374
stop(CM) ->
 
375
    gen_server:call(CM, stop).
 
376
 
 
377
send_eof(CM, Channel)                                                      ->
 
378
    gen_server:cast(CM, {eof, Channel}).
 
379
 
 
380
send(CM, Channel, Data)                                                    ->
 
381
    CM ! {ssh_cm, self(), {data, Channel, 0, Data}}.
 
382
 
 
383
send(CM, Channel, Type, Data)                                              ->
 
384
    CM ! {ssh_cm, self(), {data, Channel, Type, Data}}.
 
385
 
 
386
send_ack(CM, Channel, Data) ->
 
387
    send_ack(CM, Channel, 0, Data, infinity).
 
388
 
 
389
send_ack(CM, Channel, Type, Data) ->
 
390
    send_ack(CM, Channel, Type, Data, infinity).
 
391
 
 
392
send_ack(CM, Channel, Type, Data, Timeout) ->
 
393
    send(CM, Channel, Type, Data),
 
394
    receive
 
395
        {ssh_cm, CM, {ack, Channel}} ->
 
396
            ok
 
397
    after Timeout ->
 
398
            {error, timeout}
 
399
    end.
 
400
 
 
401
request(CM, Channel, Type, Reply, Data, TMO) ->
 
402
    case Reply of
 
403
        true -> gen_server:call(CM, {request, Channel, Type, Data}, TMO);
 
404
        false -> gen_server:cast(CM, {request, Channel, Type, Data})
 
405
    end.
 
406
 
 
407
global_request(CM, Type, Reply, Data) ->
 
408
    CM ! {ssh_cm, self(), {global_request,self(),Type,Reply,Data}},
 
409
    if Reply == true ->
 
410
            receive
 
411
                {ssh_cm, CM, {success, _Channel}} ->
 
412
                    ok;
 
413
                {ssh_cm, CM, {failure, _Channel}} ->
 
414
                    error
 
415
            end;
 
416
       true ->
 
417
            ok
 
418
    end.
 
419
 
 
420
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
421
%%
 
422
%% CM command encode/decode table
 
423
%%
 
424
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
425
 
 
426
connect_messages() ->
 
427
    [ {ssh_msg_global_request, ?SSH_MSG_GLOBAL_REQUEST,
 
428
       [string, 
 
429
        boolean,
 
430
        '...']},
 
431
 
 
432
      {ssh_msg_request_success, ?SSH_MSG_REQUEST_SUCCESS,
 
433
       ['...']},
 
434
 
 
435
      {ssh_msg_request_failure, ?SSH_MSG_REQUEST_FAILURE,
 
436
       []},
 
437
      
 
438
      {ssh_msg_channel_open, ?SSH_MSG_CHANNEL_OPEN,
 
439
       [string,
 
440
        uint32,
 
441
        uint32,
 
442
        uint32,
 
443
        '...']},
 
444
 
 
445
      {ssh_msg_channel_open_confirmation, ?SSH_MSG_CHANNEL_OPEN_CONFIRMATION,
 
446
       [uint32,
 
447
        uint32,
 
448
        uint32,
 
449
        uint32,
 
450
        '...']},
 
451
 
 
452
      {ssh_msg_channel_open_failure, ?SSH_MSG_CHANNEL_OPEN_FAILURE,
 
453
       [uint32,
 
454
        uint32,
 
455
        string,
 
456
        string]},
 
457
 
 
458
      {ssh_msg_channel_window_adjust, ?SSH_MSG_CHANNEL_WINDOW_ADJUST,
 
459
       [uint32,
 
460
        uint32]},
 
461
 
 
462
      {ssh_msg_channel_data, ?SSH_MSG_CHANNEL_DATA,
 
463
       [uint32,
 
464
        binary]},
 
465
 
 
466
      {ssh_msg_channel_extended_data, ?SSH_MSG_CHANNEL_EXTENDED_DATA,
 
467
       [uint32,
 
468
        uint32,
 
469
        binary]},
 
470
 
 
471
      {ssh_msg_channel_eof, ?SSH_MSG_CHANNEL_EOF,
 
472
       [uint32]},
 
473
 
 
474
      {ssh_msg_channel_close, ?SSH_MSG_CHANNEL_CLOSE,
 
475
       [uint32]},
 
476
 
 
477
      {ssh_msg_channel_request, ?SSH_MSG_CHANNEL_REQUEST,
 
478
       [uint32,
 
479
        string,
 
480
        boolean,
 
481
        '...']},
 
482
 
 
483
      {ssh_msg_channel_success, ?SSH_MSG_CHANNEL_SUCCESS,
 
484
       [uint32]},
 
485
 
 
486
      {ssh_msg_channel_failure, ?SSH_MSG_CHANNEL_FAILURE,
 
487
       [uint32]}
 
488
     ].
 
489
 
 
490
 
 
491
%%--------------------------------------------------------------------
 
492
%% Function: handle_cast/2
 
493
%% Description: Handling cast messages
 
494
%% Returns: {noreply, State}          |
 
495
%%          {noreply, State, Timeout} |
 
496
%%          {stop, Reason, State}            (terminate/2 is called)
 
497
%%--------------------------------------------------------------------
 
498
handle_cast({request, Channel, Type, Data}, State) ->
 
499
    {noreply, do_request(Channel, Type, Data, false, undefined, State)};
 
500
handle_cast({renegotiate, Opts}, State) ->
 
501
    State#state.ssh ! {ssh_renegotiate, false, Opts},
 
502
    {noreply, State};
 
503
handle_cast({adjust_window, Channel, Bytes}, State) ->
 
504
    #state{ssh = SSH, ctab = CTab} = State,
 
505
    with_channel(
 
506
      State, Channel,
 
507
      fun(C) ->
 
508
              WSz = C#channel.recv_window_size + Bytes,
 
509
              channel_adjust_window(SSH, C#channel.remote_id, Bytes),
 
510
              ets:insert(CTab, C#channel { recv_window_size = WSz})
 
511
      end),
 
512
    {noreply, State};
 
513
handle_cast({close, Channel}, State) ->
 
514
    #state{ssh = SSH, ctab = CTab} = State,
 
515
    with_channel(State, Channel,
 
516
                 fun(C) ->
 
517
                         channel_close(SSH, C#channel.remote_id),
 
518
                         ets:insert(CTab, C#channel{sent_close = true})
 
519
                 end),
 
520
    {noreply, State};
 
521
handle_cast({eof, Channel}, State) ->
 
522
    %%#state{ssh = SSH, ctab = _CTab} = State,
 
523
    SSH = State#state.ssh,
 
524
    with_channel(State, Channel,
 
525
                 fun(C) ->
 
526
                         channel_eof(SSH,  C#channel.remote_id)%,
 
527
                         %%ets:insert(CTab, C#channel{sent_eof = true})
 
528
                 end),
 
529
    {noreply, State};
 
530
handle_cast(_Cast, State) ->
 
531
    ?dbg(true, "handle_cast: BAD cast ~p\n(State ~p)\n", [_Cast, State]),
 
532
    {noreply, State}.
 
533
 
 
534
%%--------------------------------------------------------------------
 
535
%% Function: handle_info(Info, State) -> {noreply, State} |
 
536
%%                                       {noreply, State, Timeout} |
 
537
%%                                       {stop, Reason, State}
 
538
%% Description: Handling all non call/cast messages
 
539
%%--------------------------------------------------------------------
 
540
handle_info({ssh_msg,SSH,#ssh_msg_service_request{name="ssh-userauth"}},
 
541
            State) when State#state.role == server->
 
542
    case ssh_userauth:auth_remote(SSH, "ssh-connection", State#state.opts) of
 
543
        {ok, Handle} ->
 
544
            {noreply, State#state{authhandle = Handle}};
 
545
        _Error ->
 
546
            ssh_transport:disconnect(SSH, ?SSH_DISCONNECT_BY_APPLICATION),
 
547
            %{stop, {error, Error}, State}
 
548
            {stop, shutdown, State}
 
549
    end;
 
550
handle_info({ssh_msg, SSH, Msg}, State)                                    ->
 
551
    %%SSH = State#state.ssh,
 
552
    ?dbg(?DBG_SSHMSG, "handle_info<~p>: ssh_msg ~p\n", [SSH, Msg]),
 
553
    case ssh_message(SSH, Msg, State) of
 
554
        {disconnected, _Reason} ->
 
555
            ssh_userauth:disconnect(State#state.authhandle, State#state.opts),
 
556
            %{stop, {error, {disconnected, Reason}}, State};
 
557
            {stop, shutdown, State};
 
558
        NewState ->
 
559
            {noreply, NewState}
 
560
    end;
 
561
handle_info({ssh_cm, Sender, Msg}, State)                                  ->
 
562
    SSH = State#state.ssh,
 
563
    ?dbg(?DBG_SSHCM, "handle_info<~p>: sender=~p, ssh_cm ~p\n", [SSH, Sender, Msg]),
 
564
    %% only allow attached users (+ initial user)
 
565
    NewState = case is_user(Sender, State) of
 
566
                   false -> 
 
567
                       State;
 
568
                   true ->
 
569
                       cm_message(SSH, Msg, State)
 
570
               end,
 
571
    {noreply, NewState};
 
572
handle_info({'EXIT', SSH, Reason}, State) when SSH == State#state.ssh      ->
 
573
    error_logger:format("SSH_CM ~p EXIT ~p\n", [SSH, Reason]),
 
574
    {noreply, State};
 
575
handle_info({'EXIT', _Pid, normal}, State)                                  ->
 
576
    {noreply, State};
 
577
handle_info({'EXIT', _Pid, shutdown}, State)                                  ->
 
578
    {noreply, State};
 
579
handle_info({'EXIT', Pid, Reason}, State)                                  ->
 
580
    error_logger:format("ssh_cm: Pid ~p EXIT ~p\n", [Pid, Reason]),
 
581
    {noreply, State};
 
582
 
 
583
handle_info({'DOWN', _Ref, process, Pid, normal}, State)                   ->
 
584
    NewState = down_user(Pid, State),
 
585
    {noreply, NewState};
 
586
handle_info({'DOWN', _Ref, process, Pid, Reason}, State)                   ->
 
587
    error_logger:format("Pid ~p DOWN ~p\n", [Pid, Reason]),
 
588
    NewState = down_user(Pid, State),
 
589
    {noreply, NewState};
 
590
 
 
591
 
 
592
handle_info(_Info, State)                                                   ->
 
593
    ?dbg(true, "ssh_cm:handle_info: BAD info ~p\n(State ~p)\n", [_Info, State]),
 
594
    {noreply, State}.
 
595
 
 
596
%%--------------------------------------------------------------------
 
597
%% Function: %% handle_call(Request, From, State) -> {reply, Reply, State} |
 
598
%%                                      {reply, Reply, State, Timeout} |
 
599
%%                                      {noreply, State} |
 
600
%%                                      {noreply, State, Timeout} |
 
601
%%                                      {stop, Reason, Reply, State} |
 
602
%%                                      {stop, Reason, State}
 
603
%% Description: Handling call messages
 
604
%%--------------------------------------------------------------------
 
605
handle_call({attach, User}, _From, State) ->
 
606
    {reply, ok, add_user(User, State)};
 
607
handle_call({detach, User}, _From, State) ->
 
608
    {reply, ok, del_user(User, State)};
 
609
handle_call({send_window, Channel}, _From, State)                          ->
 
610
    Reply = case ets:lookup(State#state.ctab, Channel) of
 
611
                [C] ->
 
612
                    {ok, {C#channel.send_window_size,
 
613
                          C#channel.send_packet_size}};
 
614
                [] -> 
 
615
                    {error, einval}
 
616
            end,
 
617
    {reply, Reply, State};
 
618
handle_call({request, Channel, Type, Data}, From, State) ->
 
619
    {noreply, do_request(Channel, Type, Data, true, From, State)};
 
620
handle_call({recv_window, Channel}, _From, State) ->
 
621
    Reply = case ets:lookup(State#state.ctab, Channel) of
 
622
                [C] ->
 
623
                    {ok, {C#channel.recv_window_size,
 
624
                          C#channel.recv_packet_size}};
 
625
                [] -> 
 
626
                    {error, einval}
 
627
            end,
 
628
    {reply, Reply, State};
 
629
handle_call({set_user, Channel, User}, _From, State) ->
 
630
    Reply = case is_user(User, State) of
 
631
                false -> {error, einval};
 
632
                true ->
 
633
                    CTab = State#state.ctab,
 
634
                    case ets:lookup(CTab, Channel) of
 
635
                        [C] ->
 
636
                            ets:insert(CTab, C#channel { user = User }),
 
637
                            ok;
 
638
                        [] -> 
 
639
                            {error, einval}
 
640
                    end
 
641
            end,
 
642
    {reply, Reply, State};
 
643
handle_call(get_authhandle, _From, State) ->
 
644
    {reply, {State#state.authhandle,State#state.ssh}, State};
 
645
handle_call(get_peer_addr, _From, State) ->
 
646
    {reply, ssh_transport:peername(State#state.ssh), State};
 
647
handle_call({set_user_ack, Channel,Ack}, _From, State) ->
 
648
    CTab = State#state.ctab,
 
649
    Reply = case ets:lookup(CTab, Channel) of
 
650
                [C] ->
 
651
                    ets:insert(CTab, C#channel { user_ack = Ack }),
 
652
                    ok;
 
653
                [] -> 
 
654
                    {error, einval}
 
655
            end,
 
656
    {reply, Reply, State};
 
657
handle_call({info,User}, _From, State) ->
 
658
    Result = ets:foldl(
 
659
               fun(C, Acc) when User == all; C#channel.user == User ->
 
660
                       [C | Acc];
 
661
                  (_, Acc) ->
 
662
                       Acc
 
663
               end, [], State#state.ctab),
 
664
    {reply, {ok, Result}, State};
 
665
handle_call({open, User, Type, InitialWindowSize, MaxPacketSize, Data}, From, State) ->
 
666
        case is_user(User, State) of
 
667
            false -> 
 
668
                {reply, {error, einval}, State};
 
669
            true ->
 
670
                {Channel, State1}  = new_channel_id(State),
 
671
                channel_open(State#state.ssh, Type, Channel, InitialWindowSize,
 
672
                             MaxPacketSize, Data),
 
673
                C = #channel { type = Type,
 
674
                               sys = "none",
 
675
                               user = User,
 
676
                               local_id = Channel,
 
677
                               recv_window_size = InitialWindowSize,
 
678
                               recv_packet_size = MaxPacketSize },
 
679
                ets:insert(State#state.ctab, C),
 
680
                State2 = add_request(true, Channel, From, State1),
 
681
                {noreply, State2}
 
682
        end;
 
683
handle_call(stop, _From, State) ->
 
684
    ssh_userauth:disconnect(State#state.authhandle, State#state.opts),
 
685
    ssh_transport:close(State#state.ssh),
 
686
    {stop, normal, ok, State};
 
687
handle_call(_Call, _From, State) ->
 
688
    ?dbg(true, "handle_call: BAD call ~p\n(State ~p)\n", [_Call, State]),
 
689
    {reply, {error, bad_call}, State}.
 
690
 
 
691
 
 
692
%%--------------------------------------------------------------------
 
693
%% Function: terminate/2
 
694
%% Description: Shutdown the server
 
695
%% Returns: any (ignored by gen_server)
 
696
%%--------------------------------------------------------------------
 
697
terminate(_Reason, _State) ->
 
698
    ok.
 
699
 
 
700
%%--------------------------------------------------------------------
 
701
%% Func: code_change/3
 
702
%% Purpose: Convert process state when code is changed
 
703
%% Returns: {ok, NewState}
 
704
%%--------------------------------------------------------------------
 
705
code_change(_OldVsn, State, _Extra) ->
 
706
    {ok, State}.
 
707
 
 
708
 
 
709
%%--------------------------------------------------------------------
 
710
%%% Internal functions
 
711
%%--------------------------------------------------------------------
 
712
ssh_message(SSH, Msg, State) ->
 
713
    CTab = State#state.ctab,
 
714
    case Msg of
 
715
        #ssh_msg_channel_open_confirmation { recipient_channel = Channel,
 
716
                                             sender_channel = RID,
 
717
                                             initial_window_size = WindowSz,
 
718
                                             maximum_packet_size = PacketSz
 
719
                                            } ->
 
720
            with_channel(State, Channel,
 
721
                         fun(C) ->
 
722
                                 if C#channel.remote_id == undefined ->
 
723
                                         ets:insert(CTab, C#channel {
 
724
                                                            remote_id = RID,
 
725
                                                            send_window_size = WindowSz,
 
726
                                                            send_packet_size = PacketSz });
 
727
                                    true ->
 
728
                                         ignore
 
729
                                 end
 
730
                         end),
 
731
            reply_request(Channel, {open, Channel}, State);
 
732
 
 
733
        #ssh_msg_channel_open_failure { recipient_channel = Channel,
 
734
                                        reason = Reason,
 
735
                                        description = Descr,
 
736
                                        lang = Lang } ->
 
737
            with_channel(State, Channel,
 
738
                         fun() ->
 
739
                                 ets:delete(CTab, Channel)
 
740
                         end),
 
741
            reply_request(Channel, {open_error, Reason, Descr, Lang}, State);
 
742
 
 
743
        #ssh_msg_channel_success { recipient_channel = Channel } ->
 
744
            reply_request(Channel, success, State);
 
745
 
 
746
        #ssh_msg_channel_failure { recipient_channel = Channel} ->
 
747
            reply_request(Channel, failure, State);
 
748
            
 
749
        #ssh_msg_channel_eof { recipient_channel = Channel} ->
 
750
            with_channel(State, Channel,
 
751
                         fun(C) ->
 
752
                                 send_user(C, {eof, Channel})
 
753
%%                               if C#channel.sent_eof == true ->
 
754
%%                                       reply_request(C#channel.local_id,
 
755
%%                                                     closed, State),
 
756
%%                                       io:format("delete Channel b ~p\n", [Channel]),
 
757
%%                                       ets:delete(CTab, Channel);
 
758
%%                                  true ->
 
759
%%                                       ets:insert(CTab, C#channel { recv_eof = true })
 
760
%%                               end
 
761
                         end);
 
762
 
 
763
        #ssh_msg_channel_close { recipient_channel = Channel } ->
 
764
            with_channel(State, Channel,
 
765
                         fun(C) ->
 
766
                                 if C#channel.sent_close == false ->
 
767
                                         channel_close(SSH,C#channel.remote_id),
 
768
                                         reply_request(C#channel.local_id,
 
769
                                                       closed, State);
 
770
                                    true -> 
 
771
                                         ok
 
772
                                 end,
 
773
                                 ets:delete(CTab, Channel)
 
774
                         end),
 
775
            reply_request(Channel, closed, State);
 
776
 
 
777
        #ssh_msg_channel_data { recipient_channel = Channel,
 
778
                                data = Data } ->
 
779
            with_channel(State, Channel,
 
780
                         fun(C) ->
 
781
                                 WSz = C#channel.recv_window_size - size(Data),
 
782
                                 send_user(C, {data, Channel, 0, Data}),
 
783
                                 ets:insert(CTab, C#channel { recv_window_size = WSz})
 
784
                         end);
 
785
 
 
786
        #ssh_msg_channel_extended_data { recipient_channel = Channel,
 
787
                                         data_type_code = DataType,
 
788
                                         data = Data} ->
 
789
            with_channel(State, Channel,
 
790
                         fun(C) ->
 
791
                                 WSz = C#channel.recv_window_size - size(Data),
 
792
                                 send_user(C, {data, Channel, DataType, Data}),
 
793
                                 ets:insert(CTab, C#channel { recv_window_size = WSz})
 
794
                         end);
 
795
 
 
796
        #ssh_msg_channel_window_adjust { recipient_channel = Channel,
 
797
                                         bytes_to_add = Add } ->
 
798
            with_channel(State, Channel, 
 
799
                         fun(C) -> 
 
800
                                 update_send_window(SSH, CTab, C, Add) 
 
801
                         end);
 
802
 
 
803
        #ssh_msg_channel_open { channel_type = Type,
 
804
                                sender_channel = RID,
 
805
                                initial_window_size = RWindowSz,
 
806
                                maximum_packet_size = RPacketSz,
 
807
                                data = Data } ->
 
808
            case Type of
 
809
                "session" ->
 
810
                    %% FIXME: check that we requested this !
 
811
                    %% (install a listener & user somehow)
 
812
%                   <<?UINT32(ALen), Address:ALen/binary, ?UINT32(Port),
 
813
%                    ?UINT32(OLen), Orig:OLen/binary, ?UINT32(OrigPort)>> = Data,
 
814
                    case State#state.users of
 
815
                        [{User,_}|_] ->
 
816
                            {Channel, NewState} = new_channel_id(State),
 
817
                            LWindowSz = ?DEFAULT_WINDOW_SIZE,
 
818
                            LPacketSz = ?DEFAULT_PACKET_SIZE,
 
819
                            C = #channel { type = Type,
 
820
                                           sys = "ssh",
 
821
                                           user = User,
 
822
                                           local_id = Channel,
 
823
                                           recv_window_size = LWindowSz,
 
824
                                           recv_packet_size = LPacketSz,
 
825
                                           send_window_size = RWindowSz,
 
826
                                           send_packet_size = RPacketSz,
 
827
                                           remote_id = RID},
 
828
                            ets:insert(CTab, C),
 
829
                            channel_open_confirmation(SSH, RID, Channel,
 
830
                                                      LWindowSz, LPacketSz),
 
831
                            send_user(C, {open, Channel, RID, {session}}),
 
832
                            NewState;
 
833
                        _ ->
 
834
                            channel_open_failure(SSH, RID, 
 
835
                                                 ?SSH_OPEN_CONNECT_FAILED,
 
836
                                                 "Connection refused", "en"),
 
837
                            State
 
838
                    end;
 
839
                    
 
840
                "forwarded-tcpip" ->
 
841
                    %% FIXME: check that we requested this !
 
842
                    %% (install a listener & user somehow)
 
843
                    <<?UINT32(ALen), Address:ALen/binary, ?UINT32(Port),
 
844
                     ?UINT32(OLen), Orig:OLen/binary, ?UINT32(OrigPort)>> = Data,
 
845
                    case get_bind(Address, Port, State) of
 
846
                        undefined ->
 
847
                            channel_open_failure(SSH, RID, 
 
848
                                                 ?SSH_OPEN_CONNECT_FAILED,
 
849
                                                 "Connection refused", "en"),
 
850
                            State;
 
851
                        User ->
 
852
                            {Channel, NewState} = new_channel_id(State),
 
853
                            LWindowSz = ?DEFAULT_WINDOW_SIZE,
 
854
                            LPacketSz = ?DEFAULT_PACKET_SIZE,
 
855
                            C = #channel { type = Type,
 
856
                                           sys = "none",
 
857
                                           user = User,
 
858
                                           local_id = Channel,
 
859
                                           recv_window_size = LWindowSz,
 
860
                                           recv_packet_size = LPacketSz,
 
861
                                           send_window_size = RWindowSz,
 
862
                                           send_packet_size = RPacketSz },
 
863
                            ets:insert(CTab, C),
 
864
                            channel_open_confirmation(SSH, RID, Channel,
 
865
                                                      LWindowSz, LPacketSz),
 
866
                            send_user(C, {open, Channel, {forwarded_tcpip,
 
867
                                                          decode_ip(Address), Port,
 
868
                                                          decode_ip(Orig), OrigPort}}),
 
869
                            NewState
 
870
                    end;
 
871
                _ ->
 
872
                    channel_open_failure(SSH, RID, 
 
873
                                         ?SSH_OPEN_ADMINISTRATIVELY_PROHIBITED,
 
874
                                         "Not allowed", "en"),
 
875
                    State
 
876
            end;
 
877
 
 
878
        #ssh_msg_channel_request { recipient_channel = Channel,
 
879
                                   request_type = Type,
 
880
                                   want_reply = WantReply,
 
881
                                   data = Data } ->
 
882
            case Type of
 
883
                "exit-status" ->
 
884
                    <<?UINT32(Status)>> = Data,
 
885
                    send_user(CTab, Channel, {exit_status,Channel,Status});
 
886
                "exit-signal" ->
 
887
                    <<?UINT32(SigLen), SigName:SigLen/binary,
 
888
                     ?BOOLEAN(_Core), 
 
889
                     ?UINT32(ErrLen), Err:ErrLen/binary,
 
890
                     ?UINT32(LangLen), Lang:LangLen/binary>> = Data,
 
891
                    send_user(CTab, Channel, {exit_signal, Channel,
 
892
                                              binary_to_list(SigName),
 
893
                                              binary_to_list(Err),
 
894
                                              binary_to_list(Lang)});
 
895
                "xon-xoff" ->
 
896
                    <<?BOOLEAN(CDo)>> = Data,
 
897
                    send_user(CTab, Channel, {xon_xoff, Channel, CDo=/= 0});
 
898
                
 
899
                "window-change" ->
 
900
                    <<?UINT32(Width),?UINT32(Height),
 
901
                     ?UINT32(PixWidth), ?UINT32(PixHeight)>> = Data,
 
902
                    send_user(CTab, Channel, {window_change,Channel,
 
903
                                              Width, Height,
 
904
                                              PixWidth, PixHeight});
 
905
                "signal" ->
 
906
                    <<?UINT32(SigLen), SigName:SigLen/binary>> = Data,
 
907
                    send_user(CTab, Channel, {signal,Channel,
 
908
                                              binary_to_list(SigName)});
 
909
                "subsystem" ->
 
910
                    <<?UINT32(SsLen), SsName:SsLen/binary>> = Data,
 
911
                    send_user(CTab, Channel, {subsystem,Channel, WantReply,
 
912
                                              binary_to_list(SsName)});
 
913
                "pty-req" ->
 
914
                    <<?UINT32(TermLen), BTermName:TermLen/binary,
 
915
                     ?UINT32(Width),?UINT32(Height),
 
916
                     ?UINT32(PixWidth), ?UINT32(PixHeight),
 
917
                     Modes/binary>> = Data,
 
918
                    TermName = binary_to_list(BTermName),
 
919
                    ?dbg(?DBG_USER, "ssh_msg pty-req: TermName=~p Modes=~p\n", [TermName, Modes]),
 
920
                    Pty = #ssh_pty{term = TermName,
 
921
                                   width = not_zero(Width, 80),
 
922
                                   height = not_zero(Height, 24),
 
923
                                   pixel_width = PixWidth,
 
924
                                   pixel_height = PixHeight,
 
925
                                   modes = decode_pty_opts(Modes)},
 
926
                    send_user(CTab, Channel, {pty, Channel, WantReply, Pty});
 
927
 
 
928
                "shell" ->
 
929
                    send_user(CTab, Channel, {shell});
 
930
 
 
931
                "exec" ->
 
932
                    <<?UINT32(Len), Command:Len/binary>> = Data,
 
933
                    send_user(CTab, Channel, {exec, binary_to_list(Command)});
 
934
 
 
935
                _Other ->
 
936
                    ?dbg(true, "ssh_msg ssh_msg_channel_request: Other=~p\n",
 
937
                         [_Other]),
 
938
                    if WantReply == true ->
 
939
                            channel_failure(SSH, Channel);
 
940
                       true ->
 
941
                            ignore
 
942
                    end
 
943
            end,
 
944
            State;
 
945
            
 
946
        #ssh_msg_global_request { name = _Type,
 
947
                                  want_reply = WantReply,
 
948
                                  data = _Data } ->
 
949
            if WantReply == true ->
 
950
                    request_failure(SSH);
 
951
               true ->
 
952
                    ignore
 
953
            end,
 
954
            State;
 
955
        
 
956
 
 
957
        #ssh_msg_disconnect { code = Code,
 
958
                              description = Description,
 
959
                              language = _Lang } ->
 
960
            %% close all channels
 
961
            ets:foldl(
 
962
              fun(C, _) ->
 
963
                      reply_request(C#channel.local_id, closed, State)
 
964
              end, ok, CTab),
 
965
            ets:delete(CTab),
 
966
            {disconnected, {Code, Description}};
 
967
 
 
968
        _ ->
 
969
            ?dbg(true, "ssh_connection: ~p\n", [Msg]),
 
970
            State
 
971
    end.
 
972
 
 
973
cm_message(SSH, Msg, State) ->
 
974
    CTab = State#state.ctab,
 
975
    case Msg of
 
976
        {data, Channel, Type, Data} ->
 
977
            send_data(SSH, CTab, Channel, Type, Data),
 
978
            State;
 
979
 
 
980
        {global_request, User, Type, WantReply, Data} ->
 
981
            case Type of
 
982
                "tcpip-forward" ->
 
983
                    <<?UINT32(IPLen), IP:IPLen/binary, ?UINT32(Port)>> = Data,
 
984
                    State1 = add_user(User, State),  %% auto attach user
 
985
                    State2 = put_bind(IP, Port, User, State1),
 
986
                    send_global_request(SSH, Type, WantReply, Data),
 
987
                    State2;
 
988
                "cancel-tcpip-forward" ->
 
989
                    <<?UINT32(IPLen), IP:IPLen/binary, ?UINT32(Port)>> = Data,
 
990
                    %% note can not erase user!
 
991
                    send_global_request(SSH, Type, WantReply, Data),
 
992
                    del_bind(IP, Port, State);
 
993
                _ ->
 
994
                    send_global_request(SSH, Type, WantReply, Data),
 
995
                    State
 
996
            end;
 
997
 
 
998
        {success, Channel} ->
 
999
            channel_success(SSH, Channel),
 
1000
            State;
 
1001
 
 
1002
        _ ->
 
1003
            ?dbg(true, "ssh_connection: ~p\n", [Msg]),
 
1004
            State
 
1005
    end.
 
1006
 
 
1007
update_sys(CTab, C, Type) ->
 
1008
    case Type of
 
1009
        "subsystem" ->
 
1010
            ets:insert(CTab, C#channel { sys = "subsystem" });
 
1011
        "exec" -> 
 
1012
            ets:insert(CTab, C#channel { sys = "subsystem" });
 
1013
        "shell" -> 
 
1014
            ets:insert(CTab, C#channel { sys = "shell" });
 
1015
        _ ->
 
1016
            ok
 
1017
    end.
 
1018
 
 
1019
user_auth(SSH, Opts) ->
 
1020
    case ssh_transport:service_request(SSH, "ssh-userauth") of
 
1021
        ok ->
 
1022
            ssh_userauth:auth(SSH, "ssh-connection", Opts);
 
1023
        Error ->
 
1024
            Error
 
1025
    end.
 
1026
 
 
1027
%% User is down
 
1028
down_user(User, State) ->
 
1029
    #state{ctab = CTab, ssh = SSH} = State,
 
1030
    case is_user(User, State) of
 
1031
        true ->
 
1032
            ets:foldl(
 
1033
              fun(C, _) when C#channel.user == User ->
 
1034
                      channel_close(SSH,  C#channel.remote_id),
 
1035
                      ets:delete(CTab, C#channel.local_id);
 
1036
                 (_C, _) ->
 
1037
                      ok
 
1038
              end, ok, CTab),
 
1039
            del_user(User, State);
 
1040
        false ->
 
1041
            State
 
1042
    end.
 
1043
 
 
1044
%% reply to request, or send to user, depending on whether the
 
1045
%% Channel is in requests
 
1046
reply_request(Channel, Reply, State) ->
 
1047
    #state{ctab = CTab, requests = Requests} = State,
 
1048
    case lists:keysearch(Channel, 1, Requests) of
 
1049
        {value, {Channel, From}} ->
 
1050
            gen_server:reply(From, Reply),
 
1051
            State#state{requests = lists:keydelete(Channel, 1, Requests)};
 
1052
        false ->
 
1053
            send_user(CTab, Channel, {Reply, Channel}),
 
1054
            State
 
1055
    end.
 
1056
 
 
1057
%% Send ssh_cm messages to the 'user'
 
1058
send_user(C, Msg) when record(C, channel) ->
 
1059
    C#channel.user ! {ssh_cm, self(), Msg}.
 
1060
 
 
1061
send_user(CTab, Channel, Msg) ->
 
1062
    case ets:lookup(CTab, Channel) of
 
1063
        [C] ->
 
1064
            send_user(C, Msg);
 
1065
        [] ->
 
1066
            ignore
 
1067
    end.
 
1068
 
 
1069
%% Update the send window with Data
 
1070
%% adjust output window
 
1071
%%
 
1072
%% buffer is on form [{DataType,UserAck,User,Data}]
 
1073
%% DataType = 0   regular data
 
1074
%%            1   stderr data
 
1075
%% UserAck = true if "User" wants ack when data was sent
 
1076
%% Data = io-list
 
1077
%%
 
1078
send_data(SSH, CTab, LID, DataType, Data0) ->
 
1079
    case ets:lookup(CTab, LID) of
 
1080
        [C] ->
 
1081
            Data = if binary(Data0) -> Data0;
 
1082
                      list(Data0) -> list_to_binary(Data0)
 
1083
                   end,
 
1084
            send_window(SSH,CTab,C, DataType,
 
1085
                        C#channel.user_ack, C#channel.user,
 
1086
                        Data);
 
1087
        [] ->
 
1088
            ignore
 
1089
    end.
 
1090
 
 
1091
update_send_window(SSH, CTab, C, Bytes) ->
 
1092
    WSz0 = C#channel.send_window_size,
 
1093
    send_window(SSH, CTab, C#channel { send_window_size = WSz0+Bytes},
 
1094
                0, false, undefined, <<>>).
 
1095
 
 
1096
 
 
1097
send_window(SSH, CTab, C, DataType, UserAck, User, Data) ->
 
1098
    foreach(
 
1099
      fun({Type,Ack,Usr,Data1}) ->
 
1100
              channel_data(SSH, C#channel.remote_id, Type, Data1),
 
1101
              if Ack == true ->
 
1102
                      Usr ! {ssh_cm, self(), {ack, C#channel.local_id}};
 
1103
                 true ->
 
1104
                      ok
 
1105
              end
 
1106
      end, remove_from_send_window(CTab, C, DataType, UserAck, User, Data)).
 
1107
 
 
1108
 
 
1109
%% Get data from the send buffer 
 
1110
%% each buffer sent must be less than packet size
 
1111
remove_from_send_window(CTab, C, DataType, UserAck, User, Data) ->
 
1112
    Buf0 = if Data == <<>> ->
 
1113
                   C#channel.send_buf;
 
1114
              true ->
 
1115
                   C#channel.send_buf ++ [{DataType,UserAck,User,Data}]
 
1116
           end,
 
1117
    {Buf1,NewSz,Buf2} = get_window(Buf0, 
 
1118
                                   C#channel.send_packet_size,
 
1119
                                   C#channel.send_window_size),
 
1120
    ets:insert(CTab, C#channel { send_window_size = NewSz,
 
1121
                                 send_buf = Buf2}),
 
1122
    Buf1.
 
1123
 
 
1124
get_window(Bs, PSz, WSz) ->
 
1125
    get_window(Bs, PSz, WSz, []).
 
1126
 
 
1127
get_window(Bs, _PSz, 0, Acc) ->
 
1128
    {reverse(Acc), 0, Bs};
 
1129
get_window([B0 = {DataType,_UserAck,_User,Bin} | Bs], PSz, WSz, Acc) ->
 
1130
    BSz = size(Bin),
 
1131
    if BSz =< WSz ->  %% will fit into window
 
1132
            if BSz =< PSz ->  %% will fit into a packet
 
1133
                    get_window(Bs, PSz, WSz-BSz, [B0|Acc]);
 
1134
               true -> %% split into packet size
 
1135
                    <<Bin1:PSz/binary, Bin2/binary>> = Bin,
 
1136
                    get_window([setelement(4, B0, Bin2) | Bs],
 
1137
                               PSz, WSz-PSz, 
 
1138
                               [{DataType,false,undefined,Bin1}|Acc])
 
1139
            end;
 
1140
       WSz =< PSz ->  %% use rest of window
 
1141
            <<Bin1:WSz/binary, Bin2/binary>> = Bin,
 
1142
            get_window([setelement(4, B0, Bin2) | Bs],
 
1143
                       PSz, WSz-WSz, 
 
1144
                       [{DataType,false,undefined,Bin1}|Acc]);
 
1145
       true -> %% use packet size
 
1146
            <<Bin1:PSz/binary, Bin2/binary>> = Bin,
 
1147
            get_window([setelement(4, B0, Bin2) | Bs],
 
1148
                       PSz, WSz-PSz, 
 
1149
                       [{DataType,false,undefined,Bin1}|Acc])
 
1150
    end;
 
1151
get_window([], _PSz, WSz, Acc) ->
 
1152
    {reverse(Acc), WSz, []}.
 
1153
 
 
1154
 
 
1155
%%
 
1156
%% CHANNEL Commands
 
1157
%%
 
1158
channel_eof(SSH, Channel) ->
 
1159
    SSH ! {ssh_msg, self(), 
 
1160
           #ssh_msg_channel_eof { recipient_channel = Channel }}.
 
1161
 
 
1162
channel_close(SSH, Channel) ->
 
1163
    SSH ! {ssh_msg, self(), 
 
1164
           #ssh_msg_channel_close { recipient_channel = Channel }}.
 
1165
 
 
1166
channel_success(SSH, Channel) ->
 
1167
    SSH ! {ssh_msg, self(),
 
1168
           #ssh_msg_channel_success { recipient_channel = Channel }}.
 
1169
 
 
1170
channel_failure(SSH, Channel) ->
 
1171
    SSH ! {ssh_msg, self(),
 
1172
           #ssh_msg_channel_failure { recipient_channel = Channel }}.
 
1173
 
 
1174
 
 
1175
channel_adjust_window(SSH, Channel, Bytes) ->
 
1176
    SSH ! {ssh_msg, self(), 
 
1177
           #ssh_msg_channel_window_adjust { recipient_channel = Channel,
 
1178
                                            bytes_to_add = Bytes }}.
 
1179
 
 
1180
 
 
1181
channel_data(SSH, Channel, 0, Data) ->
 
1182
    SSH ! {ssh_msg, self(),
 
1183
           #ssh_msg_channel_data { recipient_channel = Channel,
 
1184
                                   data = Data }};
 
1185
channel_data(SSH, Channel, Type, Data) ->
 
1186
    SSH ! {ssh_msg, self(),
 
1187
           #ssh_msg_channel_extended_data { recipient_channel = Channel,
 
1188
                                            data_type_code = Type,
 
1189
                                            data = Data }}.
 
1190
 
 
1191
channel_open(SSH, Type, Channel, WindowSize, MaxPacketSize, Data) ->
 
1192
    SSH ! {ssh_msg, self(), 
 
1193
           #ssh_msg_channel_open { channel_type = Type,
 
1194
                                   sender_channel = Channel,
 
1195
                                   initial_window_size = WindowSize,
 
1196
                                   maximum_packet_size = MaxPacketSize,
 
1197
                                   data = Data
 
1198
                                  }}.
 
1199
 
 
1200
channel_open_confirmation(SSH, RID, LID, WindowSize, PacketSize) ->
 
1201
    SSH ! {ssh_msg, self(),
 
1202
           #ssh_msg_channel_open_confirmation { recipient_channel = RID,
 
1203
                                                sender_channel = LID,
 
1204
                                                initial_window_size = WindowSize,
 
1205
                                                maximum_packet_size = PacketSize}}.
 
1206
 
 
1207
channel_open_failure(SSH, RID, Reason, Description, Lang) ->
 
1208
    SSH ! {ssh_msg, self(),
 
1209
           #ssh_msg_channel_open_failure { recipient_channel = RID,
 
1210
                                           reason = Reason,
 
1211
                                           description = Description,
 
1212
                                           lang = Lang }}.
 
1213
                                           
 
1214
    
 
1215
 
 
1216
channel_request(SSH, Channel, Type, WantReply, Data) ->
 
1217
    SSH ! {ssh_msg, self(),
 
1218
           #ssh_msg_channel_request { recipient_channel = Channel,
 
1219
                                      request_type = Type,
 
1220
                                      want_reply = WantReply,
 
1221
                                      data = Data }}.
 
1222
 
 
1223
send_global_request(SSH, Type, WantReply, Data) ->
 
1224
    SSH ! {ssh_msg, self(),
 
1225
           #ssh_msg_global_request { name = Type,
 
1226
                                     want_reply = WantReply,
 
1227
                                     data = Data }}.
 
1228
 
 
1229
request_failure(SSH) ->
 
1230
    SSH ! {ssh_msg, self(), #ssh_msg_request_failure {}}.
 
1231
 
 
1232
request_success(SSH,Data) ->
 
1233
    SSH ! {ssh_msg, self(), #ssh_msg_request_success { data=Data }}.
 
1234
 
 
1235
 
 
1236
 
 
1237
decode_pty_opts(<<>>) ->                     
 
1238
    [];
 
1239
decode_pty_opts(<<0, 0, 0, 0>>) ->
 
1240
    [];
 
1241
decode_pty_opts(<<?UINT32(Len), Modes:Len/binary>>) ->
 
1242
    decode_pty_opts2(Modes);
 
1243
decode_pty_opts(Binary) ->
 
1244
    decode_pty_opts2(Binary).
 
1245
 
 
1246
decode_pty_opts2(<<?TTY_OP_END>>) ->                 
 
1247
    [];
 
1248
decode_pty_opts2(<<Code, ?UINT32(Value), Tail/binary>>) ->
 
1249
    Op = case Code of
 
1250
             ?VINTR -> vintr;
 
1251
             ?VQUIT -> vquit;
 
1252
             ?VERASE -> verase;
 
1253
             ?VKILL -> vkill;
 
1254
             ?VEOF -> veof;
 
1255
             ?VEOL -> veol;
 
1256
             ?VEOL2 -> veol2;
 
1257
             ?VSTART -> vstart;
 
1258
             ?VSTOP -> vstop;
 
1259
             ?VSUSP -> vsusp;
 
1260
             ?VDSUSP -> vdsusp;
 
1261
             ?VREPRINT -> vreprint;
 
1262
             ?VWERASE -> vwerase;
 
1263
             ?VLNEXT -> vlnext;
 
1264
             ?VFLUSH -> vflush;
 
1265
             ?VSWTCH -> vswtch;
 
1266
             ?VSTATUS -> vstatus;
 
1267
             ?VDISCARD -> vdiscard;
 
1268
             ?IGNPAR -> ignpar;
 
1269
             ?PARMRK -> parmrk;
 
1270
             ?INPCK -> inpck;
 
1271
             ?ISTRIP -> istrip;
 
1272
             ?INLCR -> inlcr;
 
1273
             ?IGNCR -> igncr;
 
1274
             ?ICRNL -> icrnl;
 
1275
             ?IUCLC -> iuclc;
 
1276
             ?IXON -> ixon;
 
1277
             ?IXANY -> ixany;
 
1278
             ?IXOFF -> ixoff;
 
1279
             ?IMAXBEL -> imaxbel;
 
1280
             ?ISIG -> isig;
 
1281
             ?ICANON -> icanon;
 
1282
             ?XCASE -> xcase;
 
1283
             ?ECHO -> echo;
 
1284
             ?ECHOE -> echoe;
 
1285
             ?ECHOK -> echok;
 
1286
             ?ECHONL -> echonl;
 
1287
             ?NOFLSH -> noflsh;
 
1288
             ?TOSTOP -> tostop;
 
1289
             ?IEXTEN -> iexten;
 
1290
             ?ECHOCTL -> echoctl;
 
1291
             ?ECHOKE -> echoke;
 
1292
             ?PENDIN -> pendin;
 
1293
             ?OPOST -> opost;
 
1294
             ?OLCUC -> olcuc;
 
1295
             ?ONLCR -> onlcr;
 
1296
             ?OCRNL -> ocrnl;
 
1297
             ?ONOCR -> onocr;
 
1298
             ?ONLRET -> onlret;
 
1299
             ?CS7 -> cs7;
 
1300
             ?CS8 -> cs8;
 
1301
             ?PARENB -> parenb;
 
1302
             ?PARODD -> parodd;
 
1303
             ?TTY_OP_ISPEED -> tty_op_ispeed;
 
1304
             ?TTY_OP_OSPEED -> tty_op_ospeed
 
1305
         end,    
 
1306
    [{Op, Value} | decode_pty_opts2(Tail)].
 
1307
 
 
1308
 
 
1309
 
 
1310
encode_pty_opts([{Opt,Value} | Opts]) ->
 
1311
    Code = case Opt of
 
1312
               vintr -> ?VINTR;
 
1313
               vquit -> ?VQUIT;
 
1314
               verase -> ?VERASE;
 
1315
               vkill -> ?VKILL;
 
1316
               veof -> ?VEOF;
 
1317
               veol -> ?VEOL;
 
1318
               veol2 -> ?VEOL2;
 
1319
               vstart -> ?VSTART;
 
1320
               vstop -> ?VSTOP;
 
1321
               vsusp -> ?VSUSP;
 
1322
               vdsusp -> ?VDSUSP;
 
1323
               vreprint -> ?VREPRINT;
 
1324
               vwerase -> ?VWERASE;
 
1325
               vlnext -> ?VLNEXT;
 
1326
               vflush -> ?VFLUSH;
 
1327
               vswtch -> ?VSWTCH;
 
1328
               vstatus -> ?VSTATUS;
 
1329
               vdiscard -> ?VDISCARD;
 
1330
               ignpar -> ?IGNPAR;
 
1331
               parmrk -> ?PARMRK;
 
1332
               inpck -> ?INPCK;
 
1333
               istrip -> ?ISTRIP;
 
1334
               inlcr -> ?INLCR;
 
1335
               igncr -> ?IGNCR;
 
1336
               icrnl -> ?ICRNL;
 
1337
               iuclc -> ?IUCLC;
 
1338
               ixon -> ?IXON;
 
1339
               ixany -> ?IXANY;
 
1340
               ixoff -> ?IXOFF;
 
1341
               imaxbel -> ?IMAXBEL;
 
1342
               isig -> ?ISIG;
 
1343
               icanon -> ?ICANON;
 
1344
               xcase -> ?XCASE;
 
1345
               echo -> ?ECHO;
 
1346
               echoe -> ?ECHOE;
 
1347
               echok -> ?ECHOK;
 
1348
               echonl -> ?ECHONL;
 
1349
               noflsh -> ?NOFLSH;
 
1350
               tostop -> ?TOSTOP;
 
1351
               iexten -> ?IEXTEN;
 
1352
               echoctl -> ?ECHOCTL;
 
1353
               echoke -> ?ECHOKE;
 
1354
               pendin -> ?PENDIN;
 
1355
               opost -> ?OPOST;
 
1356
               olcuc -> ?OLCUC;
 
1357
               onlcr -> ?ONLCR;
 
1358
               ocrnl -> ?OCRNL;
 
1359
               onocr -> ?ONOCR;
 
1360
               onlret -> ?ONLRET;
 
1361
               cs7 -> ?CS7;
 
1362
               cs8 -> ?CS8;
 
1363
               parenb -> ?PARENB;
 
1364
               parodd -> ?PARODD;
 
1365
               tty_op_ispeed -> ?TTY_OP_ISPEED;
 
1366
               tty_op_ospeed -> ?TTY_OP_OSPEED
 
1367
           end,
 
1368
    [Code, ?uint32(Value) | encode_pty_opts(Opts)];
 
1369
encode_pty_opts([]) -> 
 
1370
    [?TTY_OP_END].
 
1371
 
 
1372
 
 
1373
decode_ip(Addr) when tuple(Addr) ->
 
1374
    Addr;
 
1375
decode_ip(Addr) when binary(Addr) ->
 
1376
    decode_ip(binary_to_list(Addr));
 
1377
decode_ip(Addr) when list(Addr) ->
 
1378
    case inet_parse:address(Addr) of
 
1379
        {error,_} -> Addr;
 
1380
        {ok,A}    -> A
 
1381
    end.
 
1382
 
 
1383
%% return string() | false
 
1384
encode_ip(Addr) when tuple(Addr) ->
 
1385
    case catch inet_parse:ntoa(Addr) of
 
1386
        {'EXIT',_} -> false;
 
1387
        A -> A
 
1388
    end;
 
1389
encode_ip(Addr) when list(Addr) ->
 
1390
    case inet_parse:address(Addr) of
 
1391
        {ok, _} -> Addr;
 
1392
        Error ->
 
1393
            case inet:getaddr(Addr, inet) of
 
1394
                {ok, A} ->
 
1395
                    inet_parse:ntoa(A);
 
1396
                Error -> false
 
1397
            end
 
1398
    end.
 
1399
 
 
1400
 
 
1401
%% requests
 
1402
 
 
1403
do_request(Channel, Type, Data, WantReply, From, State) ->
 
1404
    #state{ctab = CTab, ssh = SSH} = State,
 
1405
    with_channel(
 
1406
      State, Channel,
 
1407
      fun(C) ->
 
1408
              update_sys(CTab, C, Type),
 
1409
              channel_request(SSH, C#channel.remote_id,
 
1410
                              Type, WantReply, Data)
 
1411
      end),
 
1412
    add_request(WantReply, Channel, From, State).
 
1413
 
 
1414
add_request(false, _Channel, _From, State) ->
 
1415
    State;
 
1416
add_request(true, Channel, From, State) ->
 
1417
    Requests = [{Channel, From} | State#state.requests],
 
1418
    State#state{requests = Requests}.
 
1419
    
 
1420
    
 
1421
 
 
1422
 
 
1423
%% state functions
 
1424
 
 
1425
 
 
1426
put_bind(IP, Port, User, State) ->
 
1427
    Binds = [{{IP, Port}, User}
 
1428
             | lists:keydelete({IP, Port}, 1, State#state.binds)],
 
1429
    State#state{binds = Binds}.
 
1430
 
 
1431
del_bind(IP, Port, State) ->
 
1432
    State#state{binds = lists:keydelete({IP, Port}, 1, State#state.binds)}.
 
1433
 
 
1434
del_binds_by_user(User, State) ->
 
1435
    Binds = [{B, U} || {B, U} <- State#state.binds, U =/= User],
 
1436
    State#state{binds = Binds}.
 
1437
 
 
1438
get_bind(IP, Port, State) ->
 
1439
    case lists:keysearch({IP, Port}, 1, State) of
 
1440
        {value, User} -> User;
 
1441
        _ -> undefined
 
1442
    end.
 
1443
 
 
1444
with_channel(State, Channel, Fun) ->
 
1445
    case ets:lookup(State#state.ctab, Channel) of
 
1446
        [C] ->
 
1447
            Fun(C);
 
1448
        [] ->
 
1449
            ignore
 
1450
    end,
 
1451
    State.
 
1452
 
 
1453
%% Add a user
 
1454
add_user(User, State) ->
 
1455
    Users = State#state.users,
 
1456
    case lists:keymember(User, 1, Users) of
 
1457
        false ->
 
1458
            Ref = erlang:monitor(process, User),
 
1459
            State#state{users = [{User, Ref} | Users]};
 
1460
        true ->
 
1461
            State
 
1462
    end.
 
1463
 
 
1464
%% Remove user
 
1465
del_user(User, State) ->
 
1466
    #state{users = Users, ssh = SSH} = State,
 
1467
    ?dbg(false, "del user: ~p\n",[User]),
 
1468
    case lists:keysearch(User, 1, Users) of
 
1469
        false ->
 
1470
            {{error, einval}, State};
 
1471
        {value, {User, Ref}} ->
 
1472
            erlang:demonitor(Ref),
 
1473
            State1 = del_binds_by_user(User, State),
 
1474
            State2 = State1#state{users = lists:keydelete(User, 1, Users)},
 
1475
            %% exit if no more users and we are unregistered
 
1476
            if Users == [] ->
 
1477
                    case process_info(self(), registered_name) of
 
1478
                        [] ->
 
1479
                            ssh_transport:disconnect(SSH, 0);
 
1480
                        {registered_name,_Name} ->
 
1481
                            ok
 
1482
                    end;
 
1483
               true ->
 
1484
                    ok
 
1485
            end,
 
1486
            State2          
 
1487
    end.
 
1488
 
 
1489
is_user(User, State) ->
 
1490
    lists:keymember(User, 1, State#state.users).            
 
1491
 
 
1492
%% Allocate channel ID 
 
1493
new_channel_id(State) ->
 
1494
    ID = State#state.channel_id,
 
1495
    {ID, State#state{channel_id = ID + 1}}.
 
1496
 
 
1497
not_zero(0, B) -> B;
 
1498
not_zero(A, _) -> A.