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

« back to all changes in this revision

Viewing changes to lib/inets/src/http_server/httpd.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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1997-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
%%
24
24
 
25
25
-include("httpd.hrl").
26
26
 
27
 
-deprecated({start, 0, next_major_release}).
28
 
-deprecated({start, 1, next_major_release}).
29
 
-deprecated({start_link, 1, next_major_release}).
30
 
-deprecated({start_child, 0, next_major_release}).
31
 
-deprecated({start_child, 1, next_major_release}).
32
 
-deprecated({stop, 0, next_major_release}).
33
 
-deprecated({stop, 1, next_major_release}).
34
 
-deprecated({stop, 2, next_major_release}).
35
 
-deprecated({stop_child, 0, next_major_release}).
36
 
-deprecated({stop_child, 1, next_major_release}).
37
 
-deprecated({stop_child, 2, next_major_release}).
38
 
-deprecated({restart, 0, next_major_release}).
39
 
-deprecated({restart, 1, next_major_release}).
40
 
-deprecated({restart, 2, next_major_release}).
41
 
-deprecated({block, 0, next_major_release}).
42
 
-deprecated({block, 1, next_major_release}).
43
 
-deprecated({block, 2, next_major_release}).
44
 
-deprecated({block, 3, next_major_release}).
45
 
-deprecated({block, 4, next_major_release}).
46
 
-deprecated({unblock, 0, next_major_release}).
47
 
-deprecated({unblock, 1, next_major_release}).
48
 
-deprecated({unblock, 2, next_major_release}).
49
 
 
50
27
%% Behavior callbacks
51
 
-export([start_standalone/1, start_service/1, stop_service/1, services/0, 
52
 
         service_info/1]).
 
28
-export([
 
29
         start_standalone/1, 
 
30
         start_service/1, 
 
31
         stop_service/1, 
 
32
         services/0, 
 
33
         service_info/1
 
34
        ]).
53
35
 
54
36
%% API
55
37
-export([parse_query/1, reload_config/2, info/1, info/2, info/3]).
56
38
 
57
 
%% Deprecated
58
 
-export([start/0, start/1, 
59
 
         start_link/0, start_link/1, 
60
 
         start_child/0,start_child/1,
61
 
         stop/0,stop/1,stop/2,
62
 
         stop_child/0,stop_child/1,stop_child/2,
63
 
         restart/0,restart/1,restart/2]).
64
 
 
65
 
%% Management stuff should be internal functions 
66
 
%% Will be from r13
67
 
-export([block/0,block/1,block/2,block/3,block/4,
68
 
         unblock/0,unblock/1,unblock/2]).
69
 
 
70
 
%% Internal Debugging and status info stuff...
71
 
%% Keep for now should probably be moved to test catalog
72
 
-export([get_status/1,get_status/2,get_status/3,
73
 
         get_admin_state/0,get_admin_state/1,get_admin_state/2,
74
 
         get_usage_state/0,get_usage_state/1,get_usage_state/2]).
 
39
%% Internal debugging and status info stuff...
 
40
-export([
 
41
         get_status/1, get_status/2, get_status/3,
 
42
         get_admin_state/0, get_admin_state/1, get_admin_state/2,
 
43
         get_usage_state/0, get_usage_state/1, get_usage_state/2
 
44
        ]).
75
45
 
76
46
%%%========================================================================
77
47
%%% API
111
81
                                     is_list(Properties) ->    
112
82
    httpd_conf:get_config(Address, Port, Properties).
113
83
 
 
84
 
114
85
%%%========================================================================
115
86
%%% Behavior callbacks
116
87
%%%========================================================================
149
120
        exit:{noproc, _} ->
150
121
            {error, service_not_available} 
151
122
    end.
 
123
 
 
124
 
152
125
%%%--------------------------------------------------------------
153
126
%%% Internal functions
154
127
%%%--------------------------------------------------------------------
176
149
            {ok, [{bind_address, Address}, {port, Port} | Info]}
177
150
    end.
178
151
 
 
152
 
179
153
reload(Config, Address, Port) ->
180
154
    Name = make_name(Address,Port),
181
155
    case whereis(Name) of
185
159
            {error,not_started}
186
160
    end.
187
161
 
188
 
reload(Addr, Port) when is_integer(Port) ->
189
 
    Name = make_name(Addr,Port),
190
 
    case whereis(Name) of
191
 
        Pid when is_pid(Pid) ->
192
 
            httpd_manager:reload(Pid, undefined);
193
 
        _ ->
194
 
            {error,not_started}
195
 
    end.
196
162
    
197
163
%%% =========================================================
198
 
%%% Function:    block/0, block/1, block/2, block/3, block/4
199
 
%%%              block()
200
 
%%%              block(Port)
201
 
%%%              block(ConfigFile)
202
 
%%%              block(Addr,Port)
203
 
%%%              block(Port,Mode)
204
 
%%%              block(ConfigFile,Mode)
205
 
%%%              block(Addr,Port,Mode)
206
 
%%%              block(ConfigFile,Mode,Timeout)
207
 
%%%              block(Addr,Port,Mode,Timeout)
 
164
%%% Function:    block/3, block/4
 
165
%%%              block(Addr, Port, Mode)
 
166
%%%              block(ConfigFile, Mode, Timeout)
 
167
%%%              block(Addr, Port, Mode, Timeout)
208
168
%%% 
209
169
%%% Returns:     ok | {error,Reason}
210
170
%%%              
237
197
%%%              Mode       -> disturbing | non_disturbing
238
198
%%%              Timeout    -> integer()
239
199
%%%
240
 
block() -> block(undefined,8888,disturbing).
241
 
 
242
 
block(Port) when is_integer(Port) -> 
243
 
    block(undefined,Port,disturbing);
244
 
 
245
 
block(ConfigFile) when is_list(ConfigFile) ->
246
 
    case get_addr_and_port(ConfigFile) of
247
 
        {ok,Addr,Port} ->
248
 
            block(Addr,Port,disturbing);
249
 
        Error ->
250
 
            Error
251
 
    end.
252
 
 
253
 
block(Addr,Port) when is_integer(Port) -> 
254
 
    block(Addr,Port,disturbing);
255
 
 
256
 
block(Port,Mode) when is_integer(Port) andalso is_atom(Mode) ->
257
 
    block(undefined,Port,Mode);
258
 
 
259
 
block(ConfigFile,Mode) when is_list(ConfigFile) andalso is_atom(Mode) ->
260
 
    case get_addr_and_port(ConfigFile) of
261
 
        {ok,Addr,Port} ->
262
 
            block(Addr,Port,Mode);
263
 
        Error ->
264
 
            Error
265
 
    end.
266
 
 
267
 
 
268
 
block(Addr,Port,disturbing) when is_integer(Port) ->
269
 
    do_block(Addr,Port,disturbing);
270
 
block(Addr,Port,non_disturbing) when is_integer(Port) ->
271
 
    do_block(Addr,Port,non_disturbing);
272
 
 
273
 
block(ConfigFile,Mode,Timeout) when is_list(ConfigFile) andalso 
274
 
                                    is_atom(Mode) andalso 
275
 
                                    is_integer(Timeout) ->
276
 
    case get_addr_and_port(ConfigFile) of
277
 
        {ok,Addr,Port} ->
278
 
            block(Addr,Port,Mode,Timeout);
279
 
        Error ->
280
 
            Error
281
 
    end.
282
 
 
283
 
 
284
 
block(Addr,Port,non_disturbing,Timeout) 
285
 
  when is_integer(Port) andalso is_integer(Timeout) ->
286
 
    do_block(Addr,Port,non_disturbing,Timeout);
287
 
block(Addr,Port,disturbing,Timeout) when is_integer(Port) andalso 
288
 
                                         is_integer(Timeout) ->
289
 
    do_block(Addr,Port,disturbing,Timeout).
290
 
 
291
 
do_block(Addr,Port,Mode) when is_integer(Port) andalso is_atom(Mode) -> 
 
200
 
 
201
block(Addr, Port, disturbing) when is_integer(Port) ->
 
202
    do_block(Addr, Port, disturbing);
 
203
block(Addr, Port, non_disturbing) when is_integer(Port) ->
 
204
    do_block(Addr, Port, non_disturbing);
 
205
 
 
206
block(ConfigFile, Mode, Timeout) 
 
207
  when is_list(ConfigFile) andalso 
 
208
       is_atom(Mode) andalso 
 
209
       is_integer(Timeout) ->
 
210
    case get_addr_and_port(ConfigFile) of
 
211
        {ok, Addr, Port} ->
 
212
            block(Addr, Port, Mode, Timeout);
 
213
        Error ->
 
214
            Error
 
215
    end.
 
216
 
 
217
 
 
218
block(Addr, Port, non_disturbing, Timeout) 
 
219
  when is_integer(Port) andalso is_integer(Timeout) ->
 
220
    do_block(Addr, Port, non_disturbing, Timeout);
 
221
block(Addr,Port,disturbing,Timeout) 
 
222
  when is_integer(Port) andalso is_integer(Timeout) ->
 
223
    do_block(Addr, Port, disturbing, Timeout).
 
224
 
 
225
do_block(Addr, Port, Mode) when is_integer(Port) andalso is_atom(Mode) -> 
292
226
    Name = make_name(Addr,Port),
293
227
    case whereis(Name) of
294
228
        Pid when is_pid(Pid) ->
298
232
    end.
299
233
    
300
234
 
301
 
do_block(Addr,Port,Mode,Timeout) 
 
235
do_block(Addr, Port, Mode, Timeout) 
302
236
  when is_integer(Port) andalso is_atom(Mode) -> 
303
237
    Name = make_name(Addr,Port),
304
238
    case whereis(Name) of
310
244
    
311
245
 
312
246
%%% =========================================================
313
 
%%% Function:    unblock/0, unblock/1, unblock/2
314
 
%%%              unblock()
315
 
%%%              unblock(Port)
316
 
%%%              unblock(ConfigFile)
317
 
%%%              unblock(Addr,Port)
 
247
%%% Function:    unblock/2
 
248
%%%              unblock(Addr, Port)
318
249
%%%              
319
250
%%% Description: This function is used to reverse a previous block 
320
251
%%%              operation on the HTTP server.
323
254
%%%              Addr       -> {A,B,C,D} | string() | undefined
324
255
%%%              ConfigFile -> string()
325
256
%%%
326
 
unblock()                           -> unblock(undefined,8888).
327
 
unblock(Port) when is_integer(Port) -> unblock(undefined,Port);
328
 
 
329
 
unblock(ConfigFile) when is_list(ConfigFile) ->
330
 
    case get_addr_and_port(ConfigFile) of
331
 
        {ok,Addr,Port} ->
332
 
            unblock(Addr,Port);
333
 
        Error ->
334
 
            Error
335
 
    end.
336
257
 
337
258
unblock(Addr, Port) when is_integer(Port) -> 
338
259
    Name = make_name(Addr,Port),
349
270
  {ok, Plus2Space, _} = inets_regexp:gsub(KeyValue,"[\+]"," "),
350
271
  case inets_regexp:split(Plus2Space,"=") of
351
272
    {ok,[Key|Value]} ->
352
 
      [{httpd_util:decode_hex(Key),
353
 
        httpd_util:decode_hex(lists:flatten(Value))}|foreach(Rest)];
 
273
      [{http_uri:decode(Key),
 
274
        http_uri:decode(lists:flatten(Value))}|foreach(Rest)];
354
275
    {ok,_} ->
355
276
      foreach(Rest)
356
277
  end.
358
279
get_addr_and_port(ConfigFile) ->
359
280
    case httpd_conf:load(ConfigFile) of
360
281
        {ok, ConfigList} ->
361
 
            case httpd_conf:validate_properties(ConfigList) of
 
282
            case (catch httpd_conf:validate_properties(ConfigList)) of
362
283
                {ok, Config} ->
363
284
                    Address = proplists:get_value(bind_address, Config, any), 
364
285
                    Port    = proplists:get_value(port, Config, 80),
506
427
    end.
507
428
 
508
429
do_reload_config(ConfigList, Mode) ->
509
 
    case httpd_conf:validate_properties(ConfigList) of
 
430
    case (catch httpd_conf:validate_properties(ConfigList)) of
510
431
        {ok, Config} ->
511
432
            Address = proplists:get_value(bind_address, Config, any), 
512
433
            Port    = proplists:get_value(port, Config, 80),
521
442
%%%--------------------------------------------------------------
522
443
%%% Deprecated 
523
444
%%%--------------------------------------------------------------
524
 
start() ->
525
 
    start("/var/tmp/server_root/conf/8888.conf").
526
 
 
527
 
start(ConfigFile) ->
528
 
    {ok, Pid} = inets:start(httpd, ConfigFile, stand_alone), 
529
 
    unlink(Pid),
530
 
    {ok, Pid}.
531
 
 
532
 
start_link() ->
533
 
    start("/var/tmp/server_root/conf/8888.conf").
534
 
 
535
 
start_link(ConfigFile) when is_list(ConfigFile) ->
536
 
    inets:start(httpd, ConfigFile, stand_alone). 
537
 
 
538
 
stop() ->
539
 
  stop(8888).
540
 
 
541
 
stop(Port) when is_integer(Port) ->
542
 
    stop(undefined, Port);
543
 
stop(Pid) when is_pid(Pid) ->
544
 
    old_stop(Pid);
545
 
stop(ConfigFile) when is_list(ConfigFile) ->
546
 
    old_stop(ConfigFile).
547
 
 
548
 
stop(Addr, Port) when is_integer(Port) ->
549
 
    old_stop(Addr, Port).
550
 
 
551
 
start_child() ->
552
 
    start_child("/var/tmp/server_root/conf/8888.conf").
553
 
 
554
 
start_child(ConfigFile) ->
555
 
    httpd_sup:start_child(ConfigFile).
556
 
 
557
 
stop_child() ->
558
 
  stop_child(8888).
559
 
 
560
 
stop_child(Port) ->
561
 
    stop_child(undefined, Port).
562
 
 
563
 
stop_child(Addr, Port) when is_integer(Port) ->
564
 
    httpd_sup:stop_child(Addr, Port).
565
 
 
566
 
restart() -> reload(undefined, 8888).
567
 
 
568
 
restart(Port) when is_integer(Port) ->
569
 
    reload(undefined,  Port).
570
 
restart(Addr, Port) ->
571
 
    reload(Addr, Port).
572
 
 
573
 
old_stop(Pid) when is_pid(Pid) ->
574
 
    do_stop(Pid);
575
 
old_stop(ConfigFile) when is_list(ConfigFile) ->
576
 
    case get_addr_and_port(ConfigFile) of
577
 
        {ok, Addr, Port} ->
578
 
            old_stop(Addr, Port);
 
445
 
 
446
%% start() ->
 
447
%%     start("/var/tmp/server_root/conf/8888.conf").
 
448
 
 
449
%% start(ConfigFile) ->
 
450
%%     {ok, Pid} = inets:start(httpd, ConfigFile, stand_alone), 
 
451
%%     unlink(Pid),
 
452
%%     {ok, Pid}.
 
453
 
 
454
%% start_link() ->
 
455
%%     start("/var/tmp/server_root/conf/8888.conf").
 
456
 
 
457
%% start_link(ConfigFile) when is_list(ConfigFile) ->
 
458
%%     inets:start(httpd, ConfigFile, stand_alone). 
 
459
 
 
460
%% stop() ->
 
461
%%   stop(8888).
 
462
 
 
463
%% stop(Port) when is_integer(Port) ->
 
464
%%     stop(undefined, Port);
 
465
%% stop(Pid) when is_pid(Pid) ->
 
466
%%     old_stop(Pid);
 
467
%% stop(ConfigFile) when is_list(ConfigFile) ->
 
468
%%     old_stop(ConfigFile).
 
469
 
 
470
%% stop(Addr, Port) when is_integer(Port) ->
 
471
%%     old_stop(Addr, Port).
 
472
 
 
473
%% start_child() ->
 
474
%%     start_child("/var/tmp/server_root/conf/8888.conf").
 
475
 
 
476
%% start_child(ConfigFile) ->
 
477
%%     httpd_sup:start_child(ConfigFile).
 
478
 
 
479
%% stop_child() ->
 
480
%%   stop_child(8888).
 
481
 
 
482
%% stop_child(Port) ->
 
483
%%     stop_child(undefined, Port).
 
484
 
 
485
%% stop_child(Addr, Port) when is_integer(Port) ->
 
486
%%     httpd_sup:stop_child(Addr, Port).
 
487
 
 
488
%% restart() -> reload(undefined, 8888).
 
489
 
 
490
%% restart(Port) when is_integer(Port) ->
 
491
%%     reload(undefined,  Port).
 
492
%% restart(Addr, Port) ->
 
493
%%     reload(Addr, Port).
 
494
 
 
495
%% old_stop(Pid) when is_pid(Pid) ->
 
496
%%     do_stop(Pid);
 
497
%% old_stop(ConfigFile) when is_list(ConfigFile) ->
 
498
%%     case get_addr_and_port(ConfigFile) of
 
499
%%      {ok, Addr, Port} ->
 
500
%%          old_stop(Addr, Port);
579
501
            
580
 
        Error ->
581
 
            Error
582
 
    end;
583
 
old_stop(_StartArgs) ->
584
 
    ok.
 
502
%%      Error ->
 
503
%%          Error
 
504
%%     end;
 
505
%% old_stop(_StartArgs) ->
 
506
%%     ok.
585
507
 
586
 
old_stop(Addr, Port) when is_integer(Port) ->
587
 
    Name = old_make_name(Addr, Port), 
588
 
    case whereis(Name) of
589
 
        Pid when is_pid(Pid) ->
590
 
            do_stop(Pid),
591
 
            ok;
592
 
        _ ->
593
 
            not_started
594
 
    end.
 
508
%% old_stop(Addr, Port) when is_integer(Port) ->
 
509
%%     Name = old_make_name(Addr, Port), 
 
510
%%     case whereis(Name) of
 
511
%%      Pid when is_pid(Pid) ->
 
512
%%          do_stop(Pid),
 
513
%%          ok;
 
514
%%      _ ->
 
515
%%          not_started
 
516
%%     end.
595
517
    
596
 
do_stop(Pid) ->
597
 
    exit(Pid, shutdown).
 
518
%% do_stop(Pid) ->
 
519
%%     exit(Pid, shutdown).
598
520
 
599
 
old_make_name(Addr,Port) ->
600
 
    httpd_util:make_name("httpd_instance_sup",Addr,Port).
 
521
%% old_make_name(Addr,Port) ->
 
522
%%     httpd_util:make_name("httpd_instance_sup",Addr,Port).