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

« back to all changes in this revision

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