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

« back to all changes in this revision

Viewing changes to lib/inets/src/http_server/mod_include.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
89
89
update_context([Tag|R1],[Value|R2],Context) ->
90
90
    update_context(R1,R2,[{Tag,Value}|Context]).
91
91
 
92
 
verify_tags(Command,ValidTags,TagList,ValueList) when length(TagList)==length(ValueList) ->
 
92
verify_tags(Command,ValidTags,TagList,ValueList) 
 
93
  when length(TagList) =:= length(ValueList) ->
93
94
    verify_tags(Command, ValidTags, TagList);
94
95
verify_tags(Command, _ValidTags, _TagList, _ValueList) ->
95
96
    {error, ?NICE(Command ++ " directive has spurious tags")}.
167
168
 
168
169
document_name(Data,ConfigDB,RequestURI) ->
169
170
    Path = mod_alias:path(Data,ConfigDB,RequestURI),
170
 
    case regexp:match(Path,"[^/]*\$") of
 
171
    case inets_regexp:match(Path,"[^/]*\$") of
171
172
        {match,Start,Length} ->
172
173
            string:substr(Path,Start,Length);
173
174
        nomatch ->
181
182
    
182
183
    VirtualPath = string:substr(RequestURI, 1, 
183
184
                                length(RequestURI)-length(AfterPath)),
184
 
    {match, Start, Length} = regexp:match(Path,"[^/]*\$"),
 
185
    {match, Start, Length} = inets_regexp:match(Path,"[^/]*\$"),
185
186
    FileName = string:substr(Path,Start,Length),
186
 
    case regexp:match(VirtualPath, FileName++"\$") of
 
187
    case inets_regexp:match(VirtualPath, FileName++"\$") of
187
188
        {match, _, _} ->
188
189
            httpd_util:decode_hex(VirtualPath)++AfterPath;
189
190
        nomatch ->
192
193
    end.
193
194
 
194
195
query_string_unescaped(RequestURI) ->
195
 
  case regexp:match(RequestURI,"[\?].*\$") of
 
196
  case inets_regexp:match(RequestURI,"[\?].*\$") of
196
197
    {match,Start,Length} ->
197
198
      %% Escape all shell-special variables with \
198
199
      escape(string:substr(RequestURI,Start+1,Length-1));      
328
329
    Dir  = filename:dirname(Command),
329
330
    Port = (catch open_port({spawn,Command},[stream,{cd,Dir},{env,Env}])),
330
331
    case Port of
331
 
        P when port(P) ->
 
332
        P when is_port(P) ->
332
333
            {NewErrorLog, Result} = proxy(Port, ErrorLog),
333
334
            {ok, Context, NewErrorLog, Result, R};
334
335
        {'EXIT', Reason} ->
383
384
    Dir  = filename:dirname(Path),
384
385
    Port = (catch open_port({spawn,Script},[stream,{env, Env},{cd, Dir}])),
385
386
    case Port of
386
 
        P when port(P) ->
 
387
        P when is_port(P) ->
387
388
            %% Send entity body to port.
388
389
            Res = case Info#mod.entity_body of
389
390
                      [] ->
425
426
    receive
426
427
        {Port, {data, Response}} ->
427
428
            proxy(Port, ErrorLog, lists:append(Result,Response));
428
 
        {'EXIT', Port, normal} when port(Port) ->
 
429
        {'EXIT', Port, normal} when is_port(Port) ->
429
430
            process_flag(trap_exit, false),
430
431
            {ErrorLog, Result};
431
 
        {'EXIT', Port, _Reason} when port(Port) ->
 
432
        {'EXIT', Port, _Reason} when is_port(Port) ->
432
433
            process_flag(trap_exit, false),
433
434
            {[{internal_info,
434
435
               ?NICE("Scrambled output from CGI-script")}|ErrorLog],
435
436
             Result};
436
 
        {'EXIT', Pid, Reason} when pid(Pid) ->
 
437
        {'EXIT', Pid, Reason} when is_pid(Pid) ->
437
438
            process_flag(trap_exit, false),
438
439
            {'EXIT', Pid, Reason};
439
440
        %% This should not happen!
463
464
    {ok, _Context, Err, ParsedBody} = parse(Info,Data,?DEFAULT_CONTEXT,[],[]),
464
465
    Size = length(ParsedBody),
465
466
    LastModified = case catch httpd_util:rfc1123_date(FileInfo#file_info.mtime) of
466
 
                       Date when list(Date) -> [{last_modified,Date}];
 
467
                       Date when is_list(Date) -> [{last_modified,Date}];
467
468
                       _ -> []
468
469
                   end,
469
470
    Head1 = case Info#mod.http_version of 
580
581
  parse5(R,[C|Comment],Depth).
581
582
 
582
583
 
583
 
sz(B) when binary(B) -> {binary,size(B)};
584
 
sz(L) when list(L)   -> {list,length(L)};
585
 
sz(_)                -> undefined.
 
584
sz(B) when is_binary(B) -> {binary,size(B)};
 
585
sz(L) when is_list(L)   -> {list,length(L)};
 
586
sz(_)                   -> undefined.
586
587
 
587
588
%% send_error - Handle failure to send the file
588
589
%%