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

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_SUITE_data/src/inets/mod_alias.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

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: mod_alias.erl,v 1.1 2008/12/17 09:53:34 mikpe Exp $
 
17
%%
 
18
-module(mod_alias).
 
19
-export([do/1,real_name/3,real_script_name/3,default_index/2,load/2,path/3]).
 
20
 
 
21
-include("httpd.hrl").
 
22
 
 
23
%% do
 
24
 
 
25
do(Info) ->
 
26
    ?DEBUG("do -> entry",[]),
 
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
                    do_alias(Info);
 
37
                %% A response has been generated or sent!
 
38
                Response ->
 
39
                    {proceed,Info#mod.data}
 
40
            end
 
41
    end.
 
42
 
 
43
do_alias(Info) ->
 
44
    ?DEBUG("do_alias -> Request URI: ~p",[Info#mod.request_uri]),
 
45
    {ShortPath,Path,AfterPath} =
 
46
        real_name(Info#mod.config_db,Info#mod.request_uri,
 
47
                  httpd_util:multi_lookup(Info#mod.config_db,alias)),
 
48
    %% Relocate if a trailing slash is missing else proceed!
 
49
    LastChar = lists:last(ShortPath),
 
50
    case file:read_file_info(ShortPath) of
 
51
        {ok,FileInfo} when FileInfo#file_info.type == directory,LastChar /= $/ ->
 
52
            ?LOG("do_alias -> ~n"
 
53
                 "      ShortPath: ~p~n"
 
54
                 "      LastChar:  ~p~n"
 
55
                 "      FileInfo:  ~p",
 
56
                 [ShortPath,LastChar,FileInfo]),
 
57
            ServerName = httpd_util:lookup(Info#mod.config_db,server_name),
 
58
            Port = port_string(httpd_util:lookup(Info#mod.config_db,port,80)),
 
59
            URL = "http://"++ServerName++Port++Info#mod.request_uri++"/",
 
60
            ReasonPhrase = httpd_util:reason_phrase(301),
 
61
            Message = httpd_util:message(301,URL,Info#mod.config_db),
 
62
            {proceed,
 
63
             [{response,
 
64
               {301, ["Location: ", URL, "\r\n"
 
65
                      "Content-Type: text/html\r\n",
 
66
                      "\r\n",
 
67
                      "<HTML>\n<HEAD>\n<TITLE>",ReasonPhrase,
 
68
                      "</TITLE>\n</HEAD>\n"
 
69
                      "<BODY>\n<H1>",ReasonPhrase,
 
70
                      "</H1>\n", Message,
 
71
                      "\n</BODY>\n</HTML>\n"]}}|
 
72
              [{real_name,{Path,AfterPath}}|Info#mod.data]]};
 
73
        NoFile ->
 
74
            {proceed,[{real_name,{Path,AfterPath}}|Info#mod.data]}
 
75
    end.
 
76
 
 
77
port_string(80) ->
 
78
    "";
 
79
port_string(Port) ->
 
80
    ":"++integer_to_list(Port).
 
81
 
 
82
%% real_name
 
83
 
 
84
real_name(ConfigDB, RequestURI,[]) ->
 
85
    DocumentRoot = httpd_util:lookup(ConfigDB, document_root, ""),
 
86
    RealName = DocumentRoot++RequestURI,
 
87
    {ShortPath, _AfterPath} = httpd_util:split_path(RealName),
 
88
    {Path, AfterPath}=httpd_util:split_path(default_index(ConfigDB,RealName)),
 
89
    {ShortPath, Path, AfterPath};
 
90
real_name(ConfigDB, RequestURI, [{FakeName,RealName}|Rest]) ->
 
91
    case regexp:match(RequestURI, "^"++FakeName) of
 
92
        {match, _, _} ->
 
93
            {ok, ActualName, _} = regexp:sub(RequestURI,
 
94
                                             "^"++FakeName, RealName),
 
95
            {ShortPath, _AfterPath} = httpd_util:split_path(ActualName),
 
96
            {Path, AfterPath} =
 
97
                httpd_util:split_path(default_index(ConfigDB, ActualName)),
 
98
            {ShortPath, Path, AfterPath};
 
99
        nomatch ->
 
100
            real_name(ConfigDB,RequestURI,Rest)
 
101
    end.
 
102
 
 
103
%% real_script_name
 
104
 
 
105
real_script_name(ConfigDB,RequestURI,[]) ->
 
106
    not_a_script;
 
107
real_script_name(ConfigDB,RequestURI,[{FakeName,RealName}|Rest]) ->
 
108
    case regexp:match(RequestURI,"^"++FakeName) of
 
109
        {match,_,_} ->
 
110
            {ok,ActualName,_}=regexp:sub(RequestURI,"^"++FakeName,RealName),
 
111
            httpd_util:split_script_path(default_index(ConfigDB,ActualName));
 
112
        nomatch ->
 
113
            real_script_name(ConfigDB,RequestURI,Rest)
 
114
    end.
 
115
 
 
116
%% default_index
 
117
 
 
118
default_index(ConfigDB, Path) ->
 
119
    case file:read_file_info(Path) of
 
120
        {ok, FileInfo} when FileInfo#file_info.type == directory ->
 
121
            DirectoryIndex = httpd_util:lookup(ConfigDB, directory_index, []),
 
122
            append_index(Path, DirectoryIndex);
 
123
        _ ->
 
124
            Path
 
125
    end.
 
126
 
 
127
append_index(RealName, []) ->
 
128
    RealName;
 
129
append_index(RealName, [Index|Rest]) ->
 
130
    case file:read_file_info(filename:join(RealName, Index)) of
 
131
        {error,Reason} ->
 
132
            append_index(RealName, Rest);
 
133
        _ ->
 
134
            filename:join(RealName,Index)
 
135
    end.
 
136
 
 
137
%% path
 
138
 
 
139
path(Data, ConfigDB, RequestURI) ->
 
140
    case httpd_util:key1search(Data,real_name) of
 
141
        undefined ->
 
142
            DocumentRoot = httpd_util:lookup(ConfigDB, document_root, ""),
 
143
            {Path,AfterPath} =
 
144
                httpd_util:split_path(DocumentRoot++RequestURI),
 
145
            Path;
 
146
        {Path,AfterPath} ->
 
147
            Path
 
148
    end.
 
149
 
 
150
%%
 
151
%% Configuration
 
152
%%
 
153
 
 
154
%% load
 
155
 
 
156
load([$D,$i,$r,$e,$c,$t,$o,$r,$y,$I,$n,$d,$e,$x,$ |DirectoryIndex],[]) ->
 
157
    {ok, DirectoryIndexes} = regexp:split(DirectoryIndex," "),
 
158
    {ok,[], {directory_index, DirectoryIndexes}};
 
159
load([$A,$l,$i,$a,$s,$ |Alias],[]) ->
 
160
    case regexp:split(Alias," ") of
 
161
        {ok, [FakeName, RealName]} ->
 
162
            {ok,[],{alias,{FakeName,RealName}}};
 
163
        {ok, _} ->
 
164
            {error,?NICE(httpd_conf:clean(Alias)++" is an invalid Alias")}
 
165
    end;
 
166
load([$S,$c,$r,$i,$p,$t,$A,$l,$i,$a,$s,$ |ScriptAlias],[]) ->
 
167
    case regexp:split(ScriptAlias," ") of
 
168
        {ok, [FakeName, RealName]} ->
 
169
            %% Make sure the path always has a trailing slash..
 
170
            RealName1 = filename:join(filename:split(RealName)),
 
171
            {ok, [], {script_alias,{FakeName, RealName1++"/"}}};
 
172
        {ok, _} ->
 
173
            {error, ?NICE(httpd_conf:clean(ScriptAlias)++
 
174
                          " is an invalid ScriptAlias")}
 
175
    end.