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

« back to all changes in this revision

Viewing changes to lib/ssh/src/ssh_ssh.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 shell client
 
20
 
 
21
-module(ssh_ssh).
 
22
 
 
23
-export([connect/1, connect/2, connect/3]).
 
24
 
 
25
-export([input_loop/2, shell_loop/4]).
 
26
 
 
27
-include("ssh.hrl").
 
28
-include("ssh_connect.hrl").
 
29
 
 
30
-define(default_timeout, 10000).
 
31
 
 
32
connect(A) ->
 
33
    connect(A, []).
 
34
 
 
35
connect(CM, Opts) when is_pid(Opts) ->
 
36
    Timeout = proplists:get_value(connect_timeout, Opts, ?default_timeout),
 
37
    case ssh_cm:attach(CM, Timeout) of
 
38
        {ok,CMPid} ->
 
39
            session(CMPid, Timeout);
 
40
        Error ->
 
41
            Error
 
42
    end;
 
43
connect(Host, Opts) ->
 
44
    connect(Host, 22, Opts).
 
45
 
 
46
connect(Host, Port, Opts) ->
 
47
    case ssh_cm:connect(Host, Port, Opts) of
 
48
        {ok, CM} ->
 
49
            session(CM, proplists:get_value(connect_timeout,
 
50
                                            Opts, ?default_timeout));
 
51
        Error ->
 
52
            Error
 
53
    end.
 
54
 
 
55
session(CM, Timeout) ->
 
56
    case ssh_cm:session_open(CM, Timeout) of
 
57
        {ok,Channel}  ->
 
58
            case ssh_cm:shell(CM, Channel) of
 
59
                ok ->
 
60
                    {group_leader,GIO} = 
 
61
                        process_info(self(), group_leader),
 
62
                    IO = spawn(?MODULE, input_loop,
 
63
                               [GIO, self()]),
 
64
                    shell_loop(CM, Channel, IO, false);
 
65
                Error  ->
 
66
                    ssh_cm:close(CM, Channel),
 
67
                    Error
 
68
            end;
 
69
        Error ->
 
70
            Error
 
71
    end.
 
72
 
 
73
 
 
74
input_loop(Fd, Pid) ->
 
75
    case io:get_line(Fd, '>') of
 
76
        eof ->
 
77
            Pid ! {input, self(), eof},
 
78
            ok; % input_loop(Fd, Pid);
 
79
        Line ->
 
80
            Pid ! {input, self(), Line},
 
81
            input_loop(Fd, Pid)
 
82
    end.
 
83
    
 
84
 
 
85
shell_loop(CM, Channel, IO, SentClose) ->
 
86
    receive
 
87
        {input, IO, eof} ->
 
88
            ssh_cm:send_eof(CM, Channel),
 
89
            ?MODULE:shell_loop(CM, Channel, IO, SentClose);
 
90
            
 
91
        {input, IO, Line} ->
 
92
            ssh_cm:send(CM, Channel, Line),
 
93
            ?MODULE:shell_loop(CM, Channel, IO, SentClose);
 
94
 
 
95
        {ssh_cm, CM, {data, Channel, Type, Data}} ->
 
96
            if Type == 0 ->
 
97
                    io:format("~s", [binary_to_list(Data)]);
 
98
               Type == ?SSH_EXTENDED_DATA_STDERR ->
 
99
                    error_logger:format("ssh: STDERR: ~s", 
 
100
                                        [binary_to_list(Data)]);
 
101
               true ->
 
102
                    ok
 
103
            end,
 
104
            ssh_cm:adjust_window(CM, Channel, size(Data)),
 
105
            ?MODULE:shell_loop(CM, Channel, IO, SentClose);
 
106
 
 
107
        {ssh_cm, CM, {exit_signal, Channel, _SIG, _Err, _Lang}} ->
 
108
            ?dbg(true, "SIGNAL: ~s (~s)\n", [_SIG, _Err]),
 
109
            send_close(SentClose, CM, Channel),
 
110
            ?MODULE:shell_loop(CM, Channel, IO, true);
 
111
 
 
112
        {ssh_cm, CM, {exit_status,Channel,_Status}} ->
 
113
            %send_close(SentClose, CM, Channel),
 
114
            ?MODULE:shell_loop(CM, Channel, IO, true);
 
115
 
 
116
        {ssh_cm, CM, {eof, Channel}} ->
 
117
            %send_close(SentClose, CM, Channel),
 
118
            ?MODULE:shell_loop(CM, Channel, IO, true);
 
119
 
 
120
        {ssh_cm, CM, {closed, Channel}} ->
 
121
            ssh_cm:detach(CM, ?default_timeout),
 
122
            exit(IO, kill);
 
123
 
 
124
        Other ->
 
125
            error_logger:format("ssh_ssh:shell_loop: unexpected msg ~p\n", [Other])
 
126
    end.
 
127
 
 
128
send_close(false, CM, Channel) ->
 
129
    ssh_cm:close(CM, Channel);
 
130
send_close(_, _, _) ->
 
131
    ok.