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

« back to all changes in this revision

Viewing changes to lib/ssh/src/ssh_shell.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
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2009. All Rights Reserved.
 
5
%% 
 
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
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
%%
 
21
 
 
22
-module(ssh_shell).
 
23
 
 
24
-include("ssh_connect.hrl").
 
25
 
 
26
-behaviour(ssh_channel).
 
27
 
 
28
%% ssh_channel callbacks
 
29
-export([init/1, handle_msg/2, handle_ssh_msg/2, terminate/2]).
 
30
 
 
31
%% Spawn export
 
32
-export([input_loop/2]).
 
33
 
 
34
-record(state, 
 
35
        {
 
36
         io,      %% Io process
 
37
         channel, %% Id of the ssh channel
 
38
         cm       %% Ssh connection manager
 
39
         }
 
40
       ).
 
41
 
 
42
%%====================================================================
 
43
%% ssh_channel callbacks
 
44
%%====================================================================
 
45
 
 
46
%%--------------------------------------------------------------------
 
47
%% Function: init(Args) -> {ok, State} 
 
48
%%                        
 
49
%% Description: Initiates the CLI
 
50
%%--------------------------------------------------------------------
 
51
init([ConnectionManager, ChannelId] = Args) ->
 
52
    
 
53
    %% Make sure that we are proclib compatible as
 
54
    %% this client should be runnable from the
 
55
    %% erlang shell.
 
56
    case get('$initial_call') of
 
57
        undefined ->
 
58
            Me = get_my_name(),
 
59
            Ancestors = get_ancestors(),
 
60
            put('$ancestors', [Me | Ancestors]),
 
61
            put('$initial_call', {?MODULE, init, Args});
 
62
        _ ->
 
63
            ok
 
64
    end,
 
65
 
 
66
    case ssh_connection:shell(ConnectionManager, ChannelId) of
 
67
        ok ->
 
68
            {group_leader, GIO} = 
 
69
                process_info(self(), group_leader),
 
70
            IoPid = spawn_link(?MODULE, input_loop,
 
71
                               [GIO, self()]),
 
72
            {ok, #state{io = IoPid, 
 
73
                        channel = ChannelId, 
 
74
                        cm = ConnectionManager}};
 
75
        Error ->
 
76
            {stop, Error}
 
77
    end.
 
78
 
 
79
%%--------------------------------------------------------------------
 
80
%% Function: handle_ssh_msg(Args) -> {ok, State} | {stop, ChannelId, State}
 
81
%%                        
 
82
%% Description: Handles channel messages received on the ssh-connection.
 
83
%%--------------------------------------------------------------------
 
84
handle_ssh_msg({ssh_cm, _, {data, _ChannelId, 0, Data}}, State) ->
 
85
    %% TODO: When unicode support is ready
 
86
    %% should we call this function or perhaps a new
 
87
    %% function.
 
88
    io:put_chars(Data),
 
89
    {ok, State};
 
90
 
 
91
handle_ssh_msg({ssh_cm, _, 
 
92
                {data, _ChannelId, ?SSH_EXTENDED_DATA_STDERR, Data}},
 
93
               State) ->
 
94
    %% TODO: When unicode support is ready
 
95
    %% should we call this function or perhaps a new
 
96
    %% function.
 
97
    io:put_chars(Data),
 
98
    {ok, State};
 
99
 
 
100
handle_ssh_msg({ssh_cm, _, {eof, _ChannelId}}, State) ->
 
101
    {ok, State};
 
102
 
 
103
handle_ssh_msg({ssh_cm, _, {signal, _, _}}, State) ->
 
104
    %% Ignore signals according to RFC 4254 section 6.9.
 
105
    {ok, State};
 
106
 
 
107
handle_ssh_msg({ssh_cm, _, {exit_signal, ChannelId, _, Error, _}}, State) ->
 
108
    io:put_chars("Connection closed by peer"),
 
109
    %% TODO: When unicode support is ready
 
110
    %% should we call this function or perhaps a new
 
111
    %% function. The error is encoded as UTF-8!
 
112
    io:put_chars(Error),
 
113
    {stop, ChannelId,  State};
 
114
 
 
115
handle_ssh_msg({ssh_cm, _, {exit_status, ChannelId, 0}}, State) ->
 
116
    io:put_chars("logout"),
 
117
    io:put_chars("Connection closed"),
 
118
    {stop, ChannelId, State};
 
119
 
 
120
handle_ssh_msg({ssh_cm, _, {exit_status, ChannelId, Status}}, State) ->
 
121
    io:put_chars("Connection closed by peer"),
 
122
    io:put_chars("Status: " ++ integer_to_list(Status)),
 
123
    {stop, ChannelId, State}.
 
124
 
 
125
%%--------------------------------------------------------------------
 
126
%% Function: handle_ssh_msg(Args) -> {ok, State} | {stop, ChannelId, State}
 
127
%%                        
 
128
%% Description: Handles other channel messages
 
129
%%--------------------------------------------------------------------
 
130
handle_msg({ssh_channel_up, ChannelId, ConnectionManager},
 
131
           #state{channel = ChannelId,
 
132
                  cm = ConnectionManager} = State) ->
 
133
    {ok,  State};
 
134
 
 
135
handle_msg({input, IoPid, eof}, #state{io = IoPid, channel = ChannelId, 
 
136
                                       cm = ConnectionManager} = State) ->
 
137
    ssh_connection:send_eof(ConnectionManager, ChannelId),
 
138
    {ok, State};
 
139
 
 
140
handle_msg({input, IoPid, Line}, #state{io = IoPid,
 
141
                                        channel = ChannelId,
 
142
                                        cm = ConnectionManager} = State) ->
 
143
    ssh_connection:send(ConnectionManager, ChannelId, Line),
 
144
    {ok, State}.
 
145
    
 
146
%%--------------------------------------------------------------------
 
147
%% Function: terminate(Reasons, State) -> _
 
148
%%                        
 
149
%% Description: Cleanup when shell channel is terminated
 
150
%%--------------------------------------------------------------------
 
151
terminate(_Reason, #state{io = IoPid}) ->
 
152
    exit(IoPid, kill).
 
153
    
 
154
%%--------------------------------------------------------------------
 
155
%%% Internal functions
 
156
%%--------------------------------------------------------------------
 
157
 
 
158
input_loop(Fd, Pid) ->
 
159
    case io:get_line(Fd, '>') of
 
160
        eof ->
 
161
            Pid ! {input, self(), eof},
 
162
            ok; 
 
163
        Line ->
 
164
            Pid ! {input, self(), Line},
 
165
            input_loop (Fd, Pid)
 
166
    end.
 
167
    
 
168
get_my_name() ->
 
169
    case process_info(self(),registered_name) of
 
170
        {registered_name,Name} -> Name;
 
171
        _                      -> self()
 
172
    end.
 
173
 
 
174
get_ancestors() ->
 
175
    case get('$ancestors') of
 
176
        A when is_list(A) -> A;
 
177
        _              -> []
 
178
    end.