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

« back to all changes in this revision

Viewing changes to lib/inets/src/http_server/mod_esi.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
%%
29
29
-export([do/1, load/2, store/2]).
30
30
 
31
31
-include("httpd.hrl").
 
32
-include("httpd_internal.hrl").
 
33
-include("inets_internal.hrl").
32
34
 
33
35
-define(VMODULE,"ESI").
34
36
-define(DEFAULT_ERL_TIMEOUT,15000).
35
37
 
 
38
 
36
39
%%%=========================================================================
37
40
%%%  API 
38
41
%%%=========================================================================
 
42
 
39
43
%%--------------------------------------------------------------------------
40
44
%% deliver(SessionID, Data) -> ok | {error, bad_sessionID}
41
45
%%      SessionID = pid()
47
51
%% request handling process so it can forward it to the client.
48
52
%%-------------------------------------------------------------------------
49
53
deliver(SessionID, Data) when is_pid(SessionID) ->
50
 
    SessionID ! {ok, Data},
 
54
    SessionID ! {esi_data, Data},
51
55
    ok;
52
56
deliver(_SessionID, _Data) ->
53
57
    {error, bad_sessionID}.
54
58
 
 
59
 
55
60
%%%=========================================================================
56
61
%%%  CALLBACK API 
57
62
%%%=========================================================================
63
68
%% Description:  See httpd(3) ESWAPI CALLBACK FUNCTIONS
64
69
%%-------------------------------------------------------------------------
65
70
do(ModData) ->
 
71
    ?hdrt("do", []),
66
72
    case proplists:get_value(status, ModData#mod.data) of
67
73
        {_StatusCode, _PhraseArgs, _Reason} ->
68
74
            {proceed, ModData#mod.data};
74
80
                    {proceed, ModData#mod.data}
75
81
            end
76
82
    end.
 
83
 
 
84
 
77
85
%%--------------------------------------------------------------------------
78
86
%% load(Line, Context) ->  eof | ok | {ok, NewContext} | 
79
87
%%                     {ok, NewContext, Directive} | 
127
135
                         " is an invalid ErlScriptNoCache directive")}
128
136
    end.
129
137
 
 
138
 
130
139
%%--------------------------------------------------------------------------
131
140
%% store(Directive, DirectiveList) -> {ok, NewDirective} | 
132
141
%%                                    {ok, [NewDirective]} |
163
172
 
164
173
store({erl_script_alias, Value}, _) ->
165
174
    {error, {wrong_type, {erl_script_alias, Value}}};
166
 
store({erl_script_timeout, Value} = Conf, _) 
167
 
  when is_integer(Value), Value >= 0 ->
168
 
    {ok, Conf};
 
175
store({erl_script_timeout, TimeoutSec}, _) 
 
176
  when is_integer(TimeoutSec) andalso (TimeoutSec >= 0) ->
 
177
    {ok, {erl_script_timeout, TimeoutSec * 1000}};
169
178
store({erl_script_timeout, Value}, _) ->
170
179
    {error, {wrong_type, {erl_script_timeout, Value}}};
171
 
store({erl_script_nocache, Value} = Conf, _) when Value == true; 
172
 
                                                  Value == false ->
 
180
store({erl_script_nocache, Value} = Conf, _) 
 
181
  when (Value =:= true) orelse (Value =:= false) ->
173
182
    {ok, Conf};
174
183
store({erl_script_nocache, Value}, _) ->
175
184
    {error, {wrong_type, {erl_script_nocache, Value}}}.
 
185
 
 
186
 
176
187
%%%========================================================================
177
188
%%% Internal functions
178
189
%%%========================================================================   
179
190
generate_response(ModData) ->
 
191
    ?hdrt("generate response", []),
180
192
    case scheme(ModData#mod.request_uri, ModData#mod.config_db) of
181
193
        {eval, ESIBody, Modules} ->
182
194
            eval(ModData, ESIBody, Modules);
227
239
%%------------------------ Erl mechanism --------------------------------
228
240
 
229
241
erl(#mod{method = Method} = ModData, ESIBody, Modules) 
230
 
  when Method == "GET"; Method == "HEAD"->
 
242
  when (Method =:= "GET") orelse (Method =:= "HEAD") ->
 
243
    ?hdrt("erl", [{method, Method}]),
231
244
    case httpd_util:split(ESIBody,":|%3A|/",2) of
232
245
        {ok, [ModuleName, FuncAndInput]} ->
233
246
            case httpd_util:split(FuncAndInput,"[\?/]",2) of
249
262
            {proceed, [{status,{400, none, BadRequest}} | ModData#mod.data]}
250
263
    end;
251
264
 
252
 
erl(#mod{method = "POST", entity_body = Body} = ModData, ESIBody, Modules) ->
 
265
erl(#mod{request_uri  = ReqUri, 
 
266
         method       = "PUT",
 
267
         http_version = Version, 
 
268
         data         = Data}, _ESIBody, _Modules) ->
 
269
    ?hdrt("erl", [{method, put}]),
 
270
    {proceed, [{status,{501,{"PUT", ReqUri, Version},
 
271
                        ?NICE("Erl mechanism doesn't support method PUT")}}|
 
272
               Data]};
 
273
 
 
274
erl(#mod{request_uri  = ReqUri, 
 
275
         method       = "DELETE",
 
276
         http_version = Version, 
 
277
         data         = Data}, _ESIBody, _Modules) ->
 
278
    ?hdrt("erl", [{method, delete}]),
 
279
    {proceed,[{status,{501,{"DELETE", ReqUri, Version},
 
280
                       ?NICE("Erl mechanism doesn't support method DELETE")}}|
 
281
              Data]};
 
282
 
 
283
erl(#mod{method      = "POST", 
 
284
         entity_body = Body} = ModData, ESIBody, Modules) ->
 
285
    ?hdrt("erl", [{method, post}]),
253
286
    case httpd_util:split(ESIBody,":|%3A|/",2) of
254
287
        {ok,[ModuleName, Function]} ->
255
288
            generate_webpage(ModData, ESIBody, Modules, 
265
298
                     FunctionName, Input, ScriptElements);
266
299
generate_webpage(ModData, ESIBody, Modules, Module, FunctionName,
267
300
                 Input, ScriptElements) ->
 
301
    ?hdrt("generate webpage", []),
268
302
    Function = list_to_atom(FunctionName),
269
303
    case lists:member(Module, Modules) of
270
304
        true ->
285
319
 
286
320
%% Old API that waits for the dymnamic webpage to be totally generated
287
321
%% before anythig is sent back to the client.
288
 
erl_scheme_webpage_whole(Module, Function, Env, Input, ModData) ->
289
 
    case (catch Module:Function(Env, Input)) of
 
322
erl_scheme_webpage_whole(Mod, Func, Env, Input, ModData) ->
 
323
    ?hdrt("erl_scheme_webpage_whole", [{module, Mod}, {function, Func}]),
 
324
    case (catch Mod:Func(Env, Input)) of
290
325
        {'EXIT',{undef, _}} ->
291
326
            {proceed, [{status, {404, ModData#mod.request_uri, "Not found"}}
292
327
                       | ModData#mod.data]};
323
358
%% in small chunks at the time during generation.
324
359
erl_scheme_webpage_chunk(Mod, Func, Env, Input, ModData) -> 
325
360
    process_flag(trap_exit, true),
 
361
    ?hdrt("erl_scheme_webpage_chunk", [{module, Mod}, {function, Func}]),
326
362
    Self = self(),
327
363
    %% Spawn worker that generates the webpage.
328
364
    %% It would be nicer to use erlang:function_exported/3 but if the 
330
366
    Pid = spawn_link(
331
367
            fun() ->
332
368
                    case catch Mod:Func(Self, Env, Input) of
333
 
                        {'EXIT',{undef,_}} ->
 
369
                        {'EXIT', {undef,_}} ->
334
370
                            %% Will force fallback on the old API
335
371
                            exit(erl_scheme_webpage_chunk_undefined);
336
372
                        _ ->
348
384
    deliver_webpage_chunk(ModData, Pid, Timeout).
349
385
 
350
386
deliver_webpage_chunk(#mod{config_db = Db} = ModData, Pid, Timeout) ->
 
387
    ?hdrt("deliver_webpage_chunk", [{timeout, Timeout}]),
351
388
    case receive_headers(Timeout) of
352
389
        {error, Reason} ->
353
390
            %% Happens when webpage generator callback/3 is undefined
 
391
            ?hdrv("deliver_webpage_chunk - failed receiving headers", 
 
392
                  [{reason, Reason}]),
354
393
            {error, Reason}; 
355
394
        {Headers, Body} ->
356
395
            case httpd_esi:handle_headers(Headers) of
375
414
                                IsDisableChunkedSend)
376
415
            end;
377
416
        timeout ->
 
417
            ?hdrv("deliver_webpage_chunk - timeout", []),
378
418
            send_headers(ModData, {504, "Timeout"},[{"connection", "close"}]),
379
419
            httpd_socket:close(ModData#mod.socket_type, ModData#mod.socket),
380
420
            process_flag(trap_exit,false),
383
423
 
384
424
receive_headers(Timeout) ->
385
425
    receive
 
426
        {esi_data, Chunk} ->
 
427
            ?hdrt("receive_headers - received esi data (esi)", []),
 
428
            httpd_esi:parse_headers(lists:flatten(Chunk));              
386
429
        {ok, Chunk} ->
 
430
            ?hdrt("receive_headers - received esi data (ok)", []),
387
431
            httpd_esi:parse_headers(lists:flatten(Chunk));              
388
432
        {'EXIT', Pid, erl_scheme_webpage_chunk_undefined} when is_pid(Pid) ->
 
433
            ?hdrd("receive_headers - exit:chunk-undef", []),
389
434
            {error, erl_scheme_webpage_chunk_undefined};
390
435
        {'EXIT', Pid, Reason} when is_pid(Pid) ->
 
436
            ?hdrv("receive_headers - exit", [{reason, Reason}]),
391
437
            exit({mod_esi_linked_process_died, Pid, Reason})
392
438
    after Timeout ->
393
439
            timeout
403
449
    {proceed, [{response, {already_sent, 200, Size}} | ModData#mod.data]};
404
450
 
405
451
handle_body(Pid, ModData, Body, Timeout, Size, IsDisableChunkedSend) ->
 
452
    ?hdrt("handle_body - send chunk", [{timeout, Timeout}, {size, Size}]),
406
453
    httpd_response:send_chunk(ModData, Body, IsDisableChunkedSend),
407
454
    receive 
 
455
        {esi_data, Data} ->
 
456
            ?hdrt("handle_body - received data (esi)", []),
 
457
            handle_body(Pid, ModData, Data, Timeout, Size + length(Data),
 
458
                        IsDisableChunkedSend);
408
459
        {ok, Data} ->
 
460
            ?hdrt("handle_body - received data (ok)", []),
409
461
            handle_body(Pid, ModData, Data, Timeout, Size + length(Data),
410
462
                        IsDisableChunkedSend);
411
463
        {'EXIT', Pid, normal} when is_pid(Pid) ->
 
464
            ?hdrt("handle_body - exit:normal", []),
412
465
            httpd_response:send_final_chunk(ModData, IsDisableChunkedSend),
413
466
            {proceed, [{response, {already_sent, 200, Size}} | 
414
467
                       ModData#mod.data]};
415
468
        {'EXIT', Pid, Reason} when is_pid(Pid) ->
 
469
            ?hdrv("handle_body - exit", [{reason, Reason}]),
 
470
            httpd_response:send_final_chunk(ModData, IsDisableChunkedSend),
416
471
            exit({mod_esi_linked_process_died, Pid, Reason})
 
472
 
417
473
    after Timeout ->
 
474
            ?hdrv("handle_body - timeout", []),
418
475
            process_flag(trap_exit,false),
419
 
            {proceed,[{response, {already_sent, 200, Size}} | 
420
 
                      ModData#mod.data]}  
 
476
            httpd_response:send_final_chunk(ModData, IsDisableChunkedSend),
 
477
            exit({mod_esi_linked_process_timeout, Pid})
421
478
    end.
422
479
 
423
480
erl_script_timeout(Db) ->
444
501
 
445
502
%%------------------------ Eval mechanism --------------------------------
446
503
 
447
 
eval(#mod{request_uri = ReqUri, method = "POST",
448
 
          http_version = Version, data = Data}, _ESIBody, _Modules) ->
 
504
eval(#mod{request_uri  = ReqUri, 
 
505
          method       = "PUT",
 
506
          http_version = Version, 
 
507
          data         = Data}, _ESIBody, _Modules) ->
 
508
    ?hdrt("eval", [{method, put}]),
 
509
    {proceed,[{status,{501,{"PUT", ReqUri, Version},
 
510
                       ?NICE("Eval mechanism doesn't support method PUT")}}|
 
511
              Data]};
 
512
 
 
513
eval(#mod{request_uri  = ReqUri, 
 
514
          method       = "DELETE",
 
515
          http_version = Version, 
 
516
          data         = Data}, _ESIBody, _Modules) ->
 
517
    ?hdrt("eval", [{method, delete}]),
 
518
    {proceed,[{status,{501,{"DELETE", ReqUri, Version},
 
519
                       ?NICE("Eval mechanism doesn't support method DELETE")}}|
 
520
              Data]};
 
521
 
 
522
eval(#mod{request_uri  = ReqUri, 
 
523
          method       = "POST",
 
524
          http_version = Version, 
 
525
          data         = Data}, _ESIBody, _Modules) ->
 
526
    ?hdrt("eval", [{method, post}]),
449
527
    {proceed,[{status,{501,{"POST", ReqUri, Version},
450
528
                       ?NICE("Eval mechanism doesn't support method POST")}}|
451
529
              Data]};
452
530
 
453
531
eval(#mod{method = Method} = ModData, ESIBody, Modules) 
454
 
  when Method == "GET"; Method == "HEAD" ->
 
532
  when (Method =:= "GET") orelse (Method =:= "HEAD") ->
 
533
    ?hdrt("eval", [{method, Method}]),
455
534
    case is_authorized(ESIBody, Modules) of
456
535
        true ->
457
536
            case generate_webpage(ESIBody) of