~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_manager.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_manager.erl,v 1.1 2008/12/17 09:53:34 mikpe Exp $
 
17
%%
 
18
 
 
19
-module(httpd_manager).
 
20
 
 
21
-include("httpd.hrl").
 
22
-include("httpd_verbosity.hrl").
 
23
 
 
24
-behaviour(gen_server).
 
25
 
 
26
%% External API
 
27
-export([start/2, start/3, start_link/2, start_link/3, stop/1, restart/1]).
 
28
 
 
29
%% Internal API
 
30
-export([new_connection/1, done_connection/1]).
 
31
 
 
32
%% Module API
 
33
-export([config_lookup/2, config_lookup/3, 
 
34
         config_multi_lookup/2, config_multi_lookup/3, 
 
35
         config_match/2, config_match/3]).
 
36
 
 
37
%% gen_server exports
 
38
-export([init/1, 
 
39
         handle_call/3, handle_cast/2, handle_info/2, 
 
40
         terminate/2,
 
41
         code_change/3]).
 
42
 
 
43
 
 
44
%% Management exports
 
45
-export([block/2, block/3, unblock/1]).
 
46
-export([get_admin_state/1, get_usage_state/1]).
 
47
-export([is_busy/1,is_busy/2,is_busy_or_blocked/1,is_blocked/1]). %% ???????
 
48
-export([get_status/1, get_status/2]).
 
49
-export([verbosity/2, verbosity/3]).
 
50
 
 
51
 
 
52
-export([c/1]).
 
53
 
 
54
-record(state,{socket_type  = ip_comm,
 
55
               config_file,
 
56
               config_db    = null,
 
57
               connections, %% Current request handlers
 
58
               admin_state  = unblocked,
 
59
               blocker_ref  = undefined,
 
60
               blocking_tmr = undefined,
 
61
               status       = []}).
 
62
 
 
63
 
 
64
c(Port) ->
 
65
    Ref = httpd_util:make_name("httpd",undefined,Port),
 
66
    gen_server:call(Ref, fake_close).
 
67
 
 
68
 
 
69
%%
 
70
%% External API
 
71
%%
 
72
 
 
73
start(ConfigFile, ConfigList) ->
 
74
    start(ConfigFile, ConfigList, []).
 
75
 
 
76
start(ConfigFile, ConfigList, Verbosity) ->
 
77
    Port = httpd_util:key1search(ConfigList,port,80),
 
78
    Addr = httpd_util:key1search(ConfigList,bind_address),
 
79
    Name = make_name(Addr,Port),
 
80
    ?LOG("start -> Name = ~p",[Name]),
 
81
    gen_server:start({local,Name},?MODULE,
 
82
                     [ConfigFile, ConfigList, Addr, Port, Verbosity],[]).
 
83
    
 
84
start_link(ConfigFile, ConfigList) ->
 
85
    start_link(ConfigFile, ConfigList, []).
 
86
    
 
87
start_link(ConfigFile, ConfigList, Verbosity) ->
 
88
    Port = httpd_util:key1search(ConfigList,port,80),
 
89
    Addr = httpd_util:key1search(ConfigList,bind_address),
 
90
    Name = make_name(Addr,Port),
 
91
    ?LOG("start_link -> Name = ~p",[Name]),
 
92
    gen_server:start_link({local, Name},?MODULE,
 
93
                          [ConfigFile, ConfigList, Addr, Port, Verbosity],[]).
 
94
    
 
95
%% stop
 
96
 
 
97
stop(ServerRef) ->
 
98
    gen_server:call(ServerRef, stop).
 
99
 
 
100
%% restart
 
101
 
 
102
restart(ServerRef) ->
 
103
    gen_server:call(ServerRef, restart).
 
104
 
 
105
 
 
106
%%%----------------------------------------------------------------
 
107
 
 
108
block(ServerRef, disturbing) ->
 
109
    call(ServerRef,block);
 
110
 
 
111
block(ServerRef, non_disturbing) ->
 
112
    do_block(ServerRef, non_disturbing, infinity).
 
113
 
 
114
block(ServerRef, Method, Timeout) ->
 
115
    do_block(ServerRef, Method, Timeout).
 
116
 
 
117
 
 
118
%% The reason for not using call here, is that the manager cannot
 
119
%% _wait_ for completion of the requests. It must be able to do
 
120
%% do other things at the same time as the blocking goes on.
 
121
do_block(ServerRef, Method, infinity) ->
 
122
    Ref = make_ref(),
 
123
    cast(ServerRef, {block, Method, infinity, self(), Ref}),
 
124
    receive
 
125
        {block_reply, Reply, Ref} ->
 
126
            Reply
 
127
    end;
 
128
do_block(ServerRef,Method,Timeout) when Timeout > 0 ->
 
129
    Ref = make_ref(),
 
130
    cast(ServerRef,{block,Method,Timeout,self(),Ref}),
 
131
    receive
 
132
        {block_reply,Reply,Ref} ->
 
133
            Reply
 
134
    end.
 
135
 
 
136
 
 
137
%%%----------------------------------------------------------------
 
138
 
 
139
%% unblock
 
140
 
 
141
unblock(ServerRef) ->
 
142
    call(ServerRef,unblock).
 
143
 
 
144
%% get admin/usage state
 
145
 
 
146
get_admin_state(ServerRef) ->
 
147
    call(ServerRef,get_admin_state).
 
148
 
 
149
get_usage_state(ServerRef) ->
 
150
    call(ServerRef,get_usage_state).
 
151
 
 
152
 
 
153
%% get_status
 
154
 
 
155
get_status(ServerRef) ->
 
156
    gen_server:call(ServerRef,get_status).
 
157
 
 
158
get_status(ServerRef,Timeout) ->
 
159
    gen_server:call(ServerRef,get_status,Timeout).
 
160
 
 
161
 
 
162
verbosity(ServerRef,Verbosity) ->
 
163
    verbosity(ServerRef,all,Verbosity).
 
164
 
 
165
verbosity(ServerRef,all,Verbosity) ->
 
166
    gen_server:call(ServerRef,{verbosity,all,Verbosity});
 
167
verbosity(ServerRef,manager,Verbosity) ->
 
168
    gen_server:call(ServerRef,{verbosity,manager,Verbosity});
 
169
verbosity(ServerRef,request,Verbosity) ->
 
170
    gen_server:call(ServerRef,{verbosity,request,Verbosity});
 
171
verbosity(ServerRef,acceptor,Verbosity) ->
 
172
    gen_server:call(ServerRef,{verbosity,acceptor,Verbosity});
 
173
verbosity(ServerRef,security,Verbosity) ->
 
174
    gen_server:call(ServerRef,{verbosity,security,Verbosity});
 
175
verbosity(ServerRef,auth,Verbosity) ->
 
176
    gen_server:call(ServerRef,{verbosity,auth,Verbosity}).
 
177
 
 
178
%%
 
179
%% Internal API
 
180
%%
 
181
 
 
182
 
 
183
%% new_connection
 
184
 
 
185
new_connection(Manager) ->
 
186
    gen_server:call(Manager, {new_connection, self()}).
 
187
 
 
188
%% done
 
189
 
 
190
done_connection(Manager) ->
 
191
    gen_server:cast(Manager, {done_connection, self()}).
 
192
 
 
193
 
 
194
%% is_busy(ServerRef) -> true | false
 
195
%% 
 
196
%% Tests if the server is (in usage state) busy, 
 
197
%% i.e. has rached the heavy load limit.
 
198
%% 
 
199
 
 
200
is_busy(ServerRef) ->
 
201
    gen_server:call(ServerRef,is_busy).
 
202
    
 
203
is_busy(ServerRef,Timeout) ->
 
204
    gen_server:call(ServerRef,is_busy,Timeout).
 
205
 
 
206
 
 
207
%% is_busy_or_blocked(ServerRef) -> busy | blocked | false
 
208
%% 
 
209
%% Tests if the server is busy (usage state), i.e. has rached,
 
210
%% the heavy load limit, or blocked (admin state) .
 
211
%% 
 
212
 
 
213
is_busy_or_blocked(ServerRef) ->
 
214
    gen_server:call(ServerRef,is_busy_or_blocked).
 
215
    
 
216
 
 
217
%% is_blocked(ServerRef) -> true | false
 
218
%% 
 
219
%% Tests if the server is blocked (admin state) .
 
220
%% 
 
221
 
 
222
is_blocked(ServerRef) ->
 
223
    gen_server:call(ServerRef,is_blocked).
 
224
    
 
225
 
 
226
%%
 
227
%% Module API. Theese functions are intended for use from modules only.
 
228
%%
 
229
 
 
230
config_lookup(Port, Query) ->
 
231
    config_lookup(undefined, Port, Query).
 
232
config_lookup(Addr, Port, Query) ->
 
233
    Name = httpd_util:make_name("httpd",Addr,Port),
 
234
    gen_server:call(whereis(Name), {config_lookup, Query}).
 
235
 
 
236
config_multi_lookup(Port, Query) ->
 
237
    config_multi_lookup(undefined,Port,Query).
 
238
config_multi_lookup(Addr,Port, Query) ->
 
239
    Name = httpd_util:make_name("httpd",Addr,Port),
 
240
    gen_server:call(whereis(Name), {config_multi_lookup, Query}).
 
241
 
 
242
config_match(Port, Pattern) ->
 
243
    config_match(undefined,Port,Pattern).
 
244
config_match(Addr, Port, Pattern) ->
 
245
    Name = httpd_util:make_name("httpd",Addr,Port),
 
246
    gen_server:call(whereis(Name), {config_match, Pattern}).
 
247
 
 
248
 
 
249
%%
 
250
%% Server call-back functions
 
251
%%
 
252
 
 
253
%% init
 
254
 
 
255
init([ConfigFile, ConfigList, Addr, Port, Verbosity]) ->
 
256
    process_flag(trap_exit, true),
 
257
    case (catch do_init(ConfigFile, ConfigList, Addr, Port, Verbosity)) of
 
258
        {error, Reason} ->
 
259
            ?vlog("failed starting server: ~p", [Reason]),
 
260
            {stop, Reason};
 
261
        {ok, State} ->
 
262
            {ok, State}
 
263
    end.
 
264
   
 
265
 
 
266
do_init(ConfigFile, ConfigList, Addr, Port, Verbosity) ->
 
267
    put(sname,man),
 
268
    set_verbosity(Verbosity),
 
269
    ?vlog("starting",[]),
 
270
    ConfigDB   = do_initial_store(ConfigList),
 
271
    ?vtrace("config db: ~p", [ConfigDB]),
 
272
    SocketType = httpd_socket:config(ConfigDB),
 
273
    ?vtrace("socket type: ~p, now start acceptor", [SocketType]),
 
274
    case httpd_acceptor_sup:start_acceptor(SocketType, Addr, Port, ConfigDB) of
 
275
        {ok, Pid} ->
 
276
            ?vtrace("acceptor started: ~p", [Pid]),
 
277
            Status = [{max_conn,0}, {last_heavy_load,never}, 
 
278
                      {last_connection,never}],
 
279
            State  = #state{socket_type = SocketType,
 
280
                            config_file = ConfigFile,
 
281
                            config_db   = ConfigDB,
 
282
                            connections = [],
 
283
                            status      = Status},
 
284
            ?vdebug("started",[]),
 
285
            {ok, State};
 
286
        Else ->
 
287
            Else
 
288
    end.
 
289
 
 
290
 
 
291
do_initial_store(ConfigList) ->
 
292
    case httpd_conf:store(ConfigList) of
 
293
        {ok, ConfigDB} ->
 
294
            ConfigDB;
 
295
        {error, Reason} ->
 
296
            ?vinfo("failed storing configuration: ~p",[Reason]),
 
297
            throw({error, Reason})
 
298
    end.
 
299
 
 
300
   
 
301
 
 
302
%% handle_call
 
303
 
 
304
handle_call(stop, _From, State) ->
 
305
    ?vlog("stop",[]),
 
306
    {stop, normal, ok, State};
 
307
 
 
308
handle_call({config_lookup, Query}, _From, State) ->
 
309
    ?vlog("config lookup: Query = ~p",[Query]),
 
310
    Res = httpd_util:lookup(State#state.config_db, Query),
 
311
    ?vdebug("config lookup result: ~p",[Res]),
 
312
    {reply, Res, State};
 
313
 
 
314
handle_call({config_multi_lookup, Query}, _From, State) ->
 
315
    ?vlog("multi config lookup: Query = ~p",[Query]),
 
316
    Res = httpd_util:multi_lookup(State#state.config_db, Query),
 
317
    ?vdebug("multi config lookup result: ~p",[Res]),
 
318
    {reply, Res, State};
 
319
 
 
320
handle_call({config_match, Query}, _From, State) ->
 
321
    ?vlog("config match: Query = ~p",[Query]),
 
322
    Res = ets:match_object(State#state.config_db, Query),
 
323
    ?vdebug("config match result: ~p",[Res]),
 
324
    {reply, Res, State};
 
325
 
 
326
handle_call(get_status, _From, State) ->
 
327
    ?vdebug("get status",[]),
 
328
    ManagerStatus  = manager_status(self()),
 
329
    %% AuthStatus     = auth_status(get(auth_server)),
 
330
    %% SecStatus      = sec_status(get(sec_server)),
 
331
    %% AccStatus      = sec_status(get(acceptor_server)),
 
332
    S1 = [{current_conn,length(State#state.connections)}|State#state.status]++
 
333
        [ManagerStatus],
 
334
    ?vtrace("status = ~p",[S1]),
 
335
    {reply,S1,State};
 
336
 
 
337
handle_call(is_busy, From, State) ->
 
338
    Reply = case get_ustate(State) of
 
339
                busy ->
 
340
                    true;
 
341
                _ ->
 
342
                    false
 
343
          end,
 
344
    ?vlog("is busy: ~p",[Reply]),
 
345
    {reply,Reply,State};
 
346
 
 
347
handle_call(is_busy_or_blocked, From, State) ->
 
348
    Reply = 
 
349
        case get_astate(State) of
 
350
            unblocked ->
 
351
                case get_ustate(State) of
 
352
                    busy ->
 
353
                        busy;
 
354
                    _ ->
 
355
                        false
 
356
                end;
 
357
            _ ->
 
358
                blocked
 
359
          end,
 
360
    ?vlog("is busy or blocked: ~p",[Reply]),
 
361
    {reply,Reply,State};
 
362
 
 
363
handle_call(is_blocked, From, State) ->
 
364
    Reply = 
 
365
        case get_astate(State) of
 
366
            unblocked ->
 
367
                false;
 
368
            _ ->
 
369
                true
 
370
          end,
 
371
    ?vlog("is blocked: ~p",[Reply]),
 
372
    {reply,Reply,State};
 
373
 
 
374
handle_call(get_admin_state, From, State) ->
 
375
    Reply = get_astate(State),
 
376
    ?vlog("admin state: ~p",[Reply]),
 
377
    {reply,Reply,State};
 
378
 
 
379
handle_call(get_usage_state, From, State) ->
 
380
    Reply = get_ustate(State),
 
381
    ?vlog("usage state: ~p",[Reply]),
 
382
    {reply,Reply,State};
 
383
 
 
384
handle_call({verbosity,Who,Verbosity}, From, State) ->
 
385
    V = ?vvalidate(Verbosity),
 
386
    ?vlog("~n   Set new verbosity to ~p for ~p",[V,Who]),
 
387
    Reply = set_verbosity(Who,V,State),
 
388
    {reply,Reply,State};
 
389
 
 
390
handle_call(restart, From, State) when State#state.admin_state == blocked ->
 
391
    ?vlog("restart",[]),
 
392
    case handle_restart(State) of
 
393
        {stop, Reply,S1} ->
 
394
            {stop, Reply, S1};
 
395
        {_, Reply, S1} ->
 
396
            {reply,Reply,S1}
 
397
    end;
 
398
 
 
399
handle_call(restart, From, State) ->
 
400
    ?vlog("restart(~p)",[State#state.admin_state]),
 
401
    {reply,{error,{invalid_admin_state,State#state.admin_state}},State};
 
402
 
 
403
handle_call(block, From, State) ->
 
404
    ?vlog("block(disturbing)",[]),
 
405
    {Reply,S1} = handle_block(State),
 
406
    {reply,Reply,S1};
 
407
 
 
408
handle_call(unblock, {From,_Tag}, State) ->
 
409
    ?vlog("unblock",[]),
 
410
    {Reply,S1} = handle_unblock(State,From),
 
411
    {reply, Reply, S1};
 
412
 
 
413
handle_call({new_connection, Pid}, From, State) ->
 
414
    ?vlog("~n   New connection (~p) when connection count = ~p",
 
415
          [Pid,length(State#state.connections)]),
 
416
    {S, S1} = handle_new_connection(State, Pid),
 
417
    Reply = {S, get(request_handler_verbosity)},
 
418
    {reply, Reply, S1};
 
419
 
 
420
handle_call(Request, From, State) ->
 
421
    ?vinfo("~n   unknown request '~p' from ~p", [Request,From]),
 
422
    String = 
 
423
        lists:flatten(
 
424
          io_lib:format("Unknown request "
 
425
                        "~n   ~p"
 
426
                        "~nto manager (~p)"
 
427
                        "~nfrom ~p",
 
428
                        [Request, self(), From])),
 
429
    report_error(State,String),
 
430
    {reply, ok, State}.
 
431
 
 
432
 
 
433
%% handle_cast
 
434
 
 
435
handle_cast({done_connection, Pid}, State) ->
 
436
    ?vlog("~n   Done connection (~p)", [Pid]),
 
437
    S1 = handle_done_connection(State, Pid),
 
438
    {noreply, S1};
 
439
 
 
440
handle_cast({block, disturbing, Timeout, From, Ref}, State) ->
 
441
    ?vlog("block(disturbing,~p)",[Timeout]),
 
442
    S1 = handle_block(State, Timeout, From, Ref),
 
443
    {noreply,S1};
 
444
 
 
445
handle_cast({block, non_disturbing, Timeout, From, Ref}, State) ->
 
446
    ?vlog("block(non-disturbing,~p)",[Timeout]),
 
447
    S1 = handle_nd_block(State, Timeout, From, Ref),
 
448
    {noreply,S1};
 
449
 
 
450
handle_cast(Message, State) ->
 
451
    ?vinfo("~n   received unknown message '~p'",[Message]),
 
452
    String = 
 
453
        lists:flatten(
 
454
          io_lib:format("Unknown message "
 
455
                        "~n   ~p"
 
456
                        "~nto manager (~p)",
 
457
                        [Message, self()])),
 
458
    report_error(State, String),
 
459
    {noreply, State}.
 
460
 
 
461
%% handle_info
 
462
 
 
463
handle_info({block_timeout, Method}, State) ->
 
464
    ?vlog("received block_timeout event",[]),
 
465
    S1 = handle_block_timeout(State,Method),
 
466
    {noreply, S1};
 
467
 
 
468
handle_info({'DOWN', Ref, process, _Object, Info}, State) ->
 
469
    ?vlog("~n   down message for ~p",[Ref]),
 
470
    S1 = 
 
471
        case State#state.blocker_ref of
 
472
            Ref ->
 
473
                handle_blocker_exit(State);
 
474
            _ ->
 
475
                %% Not our blocker, so ignore
 
476
                State
 
477
        end,
 
478
    {noreply, S1};
 
479
 
 
480
handle_info({'EXIT', Pid, normal}, State) ->
 
481
    ?vdebug("~n   Normal exit message from ~p", [Pid]),
 
482
    {noreply, State};
 
483
 
 
484
handle_info({'EXIT', Pid, blocked}, S) ->
 
485
    ?vdebug("blocked exit signal from request handler (~p)", [Pid]),
 
486
    {noreply, S};
 
487
 
 
488
handle_info({'EXIT', Pid, Reason}, State) ->
 
489
    ?vlog("~n   Exit message from ~p for reason ~p",[Pid, Reason]),
 
490
    S1 = check_connections(State, Pid, Reason),
 
491
    {noreply, S1};
 
492
 
 
493
handle_info(Info, State) ->
 
494
    ?vinfo("~n   received unknown info '~p'",[Info]),
 
495
    String = 
 
496
        lists:flatten(
 
497
          io_lib:format("Unknown info "
 
498
                        "~n   ~p"
 
499
                        "~nto manager (~p)",
 
500
                        [Info, self()])),
 
501
    report_error(State, String),
 
502
    {noreply, State}.
 
503
 
 
504
 
 
505
%% terminate
 
506
 
 
507
terminate(R, #state{config_db = Db}) -> 
 
508
    ?vlog("Terminating for reason: ~n   ~p", [R]),
 
509
    httpd_conf:remove_all(Db),
 
510
    ok.
 
511
 
 
512
 
 
513
%% code_change({down,ToVsn}, State, Extra)
 
514
%% 
 
515
%% NOTE:
 
516
%% Actually upgrade from 2.5.1 to 2.5.3 and downgrade from 
 
517
%% 2.5.3 to 2.5.1 is done with an application restart, so 
 
518
%% these function is actually never used. The reason for keeping
 
519
%% this stuff is only for future use.
 
520
%%
 
521
code_change({down,ToVsn},State,Extra) ->
 
522
    {ok,State};
 
523
 
 
524
%% code_change(FromVsn, State, Extra)
 
525
%%
 
526
code_change(FromVsn,State,Extra) ->
 
527
    {ok,State}.
 
528
 
 
529
 
 
530
 
 
531
%% -------------------------------------------------------------------------
 
532
%% check_connection
 
533
%%
 
534
%%
 
535
%%
 
536
%%
 
537
 
 
538
check_connections(#state{connections = []} = State, _Pid, _Reason) ->
 
539
    State;
 
540
check_connections(#state{admin_state = shutting_down,
 
541
                         connections = Connections} = State, Pid, Reason) ->
 
542
    %% Could be a crashing request handler
 
543
    case lists:delete(Pid, Connections) of
 
544
        [] -> % Crashing request handler => block complete
 
545
            String = 
 
546
                lists:flatten(
 
547
                  io_lib:format("request handler (~p) crashed:"
 
548
                                "~n   ~p", [Pid, Reason])),
 
549
            report_error(State, String),
 
550
            ?vlog("block complete",[]),
 
551
            demonitor_blocker(State#state.blocker_ref),
 
552
            {Tmr,From,Ref} = State#state.blocking_tmr,
 
553
            ?vlog("(possibly) stop block timer",[]),
 
554
            stop_block_tmr(Tmr),
 
555
            ?vlog("and send the reply",[]),
 
556
            From ! {block_reply,ok,Ref},
 
557
            State#state{admin_state = blocked, connections = [],
 
558
                        blocker_ref = undefined};
 
559
        Connections1 ->
 
560
            State#state{connections = Connections1}
 
561
    end;
 
562
check_connections(#state{connections = Connections} = State, Pid, Reason) ->
 
563
    case lists:delete(Pid, Connections) of
 
564
        Connections -> % Not a request handler, so ignore
 
565
            State;
 
566
        Connections1 ->
 
567
            String = 
 
568
                lists:flatten(
 
569
                  io_lib:format("request handler (~p) crashed:"
 
570
                                "~n   ~p", [Pid, Reason])),
 
571
            report_error(State, String),
 
572
            State#state{connections = lists:delete(Pid, Connections)}
 
573
    end.
 
574
 
 
575
 
 
576
%% -------------------------------------------------------------------------
 
577
%% handle_[new | done]_connection
 
578
%%
 
579
%%
 
580
%%
 
581
%%
 
582
 
 
583
handle_new_connection(State, Handler) ->
 
584
    UsageState = get_ustate(State),
 
585
    AdminState = get_astate(State),
 
586
    handle_new_connection(UsageState, AdminState, State, Handler).
 
587
 
 
588
handle_new_connection(busy, unblocked, State, Handler) ->
 
589
    Status = update_heavy_load_status(State#state.status),
 
590
    {{reject, busy}, 
 
591
     State#state{status = Status}};
 
592
 
 
593
handle_new_connection(_UsageState, unblocked, State, Handler) ->
 
594
    Connections = State#state.connections,
 
595
    Status      = update_connection_status(State#state.status, 
 
596
                                           length(Connections)+1),
 
597
    link(Handler),
 
598
    {accept, 
 
599
     State#state{connections = [Handler|Connections], status = Status}};
 
600
 
 
601
handle_new_connection(_UsageState, _AdminState, State, _Handler) ->
 
602
    {{reject, blocked}, 
 
603
     State}.
 
604
 
 
605
 
 
606
handle_done_connection(#state{admin_state = shutting_down,
 
607
                              connections = Connections} = State, Handler) ->
 
608
    unlink(Handler),
 
609
    case lists:delete(Handler, Connections) of
 
610
        [] -> % Ok, block complete
 
611
            ?vlog("block complete",[]),
 
612
            demonitor_blocker(State#state.blocker_ref),
 
613
            {Tmr,From,Ref} = State#state.blocking_tmr,
 
614
            ?vlog("(possibly) stop block timer",[]),
 
615
            stop_block_tmr(Tmr),
 
616
            ?vlog("and send the reply",[]),
 
617
            From ! {block_reply,ok,Ref},
 
618
            State#state{admin_state = blocked, connections = [],
 
619
                        blocker_ref = undefined};
 
620
        Connections1 ->
 
621
            State#state{connections = Connections1}
 
622
    end;
 
623
 
 
624
handle_done_connection(#state{connections = Connections} = State, Handler) ->
 
625
    State#state{connections = lists:delete(Handler, Connections)}.
 
626
    
 
627
    
 
628
%% -------------------------------------------------------------------------
 
629
%% handle_block
 
630
%%
 
631
%%
 
632
%%
 
633
%%
 
634
handle_block(#state{admin_state = AdminState} = S) ->
 
635
    handle_block(S, AdminState).
 
636
 
 
637
handle_block(S,unblocked) ->
 
638
    %% Kill all connections
 
639
    ?vtrace("handle_block(unblocked) -> kill all request handlers",[]),
 
640
%%    [exit(Pid,blocked) || Pid <- S#state.connections],
 
641
    [kill_handler(Pid) || Pid <- S#state.connections],
 
642
    {ok,S#state{connections = [], admin_state = blocked}};
 
643
handle_block(S,blocked) ->
 
644
    ?vtrace("handle_block(blocked) -> already blocked",[]),
 
645
    {ok,S};
 
646
handle_block(S,shutting_down) ->
 
647
    ?vtrace("handle_block(shutting_down) -> ongoing...",[]),
 
648
    {{error,shutting_down},S}.
 
649
    
 
650
 
 
651
kill_handler(Pid) ->
 
652
    ?vtrace("kill request handler: ~p",[Pid]),
 
653
    exit(Pid, blocked).
 
654
%%    exit(Pid, kill).
 
655
 
 
656
handle_block(S,Timeout,From,Ref) when Timeout >= 0 ->
 
657
    do_block(S,Timeout,From,Ref);
 
658
 
 
659
handle_block(S,Timeout,From,Ref) ->
 
660
    Reply = {error,{invalid_block_request,Timeout}},
 
661
    From ! {block_reply,Reply,Ref},
 
662
    S.
 
663
 
 
664
do_block(S,Timeout,From,Ref) ->
 
665
    case S#state.connections of
 
666
        [] ->
 
667
            %% Already in idle usage state => go directly to blocked
 
668
            ?vdebug("do_block -> already in idle usage state",[]),
 
669
            From ! {block_reply,ok,Ref},
 
670
            S#state{admin_state = blocked};
 
671
        _ ->
 
672
            %% Active or Busy usage state => go to shutting_down
 
673
            ?vdebug("do_block -> active or busy usage state",[]),
 
674
            %% Make sure we get to know if blocker dies...
 
675
            ?vtrace("do_block -> create blocker monitor",[]),
 
676
            MonitorRef = monitor_blocker(From),
 
677
            ?vtrace("do_block -> (possibly) start block timer",[]),
 
678
            Tmr = {start_block_tmr(Timeout,disturbing),From,Ref},
 
679
            S#state{admin_state = shutting_down, 
 
680
                    blocker_ref = MonitorRef, blocking_tmr = Tmr}
 
681
    end.
 
682
 
 
683
handle_nd_block(S,infinity,From,Ref) ->
 
684
    do_nd_block(S,infinity,From,Ref);
 
685
 
 
686
handle_nd_block(S,Timeout,From,Ref) when Timeout >= 0 ->
 
687
    do_nd_block(S,Timeout,From,Ref);
 
688
 
 
689
handle_nd_block(S,Timeout,From,Ref) ->
 
690
    Reply = {error,{invalid_block_request,Timeout}},
 
691
    From ! {block_reply,Reply,Ref},
 
692
    S.
 
693
 
 
694
do_nd_block(S,Timeout,From,Ref) ->
 
695
    case S#state.connections of
 
696
        [] ->
 
697
            %% Already in idle usage state => go directly to blocked
 
698
            ?vdebug("do_nd_block -> already in idle usage state",[]),
 
699
            From ! {block_reply,ok,Ref},
 
700
            S#state{admin_state = blocked};
 
701
        _ ->
 
702
            %% Active or Busy usage state => go to shutting_down
 
703
            ?vdebug("do_nd_block -> active or busy usage state",[]),
 
704
            %% Make sure we get to know if blocker dies...
 
705
            ?vtrace("do_nd_block -> create blocker monitor",[]),
 
706
            MonitorRef = monitor_blocker(From),
 
707
            ?vtrace("do_nd_block -> (possibly) start block timer",[]),
 
708
            Tmr = {start_block_tmr(Timeout,non_disturbing),From,Ref},
 
709
            S#state{admin_state = shutting_down, 
 
710
                    blocker_ref = MonitorRef, blocking_tmr = Tmr}
 
711
    end.
 
712
 
 
713
handle_block_timeout(S,Method) ->
 
714
    %% Time to take this to the road...
 
715
    demonitor_blocker(S#state.blocker_ref),
 
716
    handle_block_timeout1(S,Method,S#state.blocking_tmr).
 
717
 
 
718
handle_block_timeout1(S,non_disturbing,{_,From,Ref}) ->
 
719
    ?vdebug("handle_block_timeout1(non-disturbing) -> send reply: timeout",[]),
 
720
    From ! {block_reply,{error,timeout},Ref},
 
721
    S#state{admin_state = unblocked, 
 
722
            blocker_ref = undefined, blocking_tmr = undefined};
 
723
 
 
724
handle_block_timeout1(S,disturbing,{_,From,Ref}) ->
 
725
    ?vdebug("handle_block_timeout1(disturbing) -> kill all connections",[]),
 
726
    [exit(Pid,blocked) || Pid <- S#state.connections],
 
727
 
 
728
    ?vdebug("handle_block_timeout1 -> send reply: ok",[]),
 
729
    From ! {block_reply,ok,Ref},
 
730
    S#state{admin_state = blocked,    connections = [], 
 
731
            blocker_ref = undefined, blocking_tmr = undefined};
 
732
 
 
733
handle_block_timeout1(S,Method,{_,From,Ref}) ->
 
734
    ?vinfo("received block timeout with unknown block method:"
 
735
           "~n   Method:  ~p",[Method]),
 
736
    From ! {block_reply,{error,{unknown_block_method,Method}},Ref},
 
737
    S#state{admin_state = blocked,    connections = [], 
 
738
            blocker_ref = undefined, blocking_tmr = undefined};
 
739
 
 
740
handle_block_timeout1(S,Method,TmrInfo) ->
 
741
    ?vinfo("received block timeout with erroneous timer info:"
 
742
           "~n   Method:  ~p"
 
743
           "~n   TmrInfo: ~p",[Method,TmrInfo]),
 
744
    S#state{admin_state = unblocked,
 
745
            blocker_ref = undefined, blocking_tmr = undefined}.
 
746
 
 
747
handle_unblock(S,FromA) ->
 
748
    handle_unblock(S,FromA,S#state.admin_state).
 
749
 
 
750
handle_unblock(S,_FromA,unblocked) ->
 
751
    {ok,S};
 
752
handle_unblock(S,FromA,_AdminState) ->
 
753
    ?vtrace("handle_unblock -> (possibly) stop block timer",[]),
 
754
    stop_block_tmr(S#state.blocking_tmr),
 
755
    case S#state.blocking_tmr of
 
756
        {Tmr,FromB,Ref} ->
 
757
            %% Another process is trying to unblock
 
758
            %% Inform the blocker
 
759
            FromB ! {block_reply, {error,{unblocked,FromA}},Ref};
 
760
        _ ->
 
761
            ok
 
762
    end,
 
763
    {ok,S#state{admin_state = unblocked, blocking_tmr = undefined}}.
 
764
    
 
765
%% The blocker died so we give up on the block.
 
766
handle_blocker_exit(S) ->
 
767
    {Tmr,_From,_Ref} = S#state.blocking_tmr,
 
768
    ?vtrace("handle_blocker_exit -> (possibly) stop block timer",[]),
 
769
    stop_block_tmr(Tmr),
 
770
    S#state{admin_state = unblocked,
 
771
            blocker_ref = undefined, blocking_tmr = undefined}.
 
772
    
 
773
 
 
774
 
 
775
%% -------------------------------------------------------------------------
 
776
%% handle_restart
 
777
%%
 
778
%%
 
779
%%
 
780
%%
 
781
handle_restart(#state{config_file = undefined} = State) ->
 
782
    {continue, {error, undefined_config_file}, State};
 
783
handle_restart(#state{config_db = Db, config_file = ConfigFile} = State) ->
 
784
    ?vtrace("load new configuration",[]),
 
785
    {ok, Config} = httpd_conf:load(ConfigFile),
 
786
    ?vtrace("check for illegal changes (addr, port and socket-type)",[]),
 
787
    case (catch check_constant_values(Db, Config)) of
 
788
        ok ->
 
789
            %% If something goes wrong between the remove 
 
790
            %% and the store where fu-ed
 
791
            ?vtrace("remove old configuration, now hold you breath...",[]),
 
792
            httpd_conf:remove_all(Db),
 
793
            ?vtrace("store new configuration",[]),
 
794
            case httpd_conf:store(Config) of
 
795
                {ok, NewConfigDB} ->
 
796
                    ?vlog("restart done, puh!",[]),
 
797
                    {continue, ok, State#state{config_db = NewConfigDB}};
 
798
                Error ->
 
799
                    ?vlog("failed store new config: ~n   ~p",[Error]),
 
800
                    {stop, Error, State}
 
801
            end;
 
802
        Error ->
 
803
            ?vlog("restart NOT performed due to:"
 
804
                  "~n   ~p",[Error]),
 
805
            {continue, Error, State}
 
806
    end.
 
807
 
 
808
 
 
809
check_constant_values(Db, Config) ->
 
810
    %% Check port number
 
811
    ?vtrace("check_constant_values -> check port number",[]),
 
812
    Port = httpd_util:lookup(Db,port),
 
813
    case httpd_util:key1search(Config,port) of  %% MUST be equal
 
814
        Port ->
 
815
            ok;
 
816
        OtherPort ->
 
817
            throw({error,{port_number_changed,Port,OtherPort}})
 
818
    end,
 
819
 
 
820
    %% Check bind address
 
821
    ?vtrace("check_constant_values -> check bind address",[]),
 
822
    Addr = httpd_util:lookup(Db,bind_address),
 
823
    case httpd_util:key1search(Config,bind_address) of  %% MUST be equal
 
824
        Addr ->
 
825
            ok;
 
826
        OtherAddr ->
 
827
            throw({error,{addr_changed,Addr,OtherAddr}})
 
828
    end,
 
829
 
 
830
    %% Check socket type
 
831
    ?vtrace("check_constant_values -> check socket type",[]),
 
832
    SockType = httpd_util:lookup(Db, com_type),
 
833
    case httpd_util:key1search(Config, com_type) of  %% MUST be equal
 
834
        SockType ->
 
835
            ok;
 
836
        OtherSockType ->
 
837
            throw({error,{sock_type_changed,SockType,OtherSockType}})
 
838
    end,
 
839
    ?vtrace("check_constant_values -> done",[]),
 
840
    ok.
 
841
 
 
842
 
 
843
%% get_ustate(State) -> idle | active | busy
 
844
%%
 
845
%% Retrieve the usage state of the HTTP server:
 
846
%%   0 active connection            -> idle
 
847
%%   max_clients active connections -> busy
 
848
%%   Otherwise                      -> active
 
849
%%
 
850
get_ustate(State) ->
 
851
    get_ustate(length(State#state.connections),State).
 
852
 
 
853
get_ustate(0,_State) ->
 
854
    idle;
 
855
get_ustate(ConnectionCnt,State) ->
 
856
    ConfigDB = State#state.config_db,
 
857
    case httpd_util:lookup(ConfigDB, max_clients, 150) of
 
858
        ConnectionCnt ->
 
859
            busy;
 
860
        _ ->
 
861
            active
 
862
    end.
 
863
 
 
864
 
 
865
get_astate(S) -> S#state.admin_state.
 
866
 
 
867
 
 
868
%% Timer handling functions
 
869
start_block_tmr(infinity,_) ->
 
870
    undefined;
 
871
start_block_tmr(T,M) ->
 
872
    erlang:send_after(T,self(),{block_timeout,M}).
 
873
 
 
874
stop_block_tmr(undefined) ->
 
875
    ok;
 
876
stop_block_tmr(Ref) ->
 
877
    erlang:cancel_timer(Ref).
 
878
 
 
879
 
 
880
%% Monitor blocker functions
 
881
monitor_blocker(Pid) when pid(Pid) ->
 
882
    case (catch erlang:monitor(process,Pid)) of
 
883
        MonitorRef ->
 
884
            MonitorRef;
 
885
        {'EXIT',Reason} ->
 
886
            undefined
 
887
    end;
 
888
monitor_blocker(_) ->
 
889
    undefined.
 
890
 
 
891
demonitor_blocker(undefined) ->
 
892
    ok;
 
893
demonitor_blocker(Ref) ->
 
894
    (catch erlang:demonitor(Ref)).
 
895
 
 
896
 
 
897
%% Some status utility functions
 
898
 
 
899
update_heavy_load_status(Status) ->
 
900
    update_status_with_time(Status,last_heavy_load).
 
901
 
 
902
update_connection_status(Status,ConnCount) ->
 
903
    S1 = case lists:keysearch(max_conn,1,Status) of
 
904
             {value,{max_conn,C1}} when ConnCount > C1 ->
 
905
                 lists:keyreplace(max_conn,1,Status,{max_conn,ConnCount});
 
906
             {value,{max_conn,C2}} ->
 
907
                 Status;
 
908
             false ->
 
909
                 [{max_conn,ConnCount}|Status]
 
910
         end,
 
911
    update_status_with_time(S1,last_connection).
 
912
 
 
913
update_status_with_time(Status,Key) ->
 
914
    lists:keyreplace(Key,1,Status,{Key,universal_time()}).
 
915
 
 
916
universal_time() -> calendar:universal_time().
 
917
 
 
918
 
 
919
auth_status(P) when pid(P) ->
 
920
    Items = [status, message_queue_len, reductions,
 
921
             heap_size, stack_size, current_function],
 
922
    {auth_status, process_status(P,Items,[])};
 
923
auth_status(_) ->
 
924
    {auth_status, undefined}.
 
925
 
 
926
sec_status(P) when pid(P) ->
 
927
    Items = [status, message_queue_len, reductions,
 
928
             heap_size, stack_size, current_function],
 
929
    {security_status, process_status(P,Items,[])};
 
930
sec_status(_) ->
 
931
    {security_status, undefined}.
 
932
 
 
933
acceptor_status(P) when pid(P) ->
 
934
    Items = [status, message_queue_len, reductions,
 
935
             heap_size, stack_size, current_function],
 
936
    {acceptor_status, process_status(P,Items,[])};
 
937
acceptor_status(_) ->
 
938
    {acceptor_status, undefined}.
 
939
 
 
940
 
 
941
manager_status(P) ->
 
942
    Items = [status, message_queue_len, reductions,
 
943
             heap_size, stack_size],
 
944
    {manager_status, process_status(P,Items,[])}.
 
945
 
 
946
 
 
947
process_status(P,[],L) ->
 
948
    [{pid,P}|lists:reverse(L)];
 
949
process_status(P,[H|T],L) ->
 
950
    case (catch process_info(P,H)) of
 
951
        {H, Value} ->
 
952
            process_status(P,T,[{H,Value}|L]);
 
953
        _ ->
 
954
            process_status(P,T,[{H,undefined}|L])
 
955
    end.
 
956
        
 
957
make_name(Addr,Port) ->
 
958
    httpd_util:make_name("httpd",Addr,Port).
 
959
 
 
960
 
 
961
report_error(State,String) ->
 
962
    Cdb = State#state.config_db,
 
963
    error_logger:error_report(String),
 
964
    mod_log:report_error(Cdb,String),
 
965
    mod_disk_log:report_error(Cdb,String).
 
966
    
 
967
 
 
968
set_verbosity(V) ->
 
969
    Units = [manager_verbosity, 
 
970
             acceptor_verbosity, request_handler_verbosity, 
 
971
             security_verbosity, auth_verbosity],
 
972
    case httpd_util:key1search(V, all) of
 
973
        undefined ->
 
974
            set_verbosity(V, Units);
 
975
        Verbosity when atom(Verbosity) ->
 
976
            V1 = [{Unit, Verbosity} || Unit <- Units],
 
977
            set_verbosity(V1, Units)
 
978
    end.
 
979
 
 
980
set_verbosity(_V, []) ->
 
981
    ok;
 
982
set_verbosity(V, [manager_verbosity = Unit|Units]) ->
 
983
    Verbosity = httpd_util:key1search(V, Unit, ?default_verbosity),
 
984
    put(verbosity, ?vvalidate(Verbosity)),
 
985
    set_verbosity(V, Units);
 
986
set_verbosity(V, [Unit|Units]) ->
 
987
    Verbosity = httpd_util:key1search(V, Unit, ?default_verbosity),
 
988
    put(Unit, ?vvalidate(Verbosity)),
 
989
    set_verbosity(V, Units).
 
990
 
 
991
    
 
992
set_verbosity(manager,V,_S) ->
 
993
    put(verbosity,V);
 
994
set_verbosity(acceptor,V,_S) ->
 
995
    put(acceptor_verbosity,V);
 
996
set_verbosity(request,V,_S) ->
 
997
    put(request_handler_verbosity,V);
 
998
set_verbosity(security,V,S) ->
 
999
    OldVerbosity = put(security_verbosity,V),
 
1000
    Addr = httpd_util:lookup(S#state.config_db, bind_address),
 
1001
    Port = httpd_util:lookup(S#state.config_db, port),
 
1002
    mod_security_server:verbosity(Addr,Port,V),
 
1003
    OldVerbosity;
 
1004
set_verbosity(auth,V,S) ->
 
1005
    OldVerbosity = put(auth_verbosity,V),
 
1006
    Addr = httpd_util:lookup(S#state.config_db, bind_address),
 
1007
    Port = httpd_util:lookup(S#state.config_db, port),
 
1008
    mod_auth_server:verbosity(Addr,Port,V),
 
1009
    OldVerbosity;
 
1010
 
 
1011
set_verbosity(all,V,S) ->
 
1012
    OldMv = put(verbosity,V),
 
1013
    OldAv = put(acceptor_verbosity,V),
 
1014
    OldRv = put(request_handler_verbosity,V),
 
1015
    OldSv = put(security_verbosity,V),
 
1016
    OldAv = put(auth_verbosity,V),
 
1017
    Addr  = httpd_util:lookup(S#state.config_db, bind_address),
 
1018
    Port  = httpd_util:lookup(S#state.config_db, port),
 
1019
    mod_security_server:verbosity(Addr,Port,V),
 
1020
    mod_auth_server:verbosity(Addr,Port,V),
 
1021
    [{manager,OldMv}, {request,OldRv}, {security,OldSv}, {auth, OldAv}].
 
1022
    
 
1023
    
 
1024
%%
 
1025
call(ServerRef,Request) ->
 
1026
    gen_server:call(ServerRef,Request).
 
1027
 
 
1028
cast(ServerRef,Message) ->
 
1029
    gen_server:cast(ServerRef,Message).
 
1030