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

« back to all changes in this revision

Viewing changes to lib/inets/src/http.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 Mobile Arts AB
13
 
%% Portions created by Mobile Arts are Copyright 2002, Mobile Arts AB
14
 
%% All Rights Reserved.''
15
 
%% 
16
 
%%
17
 
 
18
 
%%% This version of the HTTP/1.1 client implements:
19
 
%%%      - RFC 2616 HTTP 1.1 client part
20
 
%%%      - RFC 2817 Upgrading to TLS Within HTTP/1.1 (not yet!)
21
 
%%%      - RFC 2818 HTTP Over TLS
22
 
%%%      - RFC 3229 Delta encoding in HTTP (not yet!)
23
 
%%%      - RFC 3230 Instance Digests in HTTP (not yet!)
24
 
%%%      - RFC 3310 Authentication and Key Agreement (AKA) (not yet!)
25
 
%%%      - HTTP/1.1 Specification Errata found at
26
 
%%%        http://skrb.org/ietf/http_errata.html
27
 
%%%    Additionaly follows the following recommendations:
28
 
%%%      - RFC 3143 Known HTTP Proxy/Caching Problems (not yet!)
29
 
%%%      - draft-nottingham-hdrreg-http-00.txt (not yet!)
30
 
%%%
31
 
%%% Depends on
32
 
%%%      - uri.erl for all URL parsing (except what is handled by the C driver)
33
 
%%%      - http_lib.erl for all parsing of body and headers
34
 
%%%
35
 
%%% Supported Settings are:
36
 
%%% http_timeout      % (int) Milliseconds before a request times out
37
 
%%% http_useproxy     % (bool) True if a proxy should be used
38
 
%%% http_proxy        % (string) Proxy
39
 
%%% http_noproxylist  % (list) List with hosts not requiring proxy
40
 
%%% http_autoredirect % (bool) True if automatic redirection on 30X responses
41
 
%%% http_ssl          % (list) SSL settings. A non-empty list enables SSL/TLS
42
 
%%%                      support in the HTTP client
43
 
%%% http_pipelinesize % (int) Length of pipeline. 1 means no pipeline.
44
 
%%%                      Only has effect when initiating a new session.
45
 
%%% http_sessions     % (int) Max number of open sessions for {Addr,Port}
46
 
%%%
47
 
%%% TODO: (Known bugs!)
48
 
%% - Cache handling
49
 
%% - Doesn't handle a bunch of entity headers properly
50
 
%% - Better handling of status codes different from 200,30X and 50X 
51
 
%% - Many of the settings above are not implemented!
52
 
%% - close_session/2 and cancel_request/1 doesn't work
53
 
%% - Variable pipe size.
54
 
%% - Due to the fact that inet_drv only has a single timer, the timeouts given
55
 
%%   for pipelined requests are not ok (too long)
56
 
%%
57
 
%% Note:
58
 
%% - Some servers (e.g. Microsoft-IIS/5.0) may sometimes not return a proper
59
 
%%   'Location' header on a redirect.
60
 
%%   The client will normally fail with {error,no_scheme} in these cases.
61
 
%%   Setting the relax option will cause the client to interpret the value as
62
 
%%   relativeURI 
63
 
 
64
 
-module(http).
65
 
-author("johan.blom@mobilearts.se").
66
 
 
67
 
-export([start/0,
68
 
         request/3,request/4,cancel_request/1,
69
 
         request_sync/2,request_sync/3]).
70
 
 
71
 
-include("http.hrl").
72
 
-include("jnets_httpd.hrl").
73
 
 
74
 
-define(START_OPTIONS,[]).
75
 
 
76
 
%%% HTTP Client manager. Used to store open connections.
77
 
%%% Will be started automatically unless started explicitly.
78
 
start() ->
79
 
    application:start(ssl),
80
 
    httpc_manager:start().
81
 
 
82
 
%%% Asynchronous HTTP request that spawns a handler.
83
 
%%% Method                          HTTPReq
84
 
%%% options,get,head,delete,trace = {Url,Headers}
85
 
%%% post,put                      = {Url,Headers,ContentType,Body}
86
 
%%%  where Url is a {Scheme,Host,Port,PathQuery} tuple, as returned by uri.erl
87
 
%%% 
88
 
%%% Returns: {ok,ReqId} |
89
 
%%%          {error,Reason}
90
 
%%% If {ok,ReqId} was returned, the handler will return with
91
 
%%%    gen_server:cast(From,{Ref,ReqId,{error,Reason}}) |
92
 
%%%    gen_server:cast(From,{Ref,ReqId,{Status,Headers,Body}})
93
 
%%%  where Reason is an atom and Headers a #res_headers{} record
94
 
%%% http:format_error(Reason) gives a more informative description.
95
 
%%% 
96
 
%%% Note:
97
 
%%% - Always try to find an open connection to a given host and port, and use
98
 
%%%   the associated socket.
99
 
%%% - Unless a 'Connection: close' header is provided don't close the socket
100
 
%%%   after a response is given 
101
 
%%% - A given Pid, found in the database, might be terminated before the
102
 
%%%   message is sent to the Pid. This will happen e.g., if the connection is
103
 
%%%   closed by the other party and there are no pending requests.
104
 
%%% - The HTTP connection process is spawned, if necessary, in
105
 
%%%   httpc_manager:add_connection/4
106
 
request(Ref,Method,HTTPReqCont) ->
107
 
    request(Ref,Method,HTTPReqCont,[],self()).
108
 
 
109
 
request(Ref,Method,HTTPReqCont,Settings) ->
110
 
    request(Ref,Method,HTTPReqCont,Settings,self()).
111
 
 
112
 
request(Ref,Method,{{Scheme,Host,Port,PathQuery},
113
 
                    Headers,ContentType,Body},Settings,From) ->
114
 
    case create_settings(Settings,#client_settings{}) of
115
 
        {error,Reason} ->
116
 
            {error,Reason};
117
 
        CS ->
118
 
            case create_headers(Headers,#req_headers{}) of
119
 
                {error,Reason} ->
120
 
                    {error,Reason};
121
 
                H ->
122
 
                    Req=#request{ref=Ref,from=From,
123
 
                                 scheme=Scheme,address={Host,Port},
124
 
                                 pathquery=PathQuery,method=Method,
125
 
                                 headers=H,content={ContentType,Body},
126
 
                                 settings=CS},
127
 
                    httpc_manager:request(Req)
128
 
            end
129
 
    end;
130
 
request(Ref,Method,{Url,Headers},Settings,From) ->
131
 
    request(Ref,Method,{Url,Headers,[],[]},Settings,From).
132
 
 
133
 
%%% Cancels requests identified with ReqId.
134
 
%%% FIXME! Doesn't work... 
135
 
cancel_request(ReqId) ->
136
 
    httpc_manager:cancel_request(ReqId).
137
 
 
138
 
%%% Close all sessions currently open to Host:Port
139
 
%%% FIXME! Doesn't work... 
140
 
close_session(Host,Port) ->
141
 
    httpc_manager:close_session(Host,Port).
142
 
    
143
 
 
144
 
%%% Synchronous HTTP request that waits until a response is created
145
 
%%% (e.g. successfull reply or timeout)
146
 
%%% Method                          HTTPReq
147
 
%%% options,get,head,delete,trace = {Url,Headers}
148
 
%%% post,put                      = {Url,Headers,ContentType,Body}
149
 
%%%  where Url is a string() or a {Scheme,Host,Port,PathQuery} tuple
150
 
%%% 
151
 
%%% Returns: {Status,Headers,Body} |
152
 
%%%          {error,Reason}
153
 
%%% where Reason is an atom. 
154
 
%%% http:format_error(Reason) gives a more informative description.
155
 
request_sync(Method,HTTPReqCont) ->
156
 
    request_sync(Method,HTTPReqCont,[]).
157
 
 
158
 
request_sync(Method,{Url,Headers},Settings)
159
 
  when Method==options;Method==get;Method==head;Method==delete;Method==trace ->
160
 
    case uri:parse(Url) of
161
 
        {error,Reason} ->
162
 
            {error,Reason};
163
 
        ParsedUrl ->
164
 
            request_sync2(Method,{ParsedUrl,Headers,[],[]},Settings)
165
 
    end;
166
 
request_sync(Method,{Url,Headers,ContentType,Body},Settings)
167
 
  when Method==post;Method==put ->
168
 
    case uri:parse(Url) of
169
 
        {error,Reason} ->
170
 
            {error,Reason};
171
 
        ParsedUrl ->
172
 
            request_sync2(Method,{ParsedUrl,Headers,ContentType,Body},Settings)
173
 
    end;
174
 
request_sync(Method,Request,Settings) ->
175
 
    {error,bad_request}.
176
 
 
177
 
request_sync2(Method,HTTPCont,Settings) ->
178
 
    case request(request_sync,Method,HTTPCont,Settings,self()) of
179
 
        {ok,_ReqId} ->
180
 
            receive
181
 
                {'$gen_cast',{request_sync,_ReqId2,{Status,Headers,Body}}} ->
182
 
                    {Status,pp_headers(Headers),binary_to_list(Body)};
183
 
                {'$gen_cast',{request_sync,_ReqId2,{error,Reason}}} ->
184
 
                    {error,Reason}
185
 
            end;
186
 
        Error ->
187
 
            Error
188
 
    end.
189
 
 
190
 
 
191
 
create_settings([],Out) ->
192
 
    Out;
193
 
create_settings([{http_timeout,Val}|Settings],Out) ->
194
 
    create_settings(Settings,Out#client_settings{timeout=Val});
195
 
create_settings([{http_useproxy,Val}|Settings],Out) ->
196
 
    create_settings(Settings,Out#client_settings{useproxy=Val});
197
 
create_settings([{http_proxy,Val}|Settings],Out) ->
198
 
    create_settings(Settings,Out#client_settings{proxy=Val});
199
 
create_settings([{http_noproxylist,Val}|Settings],Out) ->
200
 
    create_settings(Settings,Out#client_settings{noproxylist=Val});
201
 
create_settings([{http_autoredirect,Val}|Settings],Out) ->
202
 
    create_settings(Settings,Out#client_settings{autoredirect=Val});
203
 
create_settings([{http_ssl,Val}|Settings],Out) ->
204
 
    create_settings(Settings,Out#client_settings{ssl=Val});
205
 
create_settings([{http_pipelinesize,Val}|Settings],Out)
206
 
  when integer(Val),Val>0 ->
207
 
    create_settings(Settings,Out#client_settings{max_quelength=Val});
208
 
create_settings([{http_sessions,Val}|Settings],Out)
209
 
  when integer(Val),Val>0 ->
210
 
    create_settings(Settings,Out#client_settings{max_sessions=Val});
211
 
create_settings([{http_relaxed,Val}|Settings],Out) when Val==true;Val==false ->
212
 
    create_settings(Settings,Out#client_settings{relaxed=Val});
213
 
create_settings([{Key,_Val}|_Settings],_Out) ->
214
 
    io:format("ERROR bad settings, got ~p~n",[Key]),
215
 
    {error,bad_settings}.
216
 
 
217
 
 
218
 
create_headers([],Req) ->
219
 
    Req;
220
 
create_headers([{Key,Val}|Rest],Req) ->
221
 
    case httpd_util:to_lower(Key) of
222
 
        "expect" ->
223
 
            create_headers(Rest,Req#req_headers{expect=Val});
224
 
        OtherKey ->
225
 
            create_headers(Rest,
226
 
                           Req#req_headers{other=[{OtherKey,Val}|
227
 
                                                  Req#req_headers.other]})
228
 
    end.
229
 
                
230
 
 
231
 
pp_headers(#res_headers{connection=Connection,
232
 
                        transfer_encoding=Transfer_encoding,
233
 
                        retry_after=Retry_after,
234
 
                        content_length=Content_length,
235
 
                        content_type=Content_type,
236
 
                        location=Location,
237
 
                        other=Other}) ->
238
 
    H1=case Connection of
239
 
           undefined -> [];
240
 
           _ ->  [{'Connection',Connection}]
241
 
       end,
242
 
    H2=case Transfer_encoding of
243
 
           undefined -> [];
244
 
           _ ->  [{'Transfer-Encoding',Transfer_encoding}]
245
 
       end,
246
 
    H3=case Retry_after of
247
 
           undefined -> [];
248
 
           _ ->  [{'Retry-After',Retry_after}]
249
 
       end,
250
 
    H4=case Location of
251
 
           undefined -> [];
252
 
           _ ->  [{'Location',Location}]
253
 
       end,
254
 
    HCL=case Content_length of
255
 
           "0" -> [];
256
 
           _ ->  [{'Content-Length',Content_length}]
257
 
       end,
258
 
    HCT=case Content_type of
259
 
           undefined -> [];
260
 
           _ ->  [{'Content-Type',Content_type}]
261
 
       end,
262
 
    H1++H2++H3++H4++HCL++HCT++Other.