~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/inets/http.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
%% ``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://world.std.com/~lawrence/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 fail with {error,no_scheme} in these cases.
 
61
 
 
62
-module(http).
 
63
-author("johan.blom@mobilearts.se").
 
64
 
 
65
-export([start/0,
 
66
         request/3,request/4,cancel_request/1,
 
67
         request_sync/2,request_sync/3]).
 
68
 
 
69
-include("http.hrl").
 
70
-include("jnets_httpd.hrl").
 
71
 
 
72
-define(START_OPTIONS,[]).
 
73
 
 
74
%%% HTTP Client manager. Used to store open connections.
 
75
%%% Will be started automatically unless started explicitly.
 
76
start() ->
 
77
    application:start(ssl),
 
78
    httpc_manager:start().
 
79
 
 
80
%%% Asynchronous HTTP request that spawns a handler.
 
81
%%% Method                          HTTPReq
 
82
%%% options,get,head,delete,trace = {Url,Headers}
 
83
%%% post,put                      = {Url,Headers,ContentType,Body}
 
84
%%%  where Url is a {Scheme,Host,Port,PathQuery} tuple, as returned by uri.erl
 
85
%%% 
 
86
%%% Returns: {ok,ReqId} |
 
87
%%%          {error,Reason}
 
88
%%% If {ok,Pid} was returned, the handler will return with
 
89
%%%    gen_server:cast(From,{Ref,ReqId,{error,Reason}}) |
 
90
%%%    gen_server:cast(From,{Ref,ReqId,{Status,Headers,Body}})
 
91
%%%  where Reason is an atom and Headers a #res_headers{} record
 
92
%%% http:format_error(Reason) gives a more informative description.
 
93
%%% 
 
94
%%% Note:
 
95
%%% - Always try to find an open connection to a given host and port, and use
 
96
%%%   the associated socket.
 
97
%%% - Unless a 'Connection: close' header is provided don't close the socket
 
98
%%%   after a response is given 
 
99
%%% - A given Pid, found in the database, might be terminated before the
 
100
%%%   message is sent to the Pid. This will happen e.g., if the connection is
 
101
%%%   closed by the other party and there are no pending requests.
 
102
%%% - The HTTP connection process is spawned, if necessary, in
 
103
%%%   httpc_manager:add_connection/4
 
104
request(Ref,Method,HTTPReqCont) ->
 
105
    request(Ref,Method,HTTPReqCont,[],self()).
 
106
 
 
107
request(Ref,Method,HTTPReqCont,Settings) ->
 
108
    request(Ref,Method,HTTPReqCont,Settings,self()).
 
109
 
 
110
request(Ref,Method,{{Scheme,Host,Port,PathQuery},
 
111
                    Headers,ContentType,Body},Settings,From) ->
 
112
    case create_settings(Settings,#client_settings{}) of
 
113
        {error,Reason} ->
 
114
            {error,Reason};
 
115
        CS ->
 
116
            case create_headers(Headers,#req_headers{}) of
 
117
                {error,Reason} ->
 
118
                    {error,Reason};
 
119
                H ->
 
120
                    Req=#request{ref=Ref,from=From,
 
121
                                 scheme=Scheme,address={Host,Port},
 
122
                                 pathquery=PathQuery,method=Method,
 
123
                                 headers=H,content={ContentType,Body},
 
124
                                 settings=CS},
 
125
                    httpc_manager:request(Req)
 
126
            end
 
127
    end;
 
128
request(Ref,Method,{Url,Headers},Settings,From) ->
 
129
    request(Ref,Method,{Url,Headers,[],[]},Settings,From).
 
130
 
 
131
%%% Cancels requests identified with ReqId.
 
132
%%% FIXME! Doesn't work... 
 
133
cancel_request(ReqId) ->
 
134
    httpc_manager:cancel_request(ReqId).
 
135
 
 
136
%%% Close all sessions currently open to Host:Port
 
137
%%% FIXME! Doesn't work... 
 
138
close_session(Host,Port) ->
 
139
    httpc_manager:close_session(Host,Port).
 
140
    
 
141
 
 
142
%%% Synchronous HTTP request that waits until a response is created
 
143
%%% (e.g. successfull reply or timeout)
 
144
%%% Method                          HTTPReq
 
145
%%% options,get,head,delete,trace = {Url,Headers}
 
146
%%% post,put                      = {Url,Headers,ContentType,Body}
 
147
%%%  where Url is a string() or a {Scheme,Host,Port,PathQuery} tuple
 
148
%%% 
 
149
%%% Returns: {Status,Headers,Body} |
 
150
%%%          {error,Reason}
 
151
%%% where Reason is an atom. 
 
152
%%% http:format_error(Reason) gives a more informative description.
 
153
request_sync(Method,HTTPReqCont) ->
 
154
    request_sync(Method,HTTPReqCont,[]).
 
155
 
 
156
request_sync(Method,{Url,Headers},Settings)
 
157
  when Method==options;Method==get;Method==head;Method==delete;Method==trace ->
 
158
    case uri:parse(Url) of
 
159
        {error,Reason} ->
 
160
            {error,Reason};
 
161
        ParsedUrl ->
 
162
            request_sync(Method,{ParsedUrl,Headers,[],[]},Settings,0)
 
163
    end;
 
164
request_sync(Method,{Url,Headers,ContentType,Body},Settings)
 
165
  when Method==post;Method==put ->
 
166
    case uri:parse(Url) of
 
167
        {error,Reason} ->
 
168
            {error,Reason};
 
169
        ParsedUrl ->
 
170
            request_sync(Method,{ParsedUrl,Headers,ContentType,Body},Settings,0)
 
171
    end;
 
172
request_sync(Method,Request,Settings) ->
 
173
    {error,bad_request}.
 
174
 
 
175
request_sync(Method,HTTPCont,Settings,_Redirects) ->
 
176
    case request(request_sync,Method,HTTPCont,Settings,self()) of
 
177
        {ok,_ReqId} ->
 
178
            receive
 
179
                {'$gen_cast',{request_sync,_ReqId2,{Status,Headers,Body}}} ->
 
180
                    {Status,pp_headers(Headers),binary_to_list(Body)};
 
181
                {'$gen_cast',{request_sync,_ReqId2,{error,Reason}}} ->
 
182
                    {error,Reason};
 
183
                Error ->
 
184
                    Error
 
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([{Key,_Val}|_Settings],_Out) ->
 
212
    io:format("ERROR bad settings, got ~p~n",[Key]),
 
213
    {error,bad_settings}.
 
214
 
 
215
 
 
216
create_headers([],Req) ->
 
217
    Req;
 
218
create_headers([{Key,Val}|Rest],Req) ->
 
219
    case httpd_util:to_lower(Key) of
 
220
        "expect" ->
 
221
            create_headers(Rest,Req#req_headers{expect=Val});
 
222
        OtherKey ->
 
223
            create_headers(Rest,
 
224
                           Req#req_headers{other=[{OtherKey,Val}|
 
225
                                                  Req#req_headers.other]})
 
226
    end.
 
227
                
 
228
 
 
229
pp_headers(#res_headers{connection=Connection,
 
230
                        transfer_encoding=Transfer_encoding,
 
231
                        retry_after=Retry_after,
 
232
                        content_length=Content_length,
 
233
                        content_type=Content_type,
 
234
                        location=Location,
 
235
                        other=Other}) ->
 
236
    H1=case Connection of
 
237
           undefined -> [];
 
238
           _ ->  [{'Connection',Connection}]
 
239
       end,
 
240
    H2=case Transfer_encoding of
 
241
           undefined -> [];
 
242
           _ ->  [{'Transfer-Encoding',Transfer_encoding}]
 
243
       end,
 
244
    H3=case Retry_after of
 
245
           undefined -> [];
 
246
           _ ->  [{'Retry-After',Retry_after}]
 
247
       end,
 
248
    H4=case Location of
 
249
           undefined -> [];
 
250
           _ ->  [{'Location',Location}]
 
251
       end,
 
252
    HCL=case Content_length of
 
253
           "0" -> [];
 
254
           _ ->  [{'Content-Length',Content_length}]
 
255
       end,
 
256
    HCT=case Content_type of
 
257
           undefined -> [];
 
258
           _ ->  [{'Content-Type',Content_type}]
 
259
       end,
 
260
    H1++H2++H3++H4++HCL++HCT++Other.