~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/inets/src/http_server/mod_alias.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
%%
28
28
         path/3]).
29
29
 
30
30
-include("httpd.hrl").
 
31
-include("httpd_internal.hrl").
 
32
-include("inets_internal.hrl").
31
33
 
32
34
-define(VMODULE,"ALIAS").
33
35
 
34
36
%% do
35
37
 
36
 
do(Info) ->
37
 
    case proplists:get_value(status, Info#mod.data) of
 
38
do(#mod{data = Data} = Info) ->
 
39
    ?hdrt("do", []),
 
40
    case proplists:get_value(status, Data) of
38
41
        %% A status code has been generated!
39
42
        {_StatusCode, _PhraseArgs, _Reason} ->
40
 
            {proceed,Info#mod.data};
 
43
            {proceed, Data};
41
44
        %% No status code has been generated!
42
45
        undefined ->
43
 
            case proplists:get_value(response, Info#mod.data) of
 
46
            case proplists:get_value(response, Data) of
44
47
                %% No response has been generated!
45
48
                undefined ->
46
49
                    do_alias(Info);
47
50
                %% A response has been generated or sent!
48
51
                _Response ->
49
 
                    {proceed, Info#mod.data}
 
52
                    {proceed, Data}
50
53
            end
51
54
    end.
52
55
 
53
 
do_alias(Info) ->
54
 
    {ShortPath, Path, AfterPath} =
55
 
        real_name(Info#mod.config_db, 
56
 
                  Info#mod.request_uri,
57
 
                  httpd_util:multi_lookup(Info#mod.config_db,alias)),
 
56
do_alias(#mod{config_db   = ConfigDB, 
 
57
              request_uri = ReqURI,
 
58
              data        = Data}) ->
 
59
    {ShortPath, Path, AfterPath} = 
 
60
        real_name(ConfigDB, ReqURI, which_alias(ConfigDB)),
 
61
    ?hdrt("real name", 
 
62
          [{request_uri, ReqURI}, 
 
63
           {short_path,  ShortPath}, 
 
64
           {path,        Path}, 
 
65
           {after_path,  AfterPath}]),
58
66
    %% Relocate if a trailing slash is missing else proceed!
59
67
    LastChar = lists:last(ShortPath),
60
68
    case file:read_file_info(ShortPath) of 
61
 
        {ok, FileInfo} when FileInfo#file_info.type == directory, 
62
 
        LastChar /= $/ ->
63
 
            ServerName = httpd_util:lookup(Info#mod.config_db, server_name),
64
 
            Port = port_string(httpd_util:lookup(Info#mod.config_db,port, 80)),
65
 
            URL = "http://" ++ ServerName ++ Port ++ 
66
 
                Info#mod.request_uri ++ "/",
 
69
        {ok, FileInfo} when ((FileInfo#file_info.type =:= directory) andalso 
 
70
                             (LastChar =/= $/)) ->
 
71
            ?hdrt("directory and last-char is a /", []),
 
72
            ServerName = which_server_name(ConfigDB), 
 
73
            Port = port_string( which_port(ConfigDB) ),
 
74
            URL = "http://" ++ ServerName ++ Port ++ ReqURI ++ "/",
67
75
            ReasonPhrase = httpd_util:reason_phrase(301),
68
 
            Message = httpd_util:message(301, URL, Info#mod.config_db),
 
76
            Message = httpd_util:message(301, URL, ConfigDB),
69
77
            {proceed,
70
78
             [{response,
71
79
               {301, ["Location: ", URL, "\r\n"
76
84
                      "<BODY>\n<H1>",ReasonPhrase,
77
85
                      "</H1>\n", Message, 
78
86
                      "\n</BODY>\n</HTML>\n"]}}|
79
 
              [{real_name, {Path, AfterPath}} | Info#mod.data]]};
 
87
              [{real_name, {Path, AfterPath}} | Data]]};
80
88
        _NoFile ->
81
 
            {proceed,[{real_name, {Path, AfterPath}} | Info#mod.data]}
 
89
            {proceed, [{real_name, {Path, AfterPath}} | Data]}
82
90
    end.
83
91
 
84
92
port_string(80) ->
85
93
    "";
86
94
port_string(Port) ->
87
 
    ":"++integer_to_list(Port).
 
95
    ":" ++ integer_to_list(Port).
88
96
 
89
97
%% real_name
90
98
 
91
99
real_name(ConfigDB, RequestURI, []) ->
92
 
    DocumentRoot = httpd_util:lookup(ConfigDB, document_root, ""),
 
100
    DocumentRoot = which_document_root(ConfigDB), 
93
101
    RealName = DocumentRoot ++ RequestURI,
94
102
    {ShortPath, _AfterPath} = httpd_util:split_path(RealName),
95
 
    {Path, AfterPath} = httpd_util:split_path(default_index(ConfigDB, 
96
 
                                                            RealName)),
 
103
    {Path, AfterPath} = 
 
104
        httpd_util:split_path(default_index(ConfigDB, RealName)),
97
105
    {ShortPath, Path, AfterPath};
 
106
 
 
107
real_name(ConfigDB, RequestURI, [{MP,Replacement}|Rest])
 
108
  when element(1, MP) =:= re_pattern ->
 
109
    case re:run(RequestURI, MP, [{capture,[]}]) of
 
110
        match ->
 
111
            NewURI = re:replace(RequestURI, MP, Replacement, [{return,list}]),
 
112
            {ShortPath,_} = httpd_util:split_path(NewURI),
 
113
            {Path,AfterPath} =
 
114
                httpd_util:split_path(default_index(ConfigDB, NewURI)),
 
115
            {ShortPath, Path, AfterPath};
 
116
        nomatch ->
 
117
            real_name(ConfigDB, RequestURI, Rest)
 
118
    end;
 
119
 
98
120
real_name(ConfigDB, RequestURI, [{FakeName,RealName}|Rest]) ->
99
121
     case inets_regexp:match(RequestURI, "^" ++ FakeName) of
100
122
        {match, _, _} ->
105
127
               httpd_util:split_path(default_index(ConfigDB, ActualName)),
106
128
            {ShortPath, Path, AfterPath};
107
129
         nomatch ->
108
 
             real_name(ConfigDB,RequestURI,Rest)
 
130
             real_name(ConfigDB, RequestURI, Rest)
109
131
    end.
110
132
 
111
133
%% real_script_name
112
134
 
113
135
real_script_name(_ConfigDB, _RequestURI, []) ->
114
136
    not_a_script;
 
137
 
 
138
real_script_name(ConfigDB, RequestURI, [{MP,Replacement} | Rest])
 
139
  when element(1, MP) =:= re_pattern ->
 
140
    case re:run(RequestURI, MP, [{capture,[]}]) of
 
141
        match ->
 
142
            ActualName =
 
143
                re:replace(RequestURI, MP, Replacement, [{return,list}]),
 
144
            httpd_util:split_script_path(default_index(ConfigDB, ActualName));
 
145
        nomatch ->
 
146
            real_script_name(ConfigDB, RequestURI, Rest)
 
147
    end;
 
148
 
115
149
real_script_name(ConfigDB, RequestURI, [{FakeName,RealName} | Rest]) ->
116
 
    case inets_regexp:match(RequestURI,"^"++FakeName) of
 
150
    case inets_regexp:match(RequestURI, "^" ++ FakeName) of
117
151
        {match,_,_} ->
118
 
            {ok,ActualName,_}=inets_regexp:sub(RequestURI,"^"++FakeName,RealName),
119
 
            httpd_util:split_script_path(default_index(ConfigDB,ActualName));
 
152
            {ok, ActualName, _} = 
 
153
                inets_regexp:sub(RequestURI, "^" ++ FakeName, RealName),
 
154
            httpd_util:split_script_path(default_index(ConfigDB, ActualName));
120
155
        nomatch ->
121
 
            real_script_name(ConfigDB,RequestURI,Rest)
 
156
            real_script_name(ConfigDB, RequestURI, Rest)
122
157
    end.
123
158
 
124
159
%% default_index
125
160
 
126
161
default_index(ConfigDB, Path) ->
127
162
    case file:read_file_info(Path) of
128
 
        {ok, FileInfo} when FileInfo#file_info.type == directory ->
129
 
            DirectoryIndex = httpd_util:lookup(ConfigDB, directory_index, []),
 
163
        {ok, FileInfo} when FileInfo#file_info.type =:= directory ->
 
164
            DirectoryIndex = which_directory_index(ConfigDB),
130
165
            append_index(Path, DirectoryIndex);
131
166
        _ ->
132
167
            Path
147
182
path(Data, ConfigDB, RequestURI) ->
148
183
    case proplists:get_value(real_name, Data) of
149
184
        undefined ->
150
 
            DocumentRoot = httpd_util:lookup(ConfigDB, document_root, ""),
 
185
            DocumentRoot = which_document_root(ConfigDB), 
151
186
            {Path, _AfterPath} = 
152
 
                httpd_util:split_path(DocumentRoot++RequestURI),
 
187
                httpd_util:split_path(DocumentRoot ++ RequestURI),
153
188
            Path;
154
189
        {Path, _AfterPath} ->
155
190
            Path
164
199
load("DirectoryIndex " ++ DirectoryIndex, []) ->
165
200
    {ok, DirectoryIndexes} = inets_regexp:split(DirectoryIndex," "),
166
201
    {ok,[], {directory_index, DirectoryIndexes}};
167
 
load("Alias " ++ Alias,[]) ->
 
202
load("Alias " ++ Alias, []) ->
168
203
    case inets_regexp:split(Alias," ") of
169
204
        {ok, [FakeName, RealName]} ->
170
205
            {ok,[],{alias,{FakeName,RealName}}};
171
206
        {ok, _} ->
172
207
            {error,?NICE(httpd_conf:clean(Alias)++" is an invalid Alias")}
173
208
    end;
 
209
load("ReWrite " ++ Rule, Acc) ->
 
210
    load_re_write(Rule, Acc, "ReWrite", re_write);
174
211
load("ScriptAlias " ++ ScriptAlias, []) ->
175
212
    case inets_regexp:split(ScriptAlias, " ") of
176
213
        {ok, [FakeName, RealName]} ->
180
217
        {ok, _} ->
181
218
            {error, ?NICE(httpd_conf:clean(ScriptAlias)++
182
219
                          " is an invalid ScriptAlias")}
 
220
    end;
 
221
load("ScriptReWrite " ++ Rule, Acc) ->
 
222
    load_re_write(Rule, Acc, "ScriptReWrite", script_re_write).
 
223
 
 
224
load_re_write(Rule0, Acc, Type, Tag) ->
 
225
    case lists:dropwhile(
 
226
           fun ($\s) -> true; ($\t) -> true; (_) -> false end,
 
227
           Rule0) of
 
228
        "" ->
 
229
            {error, ?NICE(httpd_conf:clean(Rule0)++" is an invalid "++Type)};
 
230
        Rule ->
 
231
            case string:chr(Rule, $\s) of
 
232
                0 ->
 
233
                    {ok, Acc, {Tag, {Rule, ""}}};
 
234
                N ->
 
235
                    {Re, [_|Replacement]} = lists:split(N-1, Rule),
 
236
                    {ok, Acc, {Tag, {Re, Replacement}}}
 
237
            end
183
238
    end.
184
239
 
185
240
store({directory_index, Value} = Conf, _) when is_list(Value) ->
191
246
    end;
192
247
store({directory_index, Value}, _) ->
193
248
    {error, {wrong_type, {directory_index, Value}}};
194
 
store({alias, {Fake, Real}} = Conf, _) when is_list(Fake),
195
 
                                            is_list(Real) ->
 
249
store({alias, {Fake, Real}} = Conf, _)
 
250
  when is_list(Fake), is_list(Real) ->
196
251
    {ok, Conf};
197
252
store({alias, Value}, _) ->
198
253
    {error, {wrong_type, {alias, Value}}};
199
 
store({script_alias, {Fake, Real}} = Conf, _) when is_list(Fake),
200
 
                                                   is_list(Real) ->
 
254
store({re_write, {Re, Replacement}} = Conf, _)
 
255
  when is_list(Re), is_list(Replacement) ->
 
256
    case re:compile(Re) of
 
257
        {ok, MP} ->
 
258
            {ok, {alias, {MP, Replacement}}};
 
259
        {error,_} ->
 
260
            {error, {re_compile, Conf}}
 
261
    end;
 
262
store({re_write, _} = Conf, _) ->
 
263
    {error, {wrong_type, Conf}};
 
264
store({script_alias, {Fake, Real}} = Conf, _) 
 
265
  when is_list(Fake), is_list(Real) ->
201
266
    {ok, Conf};
202
267
store({script_alias, Value}, _) ->
203
 
    {error, {wrong_type, {script_alias, Value}}}.
 
268
    {error, {wrong_type, {script_alias, Value}}};
 
269
store({script_re_write, {Re, Replacement}} = Conf, _)
 
270
  when is_list(Re), is_list(Replacement) ->
 
271
    case re:compile(Re) of
 
272
        {ok, MP} ->
 
273
            {ok, {script_alias, {MP, Replacement}}};
 
274
        {error,_} ->
 
275
            {error, {re_compile, Conf}}
 
276
    end;
 
277
store({script_re_write, _} = Conf, _) ->
 
278
    {error, {wrong_type, Conf}}.
204
279
 
205
280
is_directory_index_list([]) ->
206
281
    true;
208
283
    is_directory_index_list(Tail);
209
284
is_directory_index_list(_) ->
210
285
    false.
 
286
 
 
287
 
 
288
%% ---------------------------------------------------------------------
 
289
 
 
290
which_alias(ConfigDB) ->
 
291
    httpd_util:multi_lookup(ConfigDB, alias). 
 
292
 
 
293
which_server_name(ConfigDB) ->
 
294
    httpd_util:lookup(ConfigDB, server_name).
 
295
 
 
296
which_port(ConfigDB) ->
 
297
    httpd_util:lookup(ConfigDB, port, 80). 
 
298
 
 
299
which_document_root(ConfigDB) ->
 
300
    httpd_util:lookup(ConfigDB, document_root, "").
 
301
 
 
302
which_directory_index(ConfigDB) ->
 
303
    httpd_util:lookup(ConfigDB, directory_index, []).