~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%<copyright>
2
 
%% <year>2005-2007</year>
3
 
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
 
%%</copyright>
5
 
%%<legalnotice>
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2005-2009. All Rights Reserved.
 
5
%% 
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%%
 
11
%% 
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
16
18
%%
17
 
%% The Initial Developer of the Original Code is Ericsson AB.
18
 
%%</legalnotice>
 
19
 
19
20
%%
20
21
%% Description: a gen_server implementing a simple
21
22
%% terminal (using the group module) for a CLI
23
24
 
24
25
-module(ssh_cli).
25
26
 
26
 
-behaviour(gen_server).
 
27
-behaviour(ssh_channel).
27
28
 
28
29
-include("ssh.hrl").
29
30
-include("ssh_connect.hrl").
30
31
 
31
 
%% Internal API
32
 
-export([child_spec/1, child_spec/2, child_spec/3, child_spec/4]).
 
32
%% ssh_channel callbacks
 
33
-export([init/1, handle_ssh_msg/2, handle_msg/2, terminate/2]).
33
34
 
34
35
%% backwards compatibility
35
36
-export([listen/1, listen/2, listen/3, listen/4, stop/1]).
36
37
 
37
 
%% gen_server callbacks
38
 
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
39
 
         terminate/2, code_change/3]).
40
 
 
41
 
%% defines
42
 
-define(DBG_IO_REQUEST, true).
43
 
 
44
38
%% state
45
39
-record(state, {
46
40
          cm,
48
42
          pty,
49
43
          group,
50
44
          buf,
51
 
          shell,
52
 
          remote_channel,
53
 
          options,
54
 
          address,
55
 
          port
 
45
          shell
56
46
         }).
57
47
 
58
48
%%====================================================================
59
 
%% API
60
 
%%====================================================================
61
 
child_spec(Shell) ->
62
 
    child_spec(Shell, 22).
63
 
 
64
 
child_spec(Shell, Port) ->
65
 
    child_spec(Shell, Port, []).
66
 
 
67
 
child_spec(Shell, Port, Opts) ->
68
 
    child_spec(Shell, any, Port, Opts).
69
 
 
70
 
child_spec(Shell, Address, Port, Opts) ->
71
 
    Name = make_ref(),
72
 
    StartFunc = {gen_server, 
73
 
                 start_link, [?MODULE, 
74
 
                              [Shell, Address, Port, Opts], []]},
75
 
    Restart = temporary, 
76
 
    Shutdown = 3600,
77
 
    Modules = [ssh_cli],
78
 
    Type = worker,
79
 
    {Name, StartFunc, Restart, Shutdown, Type, Modules}.
80
 
 
81
 
%%--------------------------------------------------------------------
82
 
%% Function: listen(...) -> {ok,Pid} | ignore | {error,Error}
83
 
%% Description: Starts a listening server
84
 
%% Note that the pid returned is NOT the pid of this gen_server;
85
 
%% this server is started when an SSH connection is made on the
86
 
%% listening port
87
 
%%--------------------------------------------------------------------
88
 
listen(Shell) ->
89
 
    listen(Shell, 22).
90
 
 
91
 
listen(Shell, Port) ->
92
 
    listen(Shell, Port, []).
93
 
 
94
 
listen(Shell, Port, Opts) ->
95
 
    listen(Shell, any, Port, Opts).
96
 
 
97
 
listen(Shell, HostAddr, Port, Opts) ->
98
 
    ssh:daemon(HostAddr, Port, [{shell, Shell} | Opts]).
99
 
    
100
 
 
101
 
%%--------------------------------------------------------------------
102
 
%% Function: stop(Pid) -> ok
103
 
%% Description: Stops the listener
104
 
%%--------------------------------------------------------------------
105
 
stop(Pid) ->
106
 
    ssh:stop_listener(Pid).
107
 
 
108
 
%%====================================================================
109
 
%% gen_server callbacks
110
 
%%====================================================================
111
 
 
112
 
%%--------------------------------------------------------------------
113
 
%% Function: init(Args) -> {ok, State} |
114
 
%%                         {ok, State, Timeout} |
115
 
%%                         ignore               |
116
 
%%                         {stop, Reason}
117
 
%% Description: Initiates the server
118
 
%%--------------------------------------------------------------------
119
 
init([Shell, Address, Port, Opts]) ->
120
 
    {ok, #state{shell = Shell, 
121
 
                address = Address,
122
 
                port = Port,
123
 
                options = Opts}}.
124
 
 
125
 
%%--------------------------------------------------------------------
126
 
%% Function: %% handle_call(Request, From, State) -> {reply, Reply, State} |
127
 
%%                                      {reply, Reply, State, Timeout} |
128
 
%%                                      {noreply, State} |
129
 
%%                                      {noreply, State, Timeout} |
130
 
%%                                      {stop, Reason, Reply, State} |
131
 
%%                                      {stop, Reason, State}
132
 
%% Description: Handling call messages
133
 
%%--------------------------------------------------------------------
134
 
handle_call(stop, _From, State) ->
135
 
    Result = ssh_cm:stop(State#state.cm),
136
 
    {stop, normal, Result, State};
137
 
handle_call(info, _From, State) ->
138
 
    {reply, State, State};
139
 
handle_call(_Request, _From, State) ->
140
 
    Reply = ok,
141
 
    {reply, Reply, State}.
142
 
 
143
 
%%--------------------------------------------------------------------
144
 
%% Function: handle_cast(Msg, State) -> {noreply, State} |
145
 
%%                                      {noreply, State, Timeout} |
146
 
%%                                      {stop, Reason, State}
147
 
%% Description: Handling cast messages
148
 
%%--------------------------------------------------------------------
149
 
handle_cast(_Msg, State) ->
150
 
    {noreply, State}.
151
 
 
152
 
%%--------------------------------------------------------------------
153
 
%% Function: handle_info(Info, State) -> {noreply, State} |
154
 
%%                                       {noreply, State, Timeout} |
155
 
%%                                       {stop, Reason, State}
156
 
%% Description: Handling all non call/cast messages
157
 
%%--------------------------------------------------------------------
158
 
handle_info({ssh_cm, CM, {open, Channel, RemoteChannel, {session}}}, State) ->
159
 
    {noreply,
160
 
     State#state{cm = CM, channel = Channel, remote_channel = RemoteChannel}};
161
 
 
162
 
handle_info({ssh_cm, CM, {data, _Channel, _Type, Data}}, 
163
 
            #state{remote_channel = ChannelId} = State) ->
164
 
    ssh_connection:adjust_window(CM, ChannelId, size(Data)),
165
 
    State#state.group ! {self(), {data, binary_to_list(Data)}},
166
 
    {noreply, State};
167
 
 
168
 
handle_info({ssh_cm, CM, {pty, _Channel, WantReply, Pty}}, 
169
 
            #state{remote_channel = ChannelId} = State0) ->
170
 
    ssh_connection:reply_request(CM, WantReply, success, ChannelId),
171
 
    State = State0#state{pty = Pty},
 
49
%% ssh_channel callbacks
 
50
%%====================================================================
 
51
 
 
52
%%--------------------------------------------------------------------
 
53
%% Function: init(Args) -> {ok, State} 
 
54
%%                        
 
55
%% Description: Initiates the CLI
 
56
%%--------------------------------------------------------------------
 
57
init([Shell]) ->
 
58
    {ok, #state{shell = Shell}}.
 
59
 
 
60
%%--------------------------------------------------------------------
 
61
%% Function: handle_ssh_msg(Args) -> {ok, State} | {stop, ChannelId, State}
 
62
%%                        
 
63
%% Description: Handles channel messages received on the ssh-connection.
 
64
%%--------------------------------------------------------------------
 
65
handle_ssh_msg({ssh_cm, _ConnectionManager, 
 
66
                {data, _ChannelId, _Type, Data}}, 
 
67
               #state{group = Group} = State) ->
 
68
    Group ! {self(), {data, binary_to_list(Data)}},
 
69
    {ok, State};
 
70
 
 
71
handle_ssh_msg({ssh_cm, ConnectionManager, 
 
72
                {pty, ChannelId, WantReply, 
 
73
                 {TermName, Width, Height, PixWidth, PixHeight, Modes}}}, 
 
74
               State0) ->
 
75
    State = State0#state{pty = 
 
76
                         #ssh_pty{term = TermName,
 
77
                                  width =  not_zero(Width, 80),
 
78
                                  height = not_zero(Height, 24),
 
79
                                  pixel_width = PixWidth,
 
80
                                  pixel_height = PixHeight,
 
81
                                  modes = Modes}},
172
82
    set_echo(State),
173
 
    {noreply, State};
174
 
 
175
 
handle_info({ssh_cm, _CM,
176
 
             {window_change, _Channel, Width, Height, PixWidth, PixHeight}},
177
 
            State) ->
178
 
    #state{buf = Buf, pty = Pty, cm = CM, channel = Channel} = State,
179
 
    NewPty = Pty#ssh_pty{width = Width, height = Height,
180
 
                         pixel_width = PixWidth,
181
 
                         pixel_height = PixHeight},
182
 
    {Chars, NewBuf} = io_request({window_change, Pty}, Buf, NewPty),
183
 
    write_chars(CM, Channel, Chars),
184
 
    {noreply, State#state{pty = NewPty, buf = NewBuf}};
185
 
handle_info({Group, Req}, State) when Group==State#state.group ->
186
 
    ?dbg(?DBG_IO_REQUEST, "io_request: ~w\n", [Req]),
187
 
    #state{buf = Buf, pty = Pty, cm = CM, channel = Channel} = State,
 
83
    ssh_connection:reply_request(ConnectionManager, WantReply, 
 
84
                                 success, ChannelId),
 
85
    {ok, State};
 
86
 
 
87
handle_ssh_msg({ssh_cm, ConnectionManager, 
 
88
            {env, ChannelId, WantReply, _Var, _Value}}, State) ->
 
89
    ssh_connection:reply_request(ConnectionManager, 
 
90
                                 WantReply, failure, ChannelId),
 
91
    {ok, State};
 
92
 
 
93
handle_ssh_msg({ssh_cm, ConnectionManager,
 
94
            {window_change, ChannelId, Width, Height, PixWidth, PixHeight}},
 
95
           #state{buf = Buf, pty = Pty0} = State) ->
 
96
    Pty = Pty0#ssh_pty{width = Width, height = Height,
 
97
                       pixel_width = PixWidth,
 
98
                       pixel_height = PixHeight},
 
99
    {Chars, NewBuf} = io_request({window_change, Pty0}, Buf, Pty),
 
100
    write_chars(ConnectionManager, ChannelId, Chars),
 
101
    {ok, State#state{pty = Pty, buf = NewBuf}};
 
102
 
 
103
handle_ssh_msg({ssh_cm, ConnectionManager, 
 
104
            {shell, ChannelId, WantReply}}, State) ->
 
105
    NewState = start_shell(ConnectionManager, State),
 
106
    ssh_connection:reply_request(ConnectionManager, WantReply, 
 
107
                                 success, ChannelId),
 
108
    {ok, NewState#state{channel = ChannelId,
 
109
                        cm = ConnectionManager}};
 
110
 
 
111
handle_ssh_msg({ssh_cm, ConnectionManager, 
 
112
                {exec, ChannelId, WantReply, Cmd}}, State) ->
 
113
    {Reply, Status} = exec(Cmd),
 
114
    write_chars(ConnectionManager, 
 
115
                ChannelId, io_lib:format("~p\n", [Reply])),
 
116
    ssh_connection:reply_request(ConnectionManager, WantReply, 
 
117
                                 success, ChannelId),
 
118
    ssh_connection:exit_status(ConnectionManager, ChannelId, Status),
 
119
    ssh_connection:send_eof(ConnectionManager, ChannelId),
 
120
    {stop, ChannelId, State#state{channel = ChannelId, cm = ConnectionManager}};
 
121
 
 
122
handle_ssh_msg({ssh_cm, _ConnectionManager, {eof, _ChannelId}}, State) ->
 
123
    {ok, State};
 
124
 
 
125
handle_ssh_msg({ssh_cm, _, {signal, _, _}}, State) ->
 
126
    %% Ignore signals according to RFC 4254 section 6.9.
 
127
    {ok, State};
 
128
 
 
129
handle_ssh_msg({ssh_cm, _, {exit_signal, ChannelId, _, Error, _}}, State) ->
 
130
    Report = io_lib:format("Connection closed by peer ~n Error ~p~n",
 
131
                           [Error]),
 
132
    error_logger:error_report(Report),
 
133
    {stop, ChannelId,  State};
 
134
 
 
135
handle_ssh_msg({ssh_cm, _, {exit_status, ChannelId, 0}}, State) ->
 
136
    {stop, ChannelId, State};
 
137
 
 
138
handle_ssh_msg({ssh_cm, _, {exit_status, ChannelId, Status}}, State) ->
 
139
    
 
140
    Report = io_lib:format("Connection closed by peer ~n Status ~p~n",
 
141
                           [Status]),
 
142
    error_logger:error_report(Report),
 
143
    {stop, ChannelId, State}.
 
144
 
 
145
%%--------------------------------------------------------------------
 
146
%% Function: handle_msg(Args) -> {ok, State} | {stop, ChannelId, State}
 
147
%%                        
 
148
%% Description: Handles other channel messages.
 
149
%%--------------------------------------------------------------------
 
150
handle_msg({ssh_channel_up, ChannelId, ConnectionManager},
 
151
           #state{channel = ChannelId,
 
152
                  cm = ConnectionManager} = State) ->
 
153
    {ok,  State};
 
154
 
 
155
handle_msg({Group, Req}, #state{group = Group, buf = Buf, pty = Pty,
 
156
                                 cm = ConnectionManager,
 
157
                                 channel = ChannelId} = State) ->
188
158
    {Chars, NewBuf} = io_request(Req, Buf, Pty),
189
 
    write_chars(CM, Channel, Chars),
190
 
    {noreply, State#state{buf = NewBuf}};
191
 
handle_info({ssh_cm, CM, {shell, WantReply}}, 
192
 
            #state{remote_channel = ChannelId} = State) ->
193
 
    NewState = start_shell(CM, State),
194
 
    process_flag(trap_exit, true),
195
 
    ssh_connection:reply_request(CM, WantReply, success, ChannelId),
196
 
    {noreply, NewState};
197
 
handle_info({ssh_cm, CM, {exec, Cmd}}, #state{channel = ChannelId} = State) ->
198
 
    Reply = case erl_scan:string(Cmd) of
199
 
                {ok, Tokens, _EndList} ->
200
 
                    case erl_parse:parse_exprs(Tokens) of
201
 
                        {ok, Expr_list} ->
202
 
                            case (catch erl_eval:exprs(
203
 
                                          Expr_list,
204
 
                                          erl_eval:new_bindings())) of
205
 
                                {value, Value, _NewBindings} ->
206
 
                                    Value;
207
 
                                {'EXIT', {E, _}} -> E;
208
 
                                E -> E
209
 
                            end;
210
 
                        E -> E
211
 
                    end;
212
 
                E -> E
213
 
            end,
214
 
    write_chars(CM, ChannelId, io_lib:format("~p\n", [Reply])),
215
 
    ssh_connection:send_eof(CM, ChannelId),
216
 
    ssh_connection:close(CM, ChannelId),
217
 
    {noreply, State};
218
 
handle_info({get_cm, From}, #state{cm=CM} = State) ->
219
 
    From ! {From, cm, CM},
220
 
    {noreply, State};
221
 
handle_info({ssh_cm, _CM, {eof, _Channel}}, State) ->
222
 
    {stop, normal, State};
223
 
handle_info({ssh_cm, _CM, {closed, _Channel}}, State) ->
224
 
    %% ignore -- we'll get an {eof, Channel} soon??
225
 
    {noreply, State};
226
 
handle_info({ssh_cm, CM, {subsystem, ChannelId, _WantsReply, SsName}} = Msg,
227
 
            #state{address = Address, port = Port, options = Opts,
228
 
                   remote_channel = RemoteChannel} = State) ->
229
 
    case check_subsystem(SsName, Opts) of
230
 
        none ->
231
 
            {noreply, State};
232
 
        %% Backwards compatibility
233
 
        Module when is_atom(Module) ->
234
 
            {ok, SubSystemD} = 
235
 
                gen_server:start_link(Module, [Opts], []),
236
 
            SubSystemD ! 
237
 
                {ssh_cm, CM, {open, ChannelId, RemoteChannel, {session}}},
238
 
            SubSystemD ! Msg,
239
 
            ssh_connection_manager:controlling_process(CM, ChannelId, 
240
 
                                                       SubSystemD, self()),
241
 
            {stop, normal, State};
242
 
        Fun when is_function(Fun) ->
243
 
            SubSystemD = Fun(),
244
 
            SubSystemD ! 
245
 
                {ssh_cm, CM, {open, ChannelId, RemoteChannel, {session}}},
246
 
            SubSystemD ! Msg,
247
 
            ssh_connection_manager:controlling_process(CM, ChannelId, 
248
 
                                                       SubSystemD, self()),
249
 
            {stop, normal, State};
250
 
        ChildSpec ->
251
 
            SystemSup = ssh_system_sup:system_supervisor(Address, Port),
252
 
            ChannelSup = ssh_system_sup:channel_supervisor(SystemSup),
253
 
            {ok, SubSystemD} 
254
 
                = ssh_channel_sup:start_child(ChannelSup, ChildSpec),
255
 
            SubSystemD ! 
256
 
                {ssh_cm, CM, {open, ChannelId, RemoteChannel, {session}}},
257
 
            SubSystemD ! Msg,
258
 
            ssh_connection_manager:controlling_process(CM, ChannelId, 
259
 
                                                       SubSystemD, self()),
260
 
            empty_mailbox_workaround(SubSystemD),
261
 
            {stop, normal, State}
262
 
    
263
 
    end;
264
 
handle_info({'EXIT', Group, normal},
265
 
            #state{cm=CM, channel=Channel, group=Group} = State) ->
266
 
    ssh_connection:close(CM, Channel),
267
 
    ssh_cm:stop(CM),
268
 
    {stop, normal, State};
269
 
handle_info(Info, State) ->
270
 
    ?dbg(true, "~p:handle_info: BAD info ~p\n(State ~p)\n", 
271
 
         [?MODULE, Info, State]),
272
 
    {stop, {bad_info, Info}, State}.
 
159
    write_chars(ConnectionManager, ChannelId, Chars),
 
160
    {ok, State#state{buf = NewBuf}};
 
161
 
 
162
handle_msg({'EXIT', Group, _Reason}, #state{group = Group,
 
163
                                             channel = ChannelId} = State) ->
 
164
    {stop, ChannelId, State};
 
165
 
 
166
handle_msg(_, State) ->
 
167
    {ok, State}.
273
168
 
274
169
%%--------------------------------------------------------------------
275
170
%% Function: terminate(Reason, State) -> void()
276
 
%% Description: This function is called by a gen_server when it is about to
277
 
%% terminate. It should be the opposite of Module:init/1 and do any necessary
278
 
%% cleaning up. When it returns, the gen_server terminates with Reason.
279
 
%% The return value is ignored.
 
171
%% Description: Called when the channel process is trminated
280
172
%%--------------------------------------------------------------------
281
173
terminate(_Reason, _State) ->
282
174
    ok.
283
175
 
284
176
%%--------------------------------------------------------------------
285
 
%% Func: code_change(OldVsn, State, Extra) -> {ok, NewState}
286
 
%% Description: Convert process state when code is changed
287
 
%%--------------------------------------------------------------------
288
 
code_change(_OldVsn, State, _Extra) ->
289
 
    {ok, State}.
290
 
 
291
 
%%--------------------------------------------------------------------
292
177
%%% Internal functions
293
178
%%--------------------------------------------------------------------
294
179
 
295
 
%%% io_request, handle io requests from the user process
 
180
exec(Cmd) ->
 
181
    eval(parse(scan(Cmd))).
 
182
 
 
183
scan(Cmd) ->
 
184
    erl_scan:string(Cmd). 
 
185
 
 
186
parse({ok, Tokens, _}) ->
 
187
    erl_parse:parse_exprs(Tokens);
 
188
parse(Error) ->
 
189
    Error.
 
190
 
 
191
eval({ok, Expr_list}) ->
 
192
    case (catch erl_eval:exprs(Expr_list,
 
193
                               erl_eval:new_bindings())) of
 
194
        {value, Value, _NewBindings} ->
 
195
            {Value, 0};
 
196
        {'EXIT', {Error, _}} -> 
 
197
            {Error, -1};
 
198
        Error -> 
 
199
            {Error, -1}
 
200
    end;
 
201
eval(Error) ->
 
202
    {Error, -1}.
 
203
 
 
204
%%% io_request, handle io requests from the user process,
 
205
%%% Note, this is not the real I/O-protocol, but the mockup version
 
206
%%% used between edlin and a user_driver. The protocol tags are
 
207
%%% similar, but the message set is different. 
 
208
%%% The protocol only exists internally between edlin and a character
 
209
%%% displaying device...
 
210
%%% We are *not* really unicode aware yet, we just filter away characters 
 
211
%%% beyond the latin1 range. We however handle the unicode binaries...
296
212
io_request({window_change, OldTty}, Buf, Tty) ->
297
213
    window_change(Tty, OldTty, Buf);
298
214
io_request({put_chars, Cs}, Buf, Tty) ->
299
215
    put_chars(bin_to_list(Cs), Buf, Tty);
 
216
io_request({put_chars, unicode, Cs}, Buf, Tty) ->
 
217
    put_chars([Ch || Ch <- unicode:characters_to_list(Cs,unicode), Ch =< 255], Buf, Tty);
300
218
io_request({insert_chars, Cs}, Buf, Tty) ->
301
219
    insert_chars(bin_to_list(Cs), Buf, Tty);
 
220
io_request({insert_chars, unicode, Cs}, Buf, Tty) ->
 
221
    insert_chars([Ch || Ch <- unicode:characters_to_list(Cs,unicode), Ch =< 255], Buf, Tty);
302
222
io_request({move_rel, N}, Buf, Tty) ->
303
223
    move_rel(N, Buf, Tty);
304
224
io_request({delete_chars,N}, Buf, Tty) ->
314
234
io_request({requests,Rs}, Buf, Tty) ->
315
235
    io_requests(Rs, Buf, Tty, []);
316
236
io_request(tty_geometry, Buf, Tty) ->
317
 
    io_requests([{move_rel, 0}, {put_chars, [10]}], Buf, Tty, []);
 
237
    io_requests([{move_rel, 0}, {put_chars, unicode, [10]}], Buf, Tty, []);
318
238
     %{[], Buf};
319
239
io_request(_R, Buf, _Tty) ->
320
240
    {[], Buf}.
354
274
    conv_buf(Rest, [], tl1(AccBufTail), [13 | AccWrite], 0);
355
275
conv_buf([10 | Rest], _AccBuf, AccBufTail, AccWrite, _Col) ->
356
276
    conv_buf(Rest, [], tl1(AccBufTail), [10, 13 | AccWrite], 0);
357
 
conv_buf([9 | Rest], AccBuf, AccBufTail, AccWrite, Col) ->
358
 
    NSpaces = (Col + (?TABWIDTH - 1)) rem ?TABWIDTH + 1,
359
 
    AccB = string:chars(?PAD, NSpaces-1) ++ [9 | AccBuf],
360
 
    AccW = string:chars(32, NSpaces) ++ [AccWrite],
361
 
    AccBT = nthtail(NSpaces, AccBufTail),
362
 
    conv_buf(Rest, AccB, AccBT, AccW, Col + NSpaces);
363
277
conv_buf([C | Rest], AccBuf, AccBufTail, AccWrite, Col) ->
364
278
    conv_buf(Rest, [C | AccBuf], tl1(AccBufTail), [C | AccWrite], Col + 1).
365
279
 
449
363
           end,
450
364
    [Tcol | Trow].
451
365
 
452
 
%%% write out characters
453
 
%%% make sure that there is data to send
454
 
%%% before calling ssh_connection:send
455
 
write_chars(_, _, []) ->
456
 
    ok;
457
 
write_chars(_, _, [[]]) ->
458
 
    ok;
459
 
write_chars(CM, Channel, Chars) ->
460
 
    Type = 0,
461
 
    ssh_connection:send(CM, Channel, Type, Chars).
 
366
%% %%% write out characters
 
367
%% %%% make sure that there is data to send
 
368
%% %%% before calling ssh_connection:send
 
369
write_chars(ConnectionManager, ChannelId, Chars) ->
 
370
    case erlang:iolist_size(Chars) of
 
371
        0 ->
 
372
            ok;
 
373
       _ ->
 
374
            ssh_connection:send(ConnectionManager, ChannelId, 
 
375
                                ?SSH_EXTENDED_DATA_DEFAULT, Chars)
 
376
    end.
 
377
 
462
378
%%% tail, works with empty lists
463
379
tl1([_|A]) -> A;
464
380
tl1(_) -> [].
489
405
bin_to_list(I) when integer(I) ->
490
406
    I.
491
407
 
492
 
start_shell(CM, State) ->
 
408
start_shell(ConnectionManager, State) ->
493
409
    Shell = State#state.shell,
494
 
    ?dbg(true, "start_shell: self()=~p CM=~p Shell=~p\n",
495
 
         [self(), CM, Shell]),
496
410
    ShellFun = case is_function(Shell) of
497
411
                   true ->
498
412
                       case erlang:fun_info(Shell, arity) of
499
413
                           {arity, 1} ->
500
 
                               {ok, User} = ssh_userreg:lookup_user(CM),
 
414
                               {ok, User} = 
 
415
                                   ssh_userreg:lookup_user(ConnectionManager),
501
416
                               fun() -> Shell(User) end;
502
417
                           {arity, 2} ->
503
 
                               {ok, User} = ssh_userreg:lookup_user(CM),
504
 
                               {ok, PeerAddr} = ssh_cm:get_peer_addr(CM),
 
418
                               {ok, User} = 
 
419
                                   ssh_userreg:lookup_user(ConnectionManager),
 
420
                               {ok, PeerAddr} = 
 
421
                                   ssh_cm:get_peer_addr(ConnectionManager),
505
422
                               fun() -> Shell(User, PeerAddr) end;
506
423
                           _ ->
507
424
                               Shell
513
430
    Group = group:start(self(), ShellFun, [{echo, Echo}]),
514
431
    State#state{group = Group, buf = empty_buf()}.
515
432
 
516
 
check_subsystem(SsName, Options) ->
517
 
    Spec = ssh_sftpd:subsystem_spec(Options),
518
 
    DefaultSubSys = [Spec],
519
 
    Subsystems = proplists:get_value(subsystems, 
520
 
                                     Options, DefaultSubSys),
521
 
    proplists:get_value(SsName, Subsystems, none).
522
 
 
523
 
 
524
433
% Pty can be undefined if the client never sets any pty options before
525
434
% starting the shell.
526
435
get_echo(undefined) ->
527
436
    true;
528
437
get_echo(#ssh_pty{modes = Modes}) ->
529
438
    case proplists:get_value(echo, Modes, 1) of 
530
 
        1 ->
531
 
            true;
532
439
        0 ->
533
 
            false
 
440
            false;
 
441
        _ ->
 
442
            true
534
443
    end.
535
444
 
536
445
% Group is undefined if the pty options are sent between open and
541
450
    Echo = get_echo(Pty),
542
451
    Group ! {self(), echo, Echo}.
543
452
 
544
 
empty_mailbox_workaround(Pid) ->
545
 
    receive 
546
 
        {ssh_cm, _, _} = Msg ->
547
 
            Pid ! Msg,
548
 
            empty_mailbox_workaround(Pid)
549
 
    after 0 ->
550
 
            ok
551
 
    end.
 
453
not_zero(0, B) -> 
 
454
    B;
 
455
not_zero(A, _) -> 
 
456
    A.
552
457
 
 
458
%%% Backwards compatibility
553
459
            
 
460
%%--------------------------------------------------------------------
 
461
%% Function: listen(...) -> {ok,Pid} | ignore | {error,Error}
 
462
%% Description: Starts a listening server
 
463
%% Note that the pid returned is NOT the pid of this gen_server;
 
464
%% this server is started when an SSH connection is made on the
 
465
%% listening port
 
466
%%--------------------------------------------------------------------
 
467
listen(Shell) ->
 
468
    listen(Shell, 22).
 
469
 
 
470
listen(Shell, Port) ->
 
471
    listen(Shell, Port, []).
 
472
 
 
473
listen(Shell, Port, Opts) ->
 
474
    listen(Shell, any, Port, Opts).
 
475
 
 
476
listen(Shell, HostAddr, Port, Opts) ->
 
477
    ssh:daemon(HostAddr, Port, [{shell, Shell} | Opts]).
 
478
    
 
479
 
 
480
%%--------------------------------------------------------------------
 
481
%% Function: stop(Pid) -> ok
 
482
%% Description: Stops the listener
 
483
%%--------------------------------------------------------------------
 
484
stop(Pid) ->
 
485
    ssh:stop_listener(Pid).