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

« back to all changes in this revision

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

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

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%<copyright>
2
 
%% <year>2007-2007</year>
3
 
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
 
%%</copyright>
5
 
%%<legalnotice>
6
 
%% The contents of this file are subject to the Erlang Public License,
7
 
%% Version 1.1, (the "License"); you may not use this file except in
8
 
%% compliance with the License. You should have received a copy of the
9
 
%% Erlang Public License along with this software. If not, it can be
10
 
%% retrieved online at http://www.erlang.org/.
11
 
%%
12
 
%% Software distributed under the License is distributed on an "AS IS"
13
 
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
 
%% the License for the specific language governing rights and limitations
15
 
%% under the License.
16
 
%%
17
 
%% The Initial Developer of the Original Code is Ericsson AB.
18
 
%%</legalnotice>
19
 
%%
20
 
%% Description: a gen_server implementing a simple
21
 
%% terminal (using the group module) for a CLI
22
 
%% over SSH
23
 
 
24
 
-module(ssh_daemon).
25
 
 
26
 
-behaviour(gen_server).
27
 
 
28
 
-include("ssh.hrl").
29
 
-include("ssh_connect.hrl").
30
 
 
31
 
%% API
32
 
-export([listen/1, listen/2, listen/3, listen/4, stop/1]).
33
 
 
34
 
%% gen_server callbacks
35
 
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
36
 
         terminate/2, code_change/3]).
37
 
 
38
 
%% defines
39
 
-define(DBG_IO_REQUEST, true).
40
 
 
41
 
%% state
42
 
-record(state, {
43
 
          cm,
44
 
          channel,
45
 
          pty,
46
 
          group,
47
 
          buf,
48
 
          opts
49
 
         }).
50
 
 
51
 
%%====================================================================
52
 
%% API
53
 
%%====================================================================
54
 
%%--------------------------------------------------------------------
55
 
%% Function: listen(...) -> {ok,Pid} | ignore | {error,Error}
56
 
%% Description: Starts a listening server
57
 
%% Note that the pid returned is NOT the pid of this gen_server;
58
 
%% this server is started when an SSH connection is made on the
59
 
%% listening port
60
 
%%--------------------------------------------------------------------
61
 
listen() ->
62
 
    listen(22).
63
 
 
64
 
listen(Port) ->
65
 
    listen(Port, []).
66
 
 
67
 
listen(Port, Opts) ->
68
 
    listen(any, Port, Opts).
69
 
 
70
 
listen(Addr, Port, Opts) ->
71
 
    ssh_cm:listen(
72
 
      fun() ->
73
 
              {ok, Pid} =
74
 
                  gen_server:start_link(?MODULE, [Opts], []),
75
 
              Pid
76
 
      end, Addr, Port, Opts).
77
 
 
78
 
%%--------------------------------------------------------------------
79
 
%% Function: stop(Pid) -> ok
80
 
%% Description: Stops the listener
81
 
%%--------------------------------------------------------------------
82
 
stop(Pid) ->
83
 
    ssh_cm:stop_listener(Pid).
84
 
 
85
 
%%====================================================================
86
 
%% gen_server callbacks
87
 
%%====================================================================
88
 
 
89
 
%%--------------------------------------------------------------------
90
 
%% Function: init(Args) -> {ok, State} |
91
 
%%                         {ok, State, Timeout} |
92
 
%%                         ignore               |
93
 
%%                         {stop, Reason}
94
 
%% Description: Initiates the server
95
 
%%--------------------------------------------------------------------
96
 
init([Opts]) ->
97
 
    {ok, #state{opts = Opts}}.
98
 
 
99
 
%%--------------------------------------------------------------------
100
 
%% Function: %% handle_call(Request, From, State) -> {reply, Reply, State} |
101
 
%%                                      {reply, Reply, State, Timeout} |
102
 
%%                                      {noreply, State} |
103
 
%%                                      {noreply, State, Timeout} |
104
 
%%                                      {stop, Reason, Reply, State} |
105
 
%%                                      {stop, Reason, State}
106
 
%% Description: Handling call messages
107
 
%%--------------------------------------------------------------------
108
 
handle_call(stop, _From, State) ->
109
 
    Result = ssh_cm:stop(State#state.cm),
110
 
    {stop, normal, Result, State};
111
 
handle_call(info, _From, State) ->
112
 
    {reply, State, State};
113
 
handle_call(_Request, _From, State) ->
114
 
    Reply = ok,
115
 
    {reply, Reply, State}.
116
 
 
117
 
%%--------------------------------------------------------------------
118
 
%% Function: handle_cast(Msg, State) -> {noreply, State} |
119
 
%%                                      {noreply, State, Timeout} |
120
 
%%                                      {stop, Reason, State}
121
 
%% Description: Handling cast messages
122
 
%%--------------------------------------------------------------------
123
 
handle_cast(_Msg, State) ->
124
 
    {noreply, State}.
125
 
 
126
 
%%--------------------------------------------------------------------
127
 
%% Function: handle_info(Info, State) -> {noreply, State} |
128
 
%%                                       {noreply, State, Timeout} |
129
 
%%                                       {stop, Reason, State}
130
 
%% Description: Handling all non call/cast messages
131
 
%%--------------------------------------------------------------------
132
 
handle_info({ssh_cm, CM, {open, Channel, _RemoteChannel, {session}}}, State) ->
133
 
    ?dbg(true, "session open: self()=~p CM=~p Channel=~p Opts=~p\n",
134
 
         [self(), CM, Channel, Opts]),
135
 
    process_flag(trap_exit, true),
136
 
    {noreply,
137
 
     State#state{cm = CM, channel = Channel}};
138
 
handle_info({ssh_cm, CM, {data, Channel, _Type, Data}}, State) ->
139
 
    ssh_cm:adjust_window(CM, Channel, size(Data)),
140
 
    State#state.group ! {self(), {data, binary_to_list(Data)}},
141
 
    {noreply, State};
142
 
handle_info({ssh_cm, _CM, {pty, _Channel, _WantReply, Pty}}, State) ->
143
 
    {noreply, State#state{pty = Pty}};
144
 
handle_info({ssh_cm, _CM,
145
 
             {window_change, _Channel, Width, Height, PixWidth, PixHeight}},
146
 
            State) ->
147
 
    #state{buf = Buf, pty = Pty, cm = CM, channel = Channel} = State,
148
 
    NewPty = Pty#ssh_pty{width = Width, height = Height,
149
 
                         pixel_width = PixWidth,
150
 
                         pixel_height = PixHeight},
151
 
    {Chars, NewBuf} = io_request({window_change, Pty}, Buf, NewPty),
152
 
    write_chars(CM, Channel, Chars),
153
 
    {noreply, State#state{pty = NewPty, buf = NewBuf}};
154
 
handle_info({Group, Req}, State) when Group==State#state.group ->
155
 
    ?dbg(?DBG_IO_REQUEST, "io_request: ~w\n", [Req]),
156
 
    #state{buf = Buf, pty = Pty, cm = CM, channel = Channel} = State,
157
 
    {Chars, NewBuf} = io_request(Req, Buf, Pty),
158
 
    write_chars(CM, Channel, Chars),
159
 
    {noreply, State#state{buf = NewBuf}};
160
 
handle_info({ssh_cm, CM, {shell}}, State) ->
161
 
    Shell = proplists:get_value(shell, State#state., {shell, start, []}),
162
 
    ShellFun = case is_function(Shell) of
163
 
                   true ->
164
 
                       case erlang:fun_info(Shell, arity) of
165
 
                           {arity, 1} ->
166
 
                               User = ssh_userauth:get_user_from_cm(CM),
167
 
                               fun() -> Shell(User) end;
168
 
                           {arity, 2} ->
169
 
                               User = ssh_userauth:get_user_from_cm(CM),
170
 
                               {ok, PeerAddr} = ssh_cm:get_peer_addr(CM),
171
 
                               fun() -> Shell(User, PeerAddr) end;
172
 
                           _ ->
173
 
                               Shell
174
 
                       end;
175
 
                   _ ->
176
 
                       Shell
177
 
               end,
178
 
    Group = group:start(self(), ShellFun, []),
179
 
    {noreply, State#state{group = Group}};
180
 
handle_info({ssh_cm, CM, {subsystem, _Channel, WantsReply, "sftp"}}, State) ->
181
 
    case WantsReply of
182
 
        true -> CM ! {ssh_cm, self(), {success, State#state.remote_channel}}
183
 
    end,
184
 
    {noreply, State};
185
 
handle_info({ssh_cm, _CM, {exec, Cmd}}, State) ->
186
 
    State#state.group ! {self(), {data, Cmd ++ "\n"}},
187
 
    {noreply, State};
188
 
handle_info({get_cm, From}, #state{cm=CM} = State) ->
189
 
    From ! {From, cm, CM},
190
 
    {noreply, State};
191
 
handle_info({ssh_cm, _CM, {eof, _Channel}}, State) ->
192
 
    {stop, normal, State};
193
 
handle_info({ssh_cm, _CM, {closed, _Channel}}, State) ->
194
 
    %% ignore -- we'll get an {eof, Channel} soon??
195
 
    {noreply, State};
196
 
handle_info({'EXIT', Group, normal},
197
 
            #state{cm=CM, channel=Channel, group=Group} = State) ->
198
 
    ssh_cm:close(CM, Channel),
199
 
    ssh_cm:stop(CM),
200
 
    {stop, normal, State};
201
 
handle_info(Info, State) ->
202
 
    ?dbg(true, "~p:handle_info: BAD info ~p\n(State ~p)\n", [?MODULE, Info, State]),
203
 
    {stop, {bad_info, Info}, State}.
204
 
 
205
 
%%--------------------------------------------------------------------
206
 
%% Function: terminate(Reason, State) -> void()
207
 
%% Description: This function is called by a gen_server when it is about to
208
 
%% terminate. It should be the opposite of Module:init/1 and do any necessary
209
 
%% cleaning up. When it returns, the gen_server terminates with Reason.
210
 
%% The return value is ignored.
211
 
%%--------------------------------------------------------------------
212
 
terminate(_Reason, _State) ->
213
 
    ok.
214
 
 
215
 
%%--------------------------------------------------------------------
216
 
%% Func: code_change(OldVsn, State, Extra) -> {ok, NewState}
217
 
%% Description: Convert process state when code is changed
218
 
%%--------------------------------------------------------------------
219
 
code_change(_OldVsn, State, _Extra) ->
220
 
    {ok, State}.