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

« back to all changes in this revision

Viewing changes to lib/inets/src/http_server/mod_esi.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
-module(mod_esi).
 
19
 
 
20
%% API
 
21
%% Functions provided to help erl scheme alias programmer to 
 
22
%% Create dynamic webpages that are sent back to the user during 
 
23
%% Generation
 
24
-export([deliver/2]).
 
25
 
 
26
%% Callback API
 
27
-export([do/1, load/2]).
 
28
 
 
29
-include("httpd.hrl").
 
30
 
 
31
-define(VMODULE,"ESI").
 
32
-define(DEFAULT_ERL_TIMEOUT,15000).
 
33
 
 
34
%%%=========================================================================
 
35
%%%  API 
 
36
%%%=========================================================================
 
37
%%--------------------------------------------------------------------------
 
38
%% deliver(SessionID, Data) -> ok | {error, bad_sessionID}
 
39
%%      SessionID = pid()
 
40
%%      Data = string() | io_list() (first call must send a string that 
 
41
%%      contains all header information including "\r\n\r\n", unless there
 
42
%%      is no header information at all.)
 
43
%%
 
44
%% Description: Send <Data> (Html page generated sofar) to the server
 
45
%% request handling process so it can forward it to the client.
 
46
%%-------------------------------------------------------------------------
 
47
deliver(SessionID, Data) when pid(SessionID) ->
 
48
    SessionID ! {ok, Data},
 
49
    ok;
 
50
deliver(_SessionID, _Data) ->
 
51
    {error, bad_sessionID}.
 
52
 
 
53
%%%=========================================================================
 
54
%%%  CALLBACK API 
 
55
%%%=========================================================================
 
56
%%--------------------------------------------------------------------------
 
57
%% do(ModData) -> {proceed, OldData} | {proceed, NewData} | {break, NewData} 
 
58
%%                | done
 
59
%%     ModData = #mod{}
 
60
%%
 
61
%% Description:  See httpd(3) ESWAPI CALLBACK FUNCTIONS
 
62
%%-------------------------------------------------------------------------
 
63
do(ModData) ->
 
64
    case httpd_util:key1search(ModData#mod.data, status) of
 
65
        {_StatusCode, _PhraseArgs, _Reason} ->
 
66
            {proceed, ModData#mod.data};
 
67
        undefined ->
 
68
            case httpd_util:key1search(ModData#mod.data, response) of
 
69
                undefined ->
 
70
                    generate_response(ModData);
 
71
                _Response ->
 
72
                    {proceed, ModData#mod.data}
 
73
            end
 
74
    end.
 
75
%%--------------------------------------------------------------------------
 
76
%% load(Line, Context) ->  eof | ok | {ok, NewContext} | 
 
77
%%                     {ok, NewContext, Directive} | 
 
78
%%                     {ok, NewContext, DirectiveList} | {error, Reason}
 
79
%% Line = string()
 
80
%% Context = NewContext = DirectiveList = [Directive]
 
81
%% Directive = {DirectiveKey , DirectiveValue}
 
82
%% DirectiveKey = DirectiveValue = term()
 
83
%% Reason = term() 
 
84
%%
 
85
%% Description: See httpd(3) ESWAPI CALLBACK FUNCTIONS
 
86
%%-------------------------------------------------------------------------
 
87
load("ErlScriptAlias " ++ ErlScriptAlias, []) ->
 
88
    case regexp:split(ErlScriptAlias," ") of
 
89
        {ok, [ErlName | Modules]} ->
 
90
            {ok, [], {erl_script_alias, {ErlName,Modules}}};
 
91
        {ok, _} ->
 
92
            {error, ?NICE(httpd_conf:clean(ErlScriptAlias) ++
 
93
                         " is an invalid ErlScriptAlias")}
 
94
    end;
 
95
load("EvalScriptAlias " ++ EvalScriptAlias, []) ->
 
96
    case regexp:split(EvalScriptAlias, " ") of
 
97
        {ok, [EvalName|Modules]} ->
 
98
            {ok, [], {eval_script_alias, {EvalName, Modules}}};
 
99
        {ok, _} ->
 
100
            {error, ?NICE(httpd_conf:clean(EvalScriptAlias) ++
 
101
                          " is an invalid EvalScriptAlias")}
 
102
    end;
 
103
load("ErlScriptTimeout " ++ Timeout, [])->
 
104
    case catch list_to_integer(httpd_conf:clean(Timeout)) of
 
105
        TimeoutSec when integer(TimeoutSec)  ->
 
106
           {ok, [], {erl_script_timeout, TimeoutSec * 1000}};
 
107
        _ ->
 
108
           {error, ?NICE(httpd_conf:clean(Timeout) ++
 
109
                         " is an invalid ErlScriptTimeout")}
 
110
    end;
 
111
load("ErlScriptNoCache " ++ CacheArg, [])->
 
112
    case catch list_to_atom(httpd_conf:clean(CacheArg)) of
 
113
        true ->
 
114
            {ok, [], {erl_script_nocache, true}};
 
115
        false ->
 
116
           {ok, [], {erl_script_nocache, false}};
 
117
        _ ->
 
118
           {error, ?NICE(httpd_conf:clean(CacheArg)++
 
119
                         " is an invalid ErlScriptNoCache directive")}
 
120
    end.
 
121
 
 
122
%%%========================================================================
 
123
%%% Internal functions
 
124
%%%========================================================================   
 
125
generate_response(ModData) ->
 
126
    case scheme(ModData#mod.request_uri, ModData#mod.config_db) of
 
127
        {eval, ESIBody, Modules} ->
 
128
            eval(ModData, ESIBody, Modules);
 
129
        {erl, ESIBody, Modules} ->
 
130
            erl(ModData, ESIBody, Modules);
 
131
        no_scheme ->
 
132
            {proceed, ModData#mod.data}
 
133
    end.
 
134
 
 
135
scheme(RequestURI, ConfigDB) ->
 
136
    case match_script(RequestURI, ConfigDB, erl_script_alias) of
 
137
        no_match ->
 
138
            case match_script(RequestURI, ConfigDB, eval_script_alias) of
 
139
                no_match ->
 
140
                    no_scheme;
 
141
                {EsiBody, ScriptModules} ->
 
142
                    {eval, EsiBody, ScriptModules}
 
143
            end;
 
144
        {EsiBody, ScriptModules} ->
 
145
            {erl, EsiBody, ScriptModules}
 
146
    end.
 
147
 
 
148
match_script(RequestURI, ConfigDB, AliasType) ->
 
149
    case httpd_util:multi_lookup(ConfigDB, AliasType) of
 
150
        [] ->
 
151
            no_match;
 
152
        AliasAndMods ->
 
153
            match_esi_script(RequestURI, AliasAndMods, AliasType)
 
154
    end.
 
155
 
 
156
match_esi_script(_, [], _) ->
 
157
    no_match;
 
158
match_esi_script(RequestURI, [{Alias,Modules} | Rest], AliasType) ->
 
159
    AliasMatchStr = alias_match_str(Alias, AliasType),
 
160
    case regexp:first_match(RequestURI, AliasMatchStr) of
 
161
        {match, 1, Length} ->
 
162
            {string:substr(RequestURI, Length + 1), Modules};
 
163
        nomatch ->
 
164
            match_esi_script(RequestURI, Rest, AliasType)
 
165
    end.
 
166
 
 
167
alias_match_str(Alias, erl_script_alias) ->
 
168
    "^" ++ Alias ++ "/";
 
169
alias_match_str(Alias, eval_script_alias) ->
 
170
    "^" ++ Alias ++ "\\?".
 
171
 
 
172
 
 
173
%%------------------------ Erl mechanism --------------------------------
 
174
 
 
175
erl(#mod{method = Method} = ModData, ESIBody, Modules) 
 
176
  when Method == "GET"; Method == "HEAD"->
 
177
    case httpd_util:split(ESIBody,":|%3A|/",2) of
 
178
        {ok, [Module, FuncAndInput]} ->
 
179
            case httpd_util:split(FuncAndInput,"[\?/]",2) of
 
180
                {ok, [FunctionName, Input]} ->
 
181
                    generate_webpage(ModData, ESIBody, Modules, 
 
182
                                     Module, FunctionName, Input, 
 
183
                                    script_elements(FunctionName, Input));
 
184
                {ok, [FunctionName]} ->
 
185
                    generate_webpage(ModData, ESIBody, Modules, 
 
186
                                     Module, FunctionName, "", 
 
187
                                     script_elements(FunctionName, ""));
 
188
                {ok, BadRequest} ->
 
189
                    {proceed,[{status,{400,none, BadRequest}} | 
 
190
                              ModData#mod.data]}
 
191
            end;
 
192
        {ok, BadRequest} ->
 
193
            {proceed, [{status,{400, none, BadRequest}} | ModData#mod.data]}
 
194
    end;
 
195
 
 
196
erl(#mod{method = "POST", entity_body = Body} = ModData, ESIBody, Modules) ->
 
197
    case httpd_util:split(ESIBody,":|%3A|/",2) of
 
198
        {ok,[Module, Function]} ->
 
199
            generate_webpage(ModData, ESIBody, Modules, Module, 
 
200
                             Function, Body, [{entity_body, Body}]);
 
201
        {ok, BadRequest} ->
 
202
            {proceed,[{status, {400, none, BadRequest}} | ModData#mod.data]}
 
203
    end.
 
204
 
 
205
generate_webpage(ModData, ESIBody, ["all"], ModuleName, FunctionName,
 
206
                 Input, ScriptElements) ->
 
207
    generate_webpage(ModData, ESIBody, [ModuleName], ModuleName,
 
208
                     FunctionName, Input, ScriptElements);
 
209
generate_webpage(ModData, ESIBody, Modules, ModuleName, FunctionName,
 
210
                 Input, ScriptElements) ->
 
211
    case lists:member(ModuleName, Modules) of
 
212
        true ->
 
213
            Env = httpd_script_env:create_env(esi, ModData, ScriptElements),
 
214
            Module = list_to_atom(ModuleName),
 
215
            Function = list_to_atom(FunctionName),
 
216
            case erl_scheme_webpage_chunk(Module, Function, 
 
217
                                          Env, Input, ModData) of
 
218
                {error, erl_scheme_webpage_chunk_undefined} ->
 
219
                    erl_scheme_webpage_whole(Module, Function, Env, Input,
 
220
                                             ModData);
 
221
                ResponseResult ->
 
222
                    ResponseResult
 
223
            end;
 
224
        false ->
 
225
            {proceed, [{status, {403, ModData#mod.request_uri,
 
226
                                 ?NICE("Client not authorized to evaluate: "
 
227
                                       ++  ESIBody)}} | ModData#mod.data]}
 
228
    end.
 
229
 
 
230
%% Old API that waits for the dymnamic webpage to be totally generated
 
231
%% before anythig is sent back to the client.
 
232
erl_scheme_webpage_whole(Module, Function, Env, Input, ModData) ->
 
233
    case (catch Module:Function(Env, Input)) of
 
234
        {'EXIT',Reason} ->
 
235
            {proceed, [{status, {500, none, Reason}} |
 
236
                       ModData#mod.data]};
 
237
        Response ->
 
238
            {Headers, Body} = 
 
239
                httpd_esi:parse_headers(lists:flatten(Response)),
 
240
            Length =  httpd_util:flatlength(Body),
 
241
            case httpd_esi:handle_headers(Headers) of
 
242
                {proceed, AbsPath} ->
 
243
                    {proceed, [{real_name, httpd_util:split_path(AbsPath)} 
 
244
                               | ModData#mod.data]};
 
245
                {ok, NewHeaders, StatusCode} ->
 
246
                    send_headers(ModData, StatusCode, 
 
247
                                 [{"content-length", 
 
248
                                   integer_to_list(Length)}| NewHeaders]),
 
249
                    case ModData#mod.method of
 
250
                        "HEAD" ->
 
251
                            {proceed, [{response, {already_sent, 200, 0}} | 
 
252
                                       ModData#mod.data]};
 
253
                        _ ->
 
254
                            httpd_response:send_body(ModData, 
 
255
                                                     StatusCode, Body),
 
256
                            {proceed, [{response, {already_sent, 200, 
 
257
                                                  Length}} | 
 
258
                                       ModData#mod.data]}
 
259
                    end
 
260
            end
 
261
    end.
 
262
 
 
263
%% New API that allows the dynamic wepage to be sent back to the client 
 
264
%% in small chunks at the time during generation.
 
265
erl_scheme_webpage_chunk(Mod, Func, Env, Input, ModData) -> 
 
266
    process_flag(trap_exit, true),
 
267
    Self = self(),
 
268
    %% Spawn worker that generates the webpage.
 
269
    %% It would be nicer to use erlang:function_exported/3 but if the 
 
270
    %% Module isn't loaded the function says that it is not loaded
 
271
    Pid = spawn_link(
 
272
            fun() ->
 
273
                    case catch Mod:Func(Self, Env, Input) of
 
274
                        {'EXIT',{undef,_}} ->
 
275
                            %% Will force fallback on the old API
 
276
                            exit(erl_scheme_webpage_chunk_undefined);
 
277
                        _ ->
 
278
                            ok  
 
279
                    end
 
280
            end),
 
281
 
 
282
    Response = deliver_webpage_chunk(ModData, Pid), 
 
283
  
 
284
    process_flag(trap_exit,false),
 
285
    Response.
 
286
 
 
287
deliver_webpage_chunk(#mod{config_db = Db} = ModData, Pid) ->
 
288
    Timeout = erl_script_timeout(Db),
 
289
    deliver_webpage_chunk(ModData, Pid, Timeout).
 
290
 
 
291
deliver_webpage_chunk(#mod{config_db = Db} = ModData, Pid, Timeout) ->
 
292
    case receive_headers(Timeout) of
 
293
        {error, Reason} ->
 
294
            %% Happens when webpage generator callback/3 is undefined
 
295
            {error, Reason}; 
 
296
        {Headers, Body} ->
 
297
            case httpd_esi:handle_headers(Headers) of
 
298
                {proceed, AbsPath} ->
 
299
                    {proceed, [{real_name, httpd_util:split_path(AbsPath)} 
 
300
                               | ModData#mod.data]};
 
301
                {ok, NewHeaders, StatusCode} ->
 
302
                    IsDisableChunkedSend = 
 
303
                        httpd_response:is_disable_chunked_send(Db),
 
304
                    case (ModData#mod.http_version =/= "HTTP/1.1") or
 
305
                        (IsDisableChunkedSend) of
 
306
                        true ->
 
307
                            send_headers(ModData, StatusCode, 
 
308
                                         [{"connection", "close"} | 
 
309
                                          NewHeaders]);
 
310
                        false ->
 
311
                            send_headers(ModData, StatusCode, 
 
312
                                         [{"transfer-encoding", 
 
313
                                           "chunked"} | NewHeaders])
 
314
                    end,    
 
315
                    handle_body(Pid, ModData, Body, Timeout, length(Body), 
 
316
                                IsDisableChunkedSend)
 
317
            end;
 
318
        timeout ->
 
319
            send_headers(ModData, {504, "Timeout"},[{"connection", "close"}]),
 
320
            httpd_socket:close(ModData#mod.socket_type, ModData#mod.socket),
 
321
            process_flag(trap_exit,false),
 
322
            {proceed,[{response, {already_sent, 200, 0}} | ModData#mod.data]}
 
323
    end.
 
324
 
 
325
receive_headers(Timeout) ->
 
326
    receive
 
327
        {ok, Chunk} ->
 
328
            httpd_esi:parse_headers(lists:flatten(Chunk));              
 
329
        {'EXIT', Pid, erl_scheme_webpage_chunk_undefined} when is_pid(Pid) ->
 
330
            {error, erl_scheme_webpage_chunk_undefined};
 
331
        {'EXIT', Pid, Reason} when is_pid(Pid) ->
 
332
            exit({mod_esi_linked_process_died, Pid, Reason})
 
333
    after Timeout ->
 
334
            timeout
 
335
    end.
 
336
 
 
337
send_headers(ModData, StatusCode, HTTPHeaders) ->
 
338
    ExtraHeaders = httpd_response:cache_headers(ModData),
 
339
    httpd_response:send_header(ModData, StatusCode, 
 
340
                               ExtraHeaders ++ HTTPHeaders).
 
341
 
 
342
handle_body(_, #mod{method = "HEAD"} = ModData, _, _, Size, _) ->
 
343
    process_flag(trap_exit,false),
 
344
    {proceed, [{response, {already_sent, 200, Size}} | ModData#mod.data]};
 
345
 
 
346
handle_body(Pid, ModData, Body, Timeout, Size, IsDisableChunkedSend) ->
 
347
    httpd_response:send_chunk(ModData, Body, IsDisableChunkedSend),
 
348
    receive 
 
349
        {ok, Data} ->
 
350
            handle_body(Pid, ModData, Data, Timeout, Size + length(Data),
 
351
                        IsDisableChunkedSend);
 
352
        {'EXIT', Pid, normal} when is_pid(Pid) ->
 
353
            httpd_response:send_final_chunk(ModData, IsDisableChunkedSend),
 
354
            {proceed, [{response, {already_sent, 200, Size}} | 
 
355
                       ModData#mod.data]};
 
356
        {'EXIT', Pid, Reason} when is_pid(Pid) ->
 
357
            exit({mod_esi_linked_process_died, Pid, Reason})
 
358
    after Timeout ->
 
359
            process_flag(trap_exit,false),
 
360
            {proceed,[{response, {already_sent, 200, Size}} | 
 
361
                      ModData#mod.data]}  
 
362
    end.
 
363
 
 
364
erl_script_timeout(Db) ->
 
365
    httpd_util:lookup(Db, erl_script_timeout, ?DEFAULT_ERL_TIMEOUT).
 
366
 
 
367
script_elements(FuncAndInput, Input) ->
 
368
    case input_type(FuncAndInput) of
 
369
        path_info ->
 
370
            [{path_info, Input}];
 
371
        query_string ->
 
372
            [{query_string, Input}];
 
373
        _ ->
 
374
            []
 
375
    end.
 
376
 
 
377
input_type([]) ->
 
378
    no_input;
 
379
input_type([$/|_Rest]) ->
 
380
    path_info;
 
381
input_type([$?|_Rest]) ->
 
382
    query_string;
 
383
input_type([_First|Rest]) ->
 
384
    input_type(Rest).
 
385
 
 
386
%%------------------------ Eval mechanism --------------------------------
 
387
 
 
388
eval(#mod{request_uri = ReqUri, method = "POST",
 
389
          http_version = Version, data = Data}, _ESIBody, _Modules) ->
 
390
    {proceed,[{status,{501,{"POST", ReqUri, Version},
 
391
                       ?NICE("Eval mechanism doesn't support method POST")}}|
 
392
              Data]};
 
393
 
 
394
eval(#mod{method = Method} = ModData, ESIBody, Modules) 
 
395
  when Method == "GET"; Method == "HEAD" ->
 
396
    case is_authorized(ESIBody, Modules) of
 
397
        true ->
 
398
            case generate_webpage(ESIBody) of
 
399
                {error, Reason} ->
 
400
                    {proceed, [{status, {500, none, Reason}} | 
 
401
                               ModData#mod.data]};
 
402
                {ok, Response} ->
 
403
                    {Headers, _} = 
 
404
                        httpd_esi:parse_headers(lists:flatten(Response)),
 
405
                    case httpd_esi:handle_headers(Headers) of
 
406
                        {ok, _, StatusCode} ->
 
407
                            {proceed,[{response, {StatusCode, Response}} | 
 
408
                                      ModData#mod.data]};
 
409
                        {proceed, AbsPath} ->
 
410
                            {proceed, [{real_name, AbsPath} | 
 
411
                                       ModData#mod.data]};
 
412
                        {error,Reason} ->
 
413
                            {proceed, [{status, {400, none, Reason}} | 
 
414
                                       ModData#mod.data]}
 
415
                    end
 
416
            end;
 
417
        false ->
 
418
            {proceed,[{status,
 
419
                       {403, ModData#mod.request_uri,
 
420
                        ?NICE("Client not authorized to evaluate: "
 
421
                              ++ ESIBody)}} | ModData#mod.data]}
 
422
    end.
 
423
 
 
424
generate_webpage(ESIBody) ->
 
425
    (catch lib:eval_str(string:concat(ESIBody,". "))).
 
426
 
 
427
is_authorized(_ESIBody, ["all"]) ->
 
428
    true;
 
429
is_authorized(ESIBody, Modules) ->
 
430
    case regexp:match(ESIBody, "^[^\:(%3A)]*") of
 
431
        {match, Start, Length} ->
 
432
            lists:member(string:substr(ESIBody, Start, Length), Modules);
 
433
        nomatch ->
 
434
            false
 
435
    end.