~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_get.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_get.erl,v 1.1 2008/12/17 09:53:35 mikpe Exp $
 
17
%%
 
18
-module(mod_get).
 
19
-export([do/1]).
 
20
-include("httpd.hrl").
 
21
 
 
22
%% do
 
23
 
 
24
do(Info) ->
 
25
    ?DEBUG("do -> entry",[]),
 
26
    case Info#mod.method of
 
27
        "GET" ->
 
28
            case httpd_util:key1search(Info#mod.data,status) of
 
29
                %% A status code has been generated!
 
30
                {StatusCode,PhraseArgs,Reason} ->
 
31
                    {proceed,Info#mod.data};
 
32
                %% No status code has been generated!
 
33
                undefined ->
 
34
                    case httpd_util:key1search(Info#mod.data,response) of
 
35
                        %% No response has been generated!
 
36
                        undefined ->
 
37
                            do_get(Info);
 
38
                        %% A response has been generated or sent!
 
39
                        Response ->
 
40
                            {proceed,Info#mod.data}
 
41
                    end
 
42
            end;
 
43
        %% Not a GET method!
 
44
        _ ->
 
45
            {proceed,Info#mod.data}
 
46
    end.
 
47
 
 
48
 
 
49
do_get(Info) ->
 
50
    ?DEBUG("do_get -> Request URI: ~p",[Info#mod.request_uri]),
 
51
    Path = mod_alias:path(Info#mod.data, Info#mod.config_db,
 
52
                          Info#mod.request_uri),
 
53
    {FileInfo, LastModified} =get_modification_date(Path),
 
54
 
 
55
    send_response(Info#mod.socket,Info#mod.socket_type,Path,Info,FileInfo,LastModified).
 
56
 
 
57
 
 
58
%%The common case when no range is specified
 
59
send_response(Socket,SocketType,Path,Info,FileInfo,LastModified)->
 
60
    %% Send the file!
 
61
    %% Find the modification date of the file
 
62
    case file:open(Path,[raw,binary]) of
 
63
        {ok, FileDescriptor} ->
 
64
            ?DEBUG("do_get -> FileDescriptor: ~p",[FileDescriptor]),
 
65
            Suffix = httpd_util:suffix(Path),
 
66
            MimeType = httpd_util:lookup_mime_default(Info#mod.config_db,
 
67
                                                      Suffix,"text/plain"),
 
68
            %FileInfo=file:read_file_info(Path),
 
69
            Date = httpd_util:rfc1123_date(),
 
70
            Size = integer_to_list(FileInfo#file_info.size),
 
71
            Header=case Info#mod.http_version of
 
72
                       "HTTP/1.1" ->
 
73
                           [httpd_util:header(200, MimeType, Info#mod.connection),
 
74
                            "Last-Modified: ", LastModified, "\r\n",
 
75
                            "Etag: ",httpd_util:create_etag(FileInfo),"\r\n",
 
76
                            "Content-Length: ",Size,"\r\n\r\n"];
 
77
                       "HTTP/1.0" ->
 
78
                           [httpd_util:header(200, MimeType, Info#mod.connection),
 
79
                            "Last-Modified: ", LastModified, "\r\n",
 
80
                            "Content-Length: ",Size,"\r\n\r\n"]
 
81
                   end,
 
82
 
 
83
            send(Info#mod.socket_type, Info#mod.socket,
 
84
                 Header, FileDescriptor),
 
85
            file:close(FileDescriptor),
 
86
            {proceed,[{response,{already_sent,200,
 
87
                                 FileInfo#file_info.size}},
 
88
                      {mime_type,MimeType}|Info#mod.data]};
 
89
        {error, Reason} ->
 
90
 
 
91
            {proceed,
 
92
             [{status,open_error(Reason,Info,Path)}|Info#mod.data]}
 
93
    end.
 
94
 
 
95
%% send
 
96
 
 
97
send(SocketType,Socket,Header,FileDescriptor) ->
 
98
    ?DEBUG("send -> send header",[]),
 
99
    case httpd_socket:deliver(SocketType,Socket,Header) of
 
100
        socket_closed ->
 
101
            ?LOG("send -> socket closed while sending header",[]),
 
102
            socket_close;
 
103
        _ ->
 
104
            send_body(SocketType,Socket,FileDescriptor)
 
105
    end.
 
106
 
 
107
send_body(SocketType,Socket,FileDescriptor) ->
 
108
    case file:read(FileDescriptor,?FILE_CHUNK_SIZE) of
 
109
        {ok,Binary} ->
 
110
            ?DEBUG("send_body -> send another chunk: ~p",[size(Binary)]),
 
111
            case httpd_socket:deliver(SocketType,Socket,Binary) of
 
112
                socket_closed ->
 
113
                    ?LOG("send_body -> socket closed while sending",[]),
 
114
                    socket_close;
 
115
                _ ->
 
116
                    send_body(SocketType,Socket,FileDescriptor)
 
117
            end;
 
118
        eof ->
 
119
            ?DEBUG("send_body -> done with this file",[]),
 
120
            eof
 
121
    end.
 
122
 
 
123
 
 
124
%% open_error - Handle file open failure
 
125
%%
 
126
open_error(eacces,Info,Path) ->
 
127
    open_error(403,Info,Path,"");
 
128
open_error(enoent,Info,Path) ->
 
129
    open_error(404,Info,Path,"");
 
130
open_error(enotdir,Info,Path) ->
 
131
    open_error(404,Info,Path,
 
132
               ": A component of the file name is not a directory");
 
133
open_error(emfile,_Info,Path) ->
 
134
    open_error(500,none,Path,": To many open files");
 
135
open_error({enfile,_},_Info,Path) ->
 
136
    open_error(500,none,Path,": File table overflow");
 
137
open_error(_Reason,_Info,Path) ->
 
138
    open_error(500,none,Path,"").
 
139
 
 
140
open_error(StatusCode,none,Path,Reason) ->
 
141
    {StatusCode,none,?NICE("Can't open "++Path++Reason)};
 
142
open_error(StatusCode,Info,Path,Reason) ->
 
143
    {StatusCode,Info#mod.request_uri,?NICE("Can't open "++Path++Reason)}.
 
144
 
 
145
get_modification_date(Path)->
 
146
    case file:read_file_info(Path) of
 
147
        {ok, FileInfo0} ->
 
148
            {FileInfo0, httpd_util:rfc1123_date(FileInfo0#file_info.mtime)};
 
149
        _ ->
 
150
            {#file_info{},""}
 
151
    end.