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

« back to all changes in this revision

Viewing changes to lib/inets/src/mod_responsecontrol.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
 
 
19
 
-module(mod_responsecontrol).
20
 
-export([do/1]).
21
 
 
22
 
-include("httpd.hrl").
23
 
 
24
 
 
25
 
do(Info) ->
26
 
    ?DEBUG("do -> response_control",[]),
27
 
    case httpd_util:key1search(Info#mod.data,status) of
28
 
        %% A status code has been generated!
29
 
        {StatusCode,PhraseArgs,Reason} ->
30
 
            {proceed,Info#mod.data};
31
 
        %% No status code has been generated!
32
 
        undefined ->
33
 
            case httpd_util:key1search(Info#mod.data,response) of
34
 
                %% No response has been generated!
35
 
                undefined ->
36
 
                    case do_responsecontrol(Info) of
37
 
                        continue ->
38
 
                            {proceed,Info#mod.data};
39
 
                        Response ->
40
 
                            {proceed,[Response|Info#mod.data]}
41
 
                    end;
42
 
                %% A response has been generated or sent!
43
 
                Response ->
44
 
                    {proceed,Info#mod.data}
45
 
            end
46
 
    end.
47
 
 
48
 
 
49
 
%%----------------------------------------------------------------------
50
 
%%Control that the request header did not contians any limitations 
51
 
%%wheather a response shall be createed or not
52
 
%%----------------------------------------------------------------------
53
 
 
54
 
do_responsecontrol(Info) ->
55
 
    ?DEBUG("do_response_control -> Request URI: ~p",[Info#mod.request_uri]),
56
 
    Path = mod_alias:path(Info#mod.data, Info#mod.config_db, 
57
 
                          Info#mod.request_uri),
58
 
    case file:read_file_info(Path) of
59
 
        {ok, FileInfo} ->
60
 
            control(Path,Info,FileInfo);
61
 
        _ ->
62
 
            %% The requested asset is not a plain file and then it must 
63
 
            %% be generated everytime its requested
64
 
            continue
65
 
    end.
66
 
 
67
 
%%----------------------------------------------------------------------
68
 
%%Control the If-Match, If-None-Match,  and If-Modified-Since    
69
 
%%----------------------------------------------------------------------
70
 
 
71
 
 
72
 
%% If a client sends more then one of the if-XXXX fields in a request
73
 
%% The standard says it does not specify the behaviuor so I specified it :-)
74
 
%% The priority between the fields is 
75
 
%% 1.If-modified
76
 
%% 2.If-Unmodified
77
 
%% 3.If-Match
78
 
%% 4.If-Nomatch
79
 
 
80
 
%% This means if more than one of the fields are in the request the 
81
 
%% field with highest priority will be used
82
 
 
83
 
%%If the request is a range request the If-Range field will be the winner.
84
 
 
85
 
control(Path,Info,FileInfo)->
86
 
    case control_range(Path,Info,FileInfo) of
87
 
        undefined ->
88
 
            case control_Etag(Path,Info,FileInfo) of
89
 
                undefined ->
90
 
                    case control_modification(Path,Info,FileInfo) of
91
 
                        continue ->
92
 
                            continue;
93
 
                        ReturnValue ->
94
 
                            send_return_value(ReturnValue,FileInfo)
95
 
                    end;
96
 
                continue ->
97
 
                    continue;
98
 
                ReturnValue ->
99
 
                    send_return_value(ReturnValue,FileInfo)
100
 
            end;
101
 
        Response->
102
 
            Response
103
 
    end.
104
 
 
105
 
%%----------------------------------------------------------------------
106
 
%%If there are both a range and an if-range field control if
107
 
%%----------------------------------------------------------------------
108
 
control_range(Path,Info,FileInfo) ->
109
 
    case httpd_util:key1search(Info#mod.parsed_header,"range") of
110
 
        undefined->
111
 
            undefined;
112
 
        _Range ->
113
 
            case httpd_util:key1search(Info#mod.parsed_header,"if-range") of
114
 
                undefined ->
115
 
                    undefined;
116
 
                EtagOrDate ->
117
 
                    control_if_range(Path,Info,FileInfo,EtagOrDate)
118
 
            end
119
 
    end.
120
 
 
121
 
control_if_range(Path,Info,FileInfo,EtagOrDate) ->
122
 
    case httpd_util:convert_request_date(strip_date(EtagOrDate)) of
123
 
        bad_date ->
124
 
            FileEtag=httpd_util:create_etag(FileInfo),
125
 
            case FileEtag of
126
 
                EtagOrDate ->
127
 
                    continue;
128
 
                _ ->
129
 
                    {if_range,send_file}
130
 
            end;
131
 
        ErlDate ->    
132
 
            %%We got the date in the request if it is 
133
 
            case control_modification_data(Info,FileInfo#file_info.mtime,"if-range") of
134
 
                modified ->
135
 
                    {if_range,send_file};
136
 
                _UnmodifiedOrUndefined->
137
 
                    continue
138
 
            end
139
 
    end.
140
 
                 
141
 
%%----------------------------------------------------------------------
142
 
%%Controls the values of the If-Match and I-None-Mtch
143
 
%%----------------------------------------------------------------------
144
 
control_Etag(Path,Info,FileInfo)->
145
 
    FileEtag=httpd_util:create_etag(FileInfo),
146
 
    %%Control if the E-Tag for the resource  matches one of the Etags in
147
 
    %%the -if-match header field
148
 
    case control_match(Info,FileInfo,"if-match",FileEtag) of
149
 
        nomatch ->
150
 
            %%None of the Etags in the if-match field matched the current 
151
 
            %%Etag for the resource return a 304 
152
 
            {412,Info,Path};
153
 
        match ->
154
 
            continue;
155
 
        undefined ->
156
 
            case control_match(Info,FileInfo,"if-none-match",FileEtag) of
157
 
                nomatch ->
158
 
                    continue;
159
 
                match ->
160
 
                    case  Info#mod.method of
161
 
                        "GET" ->
162
 
                            {304,Info,Path};
163
 
                        "HEAD" ->
164
 
                            {304,Info,Path};
165
 
                        _OtherrequestMethod ->
166
 
                            {412,Info,Path}
167
 
                    end;
168
 
                undefined ->
169
 
                    undefined
170
 
            end
171
 
    end.
172
 
 
173
 
%%----------------------------------------------------------------------
174
 
%%Control if there are any Etags for HeaderField in the request if so 
175
 
%%Control if they match the Etag for the requested file
176
 
%%----------------------------------------------------------------------
177
 
control_match(Info,FileInfo,HeaderField,FileEtag)-> 
178
 
    case split_etags(httpd_util:key1search(Info#mod.parsed_header,HeaderField)) of
179
 
        undefined->
180
 
            undefined;
181
 
        Etags->
182
 
            %%Control that the match any star not is availible 
183
 
            case lists:member("*",Etags) of
184
 
                true-> 
185
 
                    match;
186
 
                false->
187
 
                    compare_etags(FileEtag,Etags)
188
 
            end
189
 
    end.
190
 
 
191
 
%%----------------------------------------------------------------------
192
 
%%Split the etags from the request
193
 
%%----------------------------------------------------------------------
194
 
split_etags(undefined)->
195
 
    undefined;
196
 
split_etags(Tags) ->
197
 
    string:tokens(Tags,", ").
198
 
 
199
 
%%----------------------------------------------------------------------
200
 
%%Control if the etag for the file is in the list
201
 
%%----------------------------------------------------------------------
202
 
compare_etags(Tag,Etags) ->
203
 
    case lists:member(Tag,Etags) of
204
 
        true ->
205
 
            match;
206
 
        _ ->
207
 
            nomatch
208
 
    end.
209
 
 
210
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
211
 
%%                                                                   %%
212
 
%%Control if the file is modificated                                 %%
213
 
%%                                                                   %%
214
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%      
215
 
 
216
 
%%----------------------------------------------------------------------
217
 
%%Control the If-Modified-Since and If-Not-Modified-Since header fields
218
 
%%----------------------------------------------------------------------
219
 
control_modification(Path,Info,FileInfo)->
220
 
    ?DEBUG("control_modification() -> entry",[]),
221
 
    case control_modification_data(Info,FileInfo#file_info.mtime,"if-modified-since") of
222
 
        modified->
223
 
            continue;   
224
 
        unmodified->
225
 
            {304,Info,Path};
226
 
        undefined ->
227
 
            case control_modification_data(Info,FileInfo#file_info.mtime,"if-unmodified-since") of
228
 
                modified  ->
229
 
                    {412,Info,Path};
230
 
                _ContinueUndefined ->
231
 
                    continue    
232
 
            end
233
 
    end.
234
 
 
235
 
%%----------------------------------------------------------------------
236
 
%%Controls the date from the http-request if-modified-since and 
237
 
%%if-not-modified-since against the modification data of the
238
 
%%File
239
 
%%----------------------------------------------------------------------     
240
 
%%Info is the record about the request
241
 
%%ModificationTime is the time the file was edited last
242
 
%%Header Field is the name of the field  to control
243
 
 
244
 
control_modification_data(Info,ModificationTime,HeaderField)-> 
245
 
    case strip_date(httpd_util:key1search(Info#mod.parsed_header,HeaderField)) of
246
 
        undefined->
247
 
            undefined;
248
 
        LastModified0 ->
249
 
            LastModified=httpd_util:convert_request_date(LastModified0),
250
 
            ?DEBUG("control_modification_data() -> "
251
 
                   "~n   Request-Field:    ~s"
252
 
                   "~n   FileLastModified: ~p"
253
 
                   "~n   FieldValue:       ~p",
254
 
                   [HeaderField,ModificationTime,LastModified]),
255
 
            case LastModified of 
256
 
                bad_date ->
257
 
                    undefined;
258
 
                _ ->
259
 
                    FileTime=calendar:datetime_to_gregorian_seconds(ModificationTime),
260
 
                    FieldTime=calendar:datetime_to_gregorian_seconds(LastModified),
261
 
                    if 
262
 
                        FileTime=<FieldTime ->
263
 
                            ?DEBUG("File unmodified~n", []),
264
 
                            unmodified;
265
 
                        FileTime>=FieldTime ->
266
 
                            ?DEBUG("File modified~n", []),
267
 
                            modified        
268
 
                    end
269
 
            end
270
 
    end.
271
 
 
272
 
%%----------------------------------------------------------------------
273
 
%%Compare to dates on the form {{YYYY,MM,DD},{HH,MIN,SS}}
274
 
%%If the first date is the biggest returns biggest1 (read biggestFirst)
275
 
%%If the first date is smaller 
276
 
% compare_date(Date,bad_date)->
277
 
%     bad_date;
278
 
 
279
 
% compare_date({D1,T1},{D2,T2})->
280
 
%     case compare_date1(D1,D2) of
281
 
%               equal ->
282
 
%           compare_date1(T1,T2);
283
 
%       GTorLT->
284
 
%           GTorLT
285
 
%     end.
286
 
 
287
 
% compare_date1({T1,T2,T3},{T12,T22,T32}) when T1>T12 ->
288
 
%     bigger1;
289
 
% compare_date1({T1,T2,T3},{T1,T22,T32}) when T2>T22 ->
290
 
%     bigger1;
291
 
% compare_date1({T1,T2,T3},{T1,T2,T32}) when T3>T32 ->
292
 
%     bigger1;
293
 
% compare_date1({T1,T2,T3},{T1,T2,T3})->
294
 
%     equal;
295
 
% compare_date1(_D1,_D2)->
296
 
%     smaller1.
297
 
 
298
 
 
299
 
%% IE4 & NS4 sends an extra '; length=xxxx' string at the end of the If-Modified-Since
300
 
%% header, we detect this and ignore it (the RFCs does not mention this).
301
 
strip_date(undefined) ->
302
 
    undefined;
303
 
strip_date([]) ->
304
 
    [];
305
 
strip_date([$;,$ |Rest]) ->
306
 
    [];
307
 
strip_date([C|Rest]) ->
308
 
    [C|strip_date(Rest)].
309
 
 
310
 
send_return_value({412,_,_},FileInfo)->
311
 
    {status,{412,none,"Precondition Failed"}};
312
 
 
313
 
send_return_value({304,Info,Path},FileInfo)->
314
 
    Suffix=httpd_util:suffix(Path),
315
 
    MimeType = httpd_util:lookup_mime_default(Info#mod.config_db,Suffix,"text/plain"),
316
 
    Header = [{code,304},
317
 
              {etag,httpd_util:create_etag(FileInfo)},
318
 
              {content_length,0},
319
 
              {last_modified,httpd_util:rfc1123_date(FileInfo#file_info.mtime)}],
320
 
    {response,{response,Header,nobody}}.
321
 
              
322
 
 
323
 
 
324
 
 
325
 
 
326
 
        
327
 
 
328
 
 
329
 
 
330
 
 
331
 
 
332
 
 
333
 
 
334
 
 
335
 
 
336
 
 
337