~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/inets/httpd_acceptor.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

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: httpd_acceptor.erl,v 1.1 2008/12/17 09:53:33 mikpe Exp $
 
17
%%
 
18
-module(httpd_acceptor).
 
19
 
 
20
-include("httpd.hrl").
 
21
-include("httpd_verbosity.hrl").
 
22
 
 
23
 
 
24
%% External API
 
25
-export([start_link/6]).
 
26
 
 
27
%% Other exports (for spawn's etc.)
 
28
-export([acceptor/4, acceptor/7]).
 
29
 
 
30
 
 
31
%%
 
32
%% External API
 
33
%%
 
34
 
 
35
%% start_link
 
36
 
 
37
start_link(Manager, SocketType, Addr, Port, ConfigDb, Verbosity) ->
 
38
    Args = [self(), Manager, SocketType, Addr, Port, ConfigDb, Verbosity],
 
39
    proc_lib:start_link(?MODULE, acceptor, Args).
 
40
 
 
41
 
 
42
acceptor(Parent, Manager, SocketType, Addr, Port, ConfigDb, Verbosity) ->
 
43
    put(sname,acc),
 
44
    put(verbosity,Verbosity),
 
45
    ?vlog("starting",[]),
 
46
    case (catch do_init(SocketType, Addr, Port)) of
 
47
        {ok, ListenSocket} ->
 
48
            proc_lib:init_ack(Parent, {ok, self()}),
 
49
            acceptor(Manager, SocketType, ListenSocket, ConfigDb);
 
50
        Error ->
 
51
            proc_lib:init_ack(Parent, Error),
 
52
            error
 
53
    end.
 
54
   
 
55
do_init(SocketType, Addr, Port) ->
 
56
    do_socket_start(SocketType),
 
57
    ListenSocket = do_socket_listen(SocketType, Addr, Port),
 
58
    {ok, ListenSocket}.
 
59
 
 
60
 
 
61
do_socket_start(SocketType) ->
 
62
    case httpd_socket:start(SocketType) of
 
63
        ok ->
 
64
            ok;
 
65
        {error, Reason} ->
 
66
            ?vinfo("failed socket start: ~p",[Reason]),
 
67
            throw({error, {socket_start_failed, Reason}})
 
68
    end.
 
69
 
 
70
 
 
71
do_socket_listen(SocketType, Addr, Port) ->
 
72
    case httpd_socket:listen(SocketType, Addr, Port) of
 
73
        {error, Reason} ->
 
74
            ?vinfo("failed socket listen operation: ~p", [Reason]),
 
75
            throw({error, {listen, Reason}});
 
76
        ListenSocket ->
 
77
            ListenSocket
 
78
    end.
 
79
 
 
80
 
 
81
%% acceptor 
 
82
 
 
83
acceptor(Manager, SocketType, ListenSocket, ConfigDb) ->
 
84
    ?vdebug("await connection",[]),
 
85
    case (catch httpd_socket:accept(SocketType, ListenSocket, 30000)) of
 
86
        {error, Reason} ->
 
87
            handle_error(Reason, ConfigDb, SocketType),
 
88
            ?MODULE:acceptor(Manager, SocketType, ListenSocket, ConfigDb);
 
89
 
 
90
        {'EXIT', Reason} ->
 
91
            handle_error({'EXIT', Reason}, ConfigDb, SocketType),
 
92
            ?MODULE:acceptor(Manager, SocketType, ListenSocket, ConfigDb);
 
93
 
 
94
        Socket ->
 
95
            handle_connection(Manager, ConfigDb, SocketType, Socket),
 
96
            ?MODULE:acceptor(Manager, SocketType, ListenSocket, ConfigDb)
 
97
    end.
 
98
 
 
99
 
 
100
handle_connection(Manager, ConfigDb, SocketType, Socket) ->
 
101
    case httpd_request_handler:start_link(Manager, ConfigDb) of
 
102
        {ok, Pid} ->
 
103
            httpd_socket:controlling_process(SocketType, Socket, Pid),
 
104
            httpd_request_handler:synchronize(Pid, SocketType, Socket);
 
105
        {error, Reason} ->
 
106
            handle_connection_err(SocketType, Socket, ConfigDb, Reason)
 
107
    end.
 
108
 
 
109
 
 
110
handle_connection_err(SocketType, Socket, ConfigDb, Reason) ->
 
111
    String = 
 
112
        lists:flatten(
 
113
          io_lib:format("failed starting request handler:~n   ~p", [Reason])),
 
114
    report_error(ConfigDb, String),
 
115
    httpd_socket:close(SocketType, Socket).
 
116
 
 
117
 
 
118
handle_error(timeout, _, _) ->
 
119
    ?vtrace("Accept timeout",[]),
 
120
    ok;
 
121
 
 
122
handle_error({enfile, _}, _, _) ->
 
123
    ?vinfo("Accept error: enfile",[]),
 
124
    %% Out of sockets...
 
125
    sleep(200);
 
126
 
 
127
handle_error(emfile, _, _) ->
 
128
    ?vinfo("Accept error: emfile",[]),
 
129
    %% Too many open files -> Out of sockets...
 
130
    sleep(200);
 
131
 
 
132
handle_error(closed, _, _) ->
 
133
    ?vlog("Accept error: closed",[]),
 
134
    %% This propably only means that the application is stopping, 
 
135
    %% but just in case
 
136
    exit(closed);
 
137
 
 
138
handle_error(econnaborted, _, _) ->
 
139
    ?vlog("Accept aborted",[]),
 
140
    ok;
 
141
 
 
142
handle_error(esslaccept, _, _) ->
 
143
    %% The user has selected to cancel the installation of 
 
144
    %% the certifikate, This is not a real error, so we do 
 
145
    %% not write an error message.
 
146
    ok;
 
147
 
 
148
handle_error({'EXIT', Reason}, ConfigDb, SocketType) ->
 
149
    ?vinfo("Accept exit:~n   ~p",[Reason]),
 
150
    String = lists:flatten(io_lib:format("Accept exit: ~p", [Reason])),
 
151
    accept_failed(SocketType, ConfigDb, String);
 
152
 
 
153
handle_error(Reason, ConfigDb, SocketType) ->
 
154
    ?vinfo("Accept error:~n   ~p",[Reason]),
 
155
    String = lists:flatten(io_lib:format("Accept error: ~p", [Reason])),
 
156
    accept_failed(SocketType, ConfigDb, String).
 
157
 
 
158
 
 
159
accept_failed(SocketType, ConfigDb, String) ->
 
160
    error_logger:error_report(String),
 
161
    mod_log:error_log(SocketType, undefined, ConfigDb, 
 
162
                      {0, "unknown"}, String),
 
163
    mod_disk_log:error_log(SocketType, undefined, ConfigDb, 
 
164
                           {0, "unknown"}, String),
 
165
    exit({accept_failed, String}).
 
166
 
 
167
 
 
168
report_error(Db, String) ->
 
169
    error_logger:error_report(String),
 
170
    mod_log:report_error(Db, String),
 
171
    mod_disk_log:report_error(Db, String).
 
172
    
 
173
 
 
174
sleep(T) -> receive after T -> ok end.
 
175
 
 
176