~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
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>2005-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
 
 
21
 
%%% Description: tcp listen and accept-loop
22
 
 
23
 
-module(ssh_tcp_wrap).
24
 
 
25
 
-export([spawn_server/3, server/4]).
26
 
-export([server_init/4, server_loop/3, accept_loop/4]). %% helper
27
 
 
28
 
-define(ACCEPT_TIMEOUT, 10000).
29
 
 
30
 
%% Spawn the server loop
31
 
spawn_server(Port, Opts, Fun) ->
32
 
    Pid = spawn(?MODULE, server_init, [self(),Port,Opts,Fun]),
33
 
    Ref = erlang:monitor(process, Pid),
34
 
    receive
35
 
        {'DOWN', Ref, _, _, Reason} ->
36
 
            {error, Reason};
37
 
        {Pid, Reply} ->
38
 
            erlang:demonitor(Ref),
39
 
            Reply
40
 
    end.
41
 
 
42
 
server_init(Starter, Port, Opts, Fun) ->
43
 
    case gen_tcp:listen(Port, Opts) of
44
 
        {ok, Listen} ->
45
 
            if Port == 0 ->
46
 
                    case inet:sockname(Listen) of
47
 
                        {ok, {_,Port1}} -> 
48
 
                            Starter ! {self(), {ok,self(),Port1}},
49
 
                            server_loop(self(), Listen, Fun);
50
 
                        Error ->
51
 
                            gen_tcp:close(Listen),
52
 
                            Starter ! {self(), Error}
53
 
                    end;
54
 
               true ->
55
 
                    Starter ! {self(), {ok,self(),Port}},
56
 
                    server_loop(self(), Listen, Fun)
57
 
            end;
58
 
        Error ->
59
 
            error_logger:format(
60
 
              "Failed to listen on port: ~p opts:~p: rsn:~p~n",
61
 
              [Port, Opts,Error]),
62
 
            Starter ! {self(), Error}
63
 
    end.
64
 
 
65
 
 
66
 
%% Run the server loop
67
 
server(Port, Opts, Fun, From) ->
68
 
    case gen_tcp:listen(Port, Opts) of
69
 
        {ok, Listen} ->
70
 
            From ! ok,
71
 
            server_loop(self(), Listen, Fun);
72
 
        Error ->
73
 
            error_logger:format(
74
 
              "Failed to listen on port: ~p opts:~p: rsn:~p~n",
75
 
              [Port, Opts,Error]),
76
 
            From ! Error
77
 
    end.
78
 
 
79
 
server_loop(User, Listen, Fun) ->
80
 
    Pid = spawn(fun() -> 
81
 
                        ?MODULE:accept_loop(User, erlang:monitor(process,User),
82
 
                                            Listen, Fun)
83
 
                end),
84
 
    Ref = erlang:monitor(process, Pid),
85
 
    receive
86
 
        {'DOWN', Ref, _, _, _Reason} ->
87
 
            ?MODULE:server_loop(User, Listen, Fun);
88
 
        {Pid, stop} ->
89
 
            stopped;
90
 
        {User, stop} ->
91
 
            stopped;
92
 
        {Pid, _Result} ->
93
 
            erlang:demonitor(Ref),
94
 
            ?MODULE:server_loop(User, Listen, Fun)
95
 
    end.
96
 
 
97
 
accept_loop(User, Ref, Listen, Fun) ->
98
 
    %% Timeout makes it possible to replace this module
99
 
    %% once every ?ACCEPT_TIMEOUT milliseconds
100
 
    case gen_tcp:accept(Listen, ?ACCEPT_TIMEOUT) of
101
 
        {ok, S} ->
102
 
            %% poll if 'User' is still alive
103
 
            receive
104
 
                {'DOWN', Ref, _, _, Reason} ->
105
 
                    gen_tcp:close(S),
106
 
                    exit(Reason)
107
 
            after 0 ->
108
 
                    User ! {self(), ok},
109
 
                    Fun(S)
110
 
            end;
111
 
        {error, timeout} ->
112
 
            %% poll if 'User' is still alive
113
 
            receive
114
 
                {'DOWN', Ref, _, _, Reason} ->
115
 
                    exit(Reason)
116
 
            after 0 ->
117
 
                    ?MODULE:accept_loop(User, Ref, Listen, Fun)
118
 
            end;
119
 
        {error, closed} ->
120
 
            Listen ! {self(), stop};
121
 
        Error ->
122
 
            Listen ! {self(), Error}
123
 
    end.