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

« back to all changes in this revision

Viewing changes to lib/inets/test/httpc_SUITE.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
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2004-2011. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
 
 
21
%% 
 
22
%% ts:run(inets, httpc_SUITE, [batch]).
 
23
%% 
 
24
 
 
25
-module(httpc_SUITE).
 
26
 
 
27
-include_lib("common_test/include/ct.hrl").
 
28
-include("test_server_line.hrl").
 
29
 
 
30
-include_lib("kernel/include/file.hrl").
 
31
 
 
32
%% Note: This directive should only be used in test suites.
 
33
-compile(export_all).
 
34
 
 
35
%% Test server specific exports
 
36
-define(PROXY_URL, "http://www.erlang.org").
 
37
-define(PROXY, "www-proxy.ericsson.se").
 
38
-define(PROXY_PORT, 8080).
 
39
-define(IP_PORT, 8998).
 
40
-define(SSL_PORT, 8999).
 
41
-define(NOT_IN_USE_PORT, 8997).
 
42
-define(LOCAL_HOST, {127,0,0,1}).
 
43
-define(IPV6_LOCAL_HOST, "0:0:0:0:0:0:0:1").
 
44
-define(URL_START, "http://localhost:").
 
45
-define(SSL_URL_START, "https://localhost:").
 
46
-define(CR, $\r).
 
47
-define(LF, $\n).
 
48
-define(HTTP_MAX_HEADER_SIZE, 10240).
 
49
 
 
50
 
 
51
%%--------------------------------------------------------------------
 
52
%% all(Arg) -> [Doc] | [Case] | {skip, Comment}
 
53
%% Arg - doc | suite
 
54
%% Doc - string()
 
55
%% Case - atom() 
 
56
%%      Name of a test case function. 
 
57
%% Comment - string()
 
58
%% Description: Returns documentation/test cases in this test suite
 
59
%%              or a skip tuple if the platform is not supported.  
 
60
%%--------------------------------------------------------------------
 
61
 
 
62
suite() -> [{ct_hooks,[ts_install_cth]}].
 
63
 
 
64
all() -> 
 
65
    [proxy_options, proxy_head, proxy_get, proxy_trace,
 
66
     proxy_post, proxy_put, proxy_delete, proxy_auth,
 
67
     proxy_headers, proxy_emulate_lower_versions,
 
68
     http_options, http_head, http_get, http_post,
 
69
     http_dummy_pipe, http_inets_pipe, http_trace,
 
70
     http_async, http_save_to_file, http_save_to_file_async,
 
71
     http_headers, http_headers_dummy, http_bad_response,
 
72
     ssl_head, ossl_head, essl_head, ssl_get, ossl_get,
 
73
     essl_get, ssl_trace, ossl_trace, essl_trace,
 
74
     http_redirect, http_redirect_loop,
 
75
     http_internal_server_error, http_userinfo, http_cookie,
 
76
     http_server_does_not_exist, http_invalid_http,
 
77
     http_emulate_lower_versions, http_relaxed,
 
78
     page_does_not_exist, proxy_page_does_not_exist,
 
79
     proxy_https_not_supported, http_stream,
 
80
     http_stream_once, proxy_stream, parse_url, options,
 
81
     ipv6, headers_as_is, {group, tickets}].
 
82
 
 
83
groups() -> 
 
84
    [{tickets, [],
 
85
      [hexed_query_otp_6191, empty_body_otp_6243,
 
86
       empty_response_header_otp_6830,
 
87
       transfer_encoding_otp_6807, proxy_not_modified_otp_6821,
 
88
       no_content_204_otp_6982, missing_CR_otp_7304,
 
89
       {group, otp_7883}, {group, otp_8154}, {group, otp_8106},
 
90
       otp_8056, otp_8352, otp_8371, otp_8739]},
 
91
     {otp_7883, [], [otp_7883_1, otp_7883_2]},
 
92
     {otp_8154, [], [otp_8154_1]},
 
93
     {otp_8106, [],
 
94
      [otp_8106_pid, otp_8106_fun, otp_8106_mfa]}].
 
95
 
 
96
init_per_group(_GroupName, Config) ->
 
97
    Config.
 
98
 
 
99
end_per_group(_GroupName, Config) ->
 
100
    Config.
 
101
 
 
102
 
 
103
%%--------------------------------------------------------------------
 
104
%% Function: init_per_suite(Config) -> Config
 
105
%% Config - [tuple()]
 
106
%%   A list of key/value pairs, holding the test case configuration.
 
107
%% Description: Initiation before the whole suite
 
108
%%
 
109
%% Note: This function is free to add any key/value pairs to the Config
 
110
%% variable, but should NOT alter/remove any existing entries.
 
111
%%--------------------------------------------------------------------
 
112
init_per_suite(Config) ->
 
113
    PrivDir = ?config(priv_dir, Config),
 
114
    DataDir = ?config(data_dir, Config),
 
115
    ServerRoot = filename:join(PrivDir, "server_root"),
 
116
    DocRoot = filename:join(ServerRoot, "htdocs"),
 
117
    IpConfFile = integer_to_list(?IP_PORT) ++ ".conf",
 
118
    SslConfFile = integer_to_list(?SSL_PORT) ++ ".conf",
 
119
    
 
120
    setup_server_dirs(ServerRoot, DocRoot, DataDir),
 
121
    create_config(IpConfFile, ip_comm, ?IP_PORT, PrivDir, ServerRoot, 
 
122
                  DocRoot, DataDir),
 
123
    create_config(SslConfFile, ssl, ?SSL_PORT, PrivDir, ServerRoot, 
 
124
                  DocRoot, DataDir),
 
125
 
 
126
    Cgi = case test_server:os_type() of
 
127
              {win32, _} ->
 
128
                  filename:join([ServerRoot, "cgi-bin", "cgi_echo.exe"]);
 
129
              _ ->
 
130
                  filename:join([ServerRoot, "cgi-bin", "cgi_echo"])
 
131
          end,
 
132
    
 
133
    {ok, FileInfo} = file:read_file_info(Cgi),
 
134
    ok = file:write_file_info(Cgi, FileInfo#file_info{mode = 8#00755}),
 
135
 
 
136
    [{server_root,    ServerRoot}, 
 
137
     {doc_root,       DocRoot},
 
138
     {local_port,     ?IP_PORT}, 
 
139
     {local_ssl_port, ?SSL_PORT} | Config].
 
140
 
 
141
%%--------------------------------------------------------------------
 
142
%% Function: end_per_suite(Config) -> _
 
143
%% Config - [tuple()]
 
144
%%   A list of key/value pairs, holding the test case configuration.
 
145
%% Description: Cleanup after the whole suite
 
146
%%--------------------------------------------------------------------
 
147
end_per_suite(Config) ->
 
148
    PrivDir = ?config(priv_dir, Config),        
 
149
    inets_test_lib:del_dirs(PrivDir),
 
150
    application:stop(inets),
 
151
    application:stop(ssl),
 
152
    ok.
 
153
 
 
154
%%--------------------------------------------------------------------
 
155
%% Function: init_per_testcase(Case, Config) -> Config
 
156
%% Case - atom()
 
157
%%   Name of the test case that is about to be run.
 
158
%% Config - [tuple()]
 
159
%%   A list of key/value pairs, holding the test case configuration.
 
160
%%
 
161
%% Description: Initiation before each test case
 
162
%%
 
163
%% Note: This function is free to add any key/value pairs to the Config
 
164
%% variable, but should NOT alter/remove any existing entries.
 
165
%%--------------------------------------------------------------------
 
166
init_per_testcase(otp_8154_1 = Case, Config) ->
 
167
    init_per_testcase(Case, 5, Config);
 
168
init_per_testcase(Case, Config) ->
 
169
    init_per_testcase(Case, 2, Config).
 
170
 
 
171
init_per_testcase_ssl(Tag, PrivDir, SslConfFile, Config) ->
 
172
    tsp("init_per_testcase_ssl -> stop ssl"),
 
173
    application:stop(ssl),
 
174
    Config2 = lists:keydelete(local_ssl_server, 1, Config),
 
175
    %% Will start inets 
 
176
    tsp("init_per_testcase_ssl -> try start http server (including inets)"),
 
177
    Server = inets_test_lib:start_http_server(
 
178
               filename:join(PrivDir, SslConfFile), Tag),
 
179
    tsp("init_per_testcase -> Server: ~p", [Server]),
 
180
    [{local_ssl_server, Server} | Config2].
 
181
 
 
182
init_per_testcase(Case, Timeout, Config) ->
 
183
    io:format(user, "~n~n*** INIT ~w:[~w][~w] ***~n~n", 
 
184
              [?MODULE, Timeout, Case]),
 
185
    PrivDir     = ?config(priv_dir, Config),
 
186
    tsp("init_per_testcase -> stop inets"),
 
187
    application:stop(inets),
 
188
    Dog         = test_server:timetrap(inets_test_lib:minutes(Timeout)),
 
189
    TmpConfig   = lists:keydelete(watchdog, 1, Config),
 
190
    IpConfFile  = integer_to_list(?IP_PORT) ++ ".conf",
 
191
    SslConfFile = integer_to_list(?SSL_PORT) ++ ".conf",
 
192
 
 
193
    %% inets:enable_trace(max, io, httpd),
 
194
    %% inets:enable_trace(max, io, httpc),
 
195
    inets:enable_trace(max, io, all),
 
196
 
 
197
    NewConfig = 
 
198
        case atom_to_list(Case) of
 
199
            [$s, $s, $l | _] ->
 
200
                init_per_testcase_ssl(ssl, PrivDir, SslConfFile, [{watchdog, Dog} | TmpConfig]);
 
201
 
 
202
            [$o, $s, $s, $l | _] ->
 
203
                init_per_testcase_ssl(ossl, PrivDir, SslConfFile, [{watchdog, Dog} | TmpConfig]);
 
204
 
 
205
            [$e, $s, $s, $l | _] ->
 
206
                init_per_testcase_ssl(essl, PrivDir, SslConfFile, [{watchdog, Dog} | TmpConfig]);
 
207
 
 
208
            "proxy" ++ Rest ->
 
209
                case Rest of                           
 
210
                    "_https_not_supported" ->   
 
211
                        tsp("init_per_testcase -> [proxy case] start inets"),
 
212
                        inets:start(),
 
213
                        tsp("init_per_testcase -> [proxy case] start ssl"),
 
214
                        application:start(crypto),
 
215
                        application:start(public_key),
 
216
                        case (catch application:start(ssl)) of
 
217
                            ok ->
 
218
                                [{watchdog, Dog} | TmpConfig];
 
219
                            _ ->
 
220
                                [{skip, "SSL does not seem to be supported"} 
 
221
                                 | TmpConfig]
 
222
                        end;
 
223
                    _ ->
 
224
                        case is_proxy_available(?PROXY, ?PROXY_PORT) of
 
225
                            true ->
 
226
                                inets:start(),
 
227
                                [{watchdog, Dog} | TmpConfig];
 
228
                            false ->
 
229
                                [{skip, "Failed to contact proxy"} | 
 
230
                                 TmpConfig]
 
231
                        end
 
232
                end;
 
233
            _ -> 
 
234
                TmpConfig2 = lists:keydelete(local_server, 1, TmpConfig),
 
235
                Server = 
 
236
                    %% Will start inets 
 
237
                    inets_test_lib:start_http_server(
 
238
                      filename:join(PrivDir, IpConfFile)),
 
239
                [{watchdog, Dog}, {local_server, Server} | TmpConfig2]
 
240
        end,
 
241
    
 
242
    %% httpc:set_options([{proxy, {{?PROXY, ?PROXY_PORT}, 
 
243
    %%                          ["localhost", ?IPV6_LOCAL_HOST]}}]),
 
244
 
 
245
    httpc:set_options([{proxy, {{?PROXY, ?PROXY_PORT}, 
 
246
                                ["localhost", ?IPV6_LOCAL_HOST]}},
 
247
                       {ipfamily, inet6fb4}]),
 
248
 
 
249
    %% snmp:set_trace([gen_tcp]),
 
250
    NewConfig.
 
251
 
 
252
 
 
253
%%--------------------------------------------------------------------
 
254
%% Function: end_per_testcase(Case, Config) -> _
 
255
%% Case - atom()
 
256
%%   Name of the test case that is about to be run.
 
257
%% Config - [tuple()]
 
258
%%   A list of key/value pairs, holding the test case configuration.
 
259
%% Description: Cleanup after each test case
 
260
%%--------------------------------------------------------------------
 
261
end_per_testcase(http_save_to_file, Config) ->
 
262
    PrivDir = ?config(priv_dir, Config),        
 
263
    FullPath = filename:join(PrivDir, "dummy.html"),
 
264
    file:delete(FullPath),
 
265
    finish(Config);
 
266
        
 
267
end_per_testcase(_, Config) ->
 
268
    finish(Config).
 
269
 
 
270
finish(Config) ->
 
271
    Dog = ?config(watchdog, Config),
 
272
    case Dog of 
 
273
        undefined ->
 
274
            ok;
 
275
        _ ->
 
276
            test_server:timetrap_cancel(Dog)
 
277
    end.
 
278
 
 
279
%%-------------------------------------------------------------------------
 
280
%% Test cases starts here.
 
281
%%-------------------------------------------------------------------------
 
282
 
 
283
 
 
284
 
 
285
%%-------------------------------------------------------------------------
 
286
 
 
287
http_options(doc) ->
 
288
    ["Test http options request against local server."];
 
289
http_options(suite) ->
 
290
    [];
 
291
http_options(Config) when is_list(Config) ->
 
292
    {skip, "Not supported by httpd"}.
 
293
 
 
294
http_head(doc) ->
 
295
    ["Test http head request against local server."];
 
296
http_head(suite) ->
 
297
    [];
 
298
http_head(Config) when is_list(Config) ->
 
299
    case ?config(local_server, Config) of 
 
300
        ok ->
 
301
            Port = ?config(local_port, Config),
 
302
            URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
303
            case httpc:request(head, {URL, []}, [], []) of
 
304
                {ok, {{_,200,_}, [_ | _], []}} ->
 
305
                    ok;
 
306
                {ok, WrongReply} ->
 
307
                    tsf({wrong_reply, WrongReply});
 
308
                Error ->
 
309
                    tsf({failed, Error})
 
310
            end;
 
311
          _ ->
 
312
              {skip, "Failed to start local http-server"}
 
313
      end.  
 
314
%%-------------------------------------------------------------------------
 
315
http_get(doc) ->
 
316
    ["Test http get request against local server"];
 
317
http_get(suite) ->
 
318
    [];
 
319
http_get(Config) when is_list(Config) ->
 
320
    tsp("http_get -> entry with"
 
321
        "~n   Config: ~p", [Config]),
 
322
    case ?config(local_server, Config) of 
 
323
        ok ->
 
324
            tsp("local-server running"),
 
325
            Method       = get, 
 
326
            Port         = ?config(local_port, Config),
 
327
            URL          = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
328
            Request      = {URL, []}, 
 
329
            Timeout      = timer:seconds(1), 
 
330
            ConnTimeout  = Timeout + timer:seconds(1), 
 
331
            HttpOptions1 = [{timeout, Timeout}, {connect_timeout, ConnTimeout}], 
 
332
            Options1     = [], 
 
333
            Body = 
 
334
                case httpc:request(Method, Request, HttpOptions1, Options1) of
 
335
                    {ok, {{_,200,_}, [_ | _], ReplyBody = [_ | _]}} ->
 
336
                        ReplyBody;
 
337
                    {ok, UnexpectedReply1} ->
 
338
                        tsf({unexpected_reply, UnexpectedReply1});
 
339
                    {error, _} = Error1 ->
 
340
                        tsf({bad_reply, Error1})
 
341
                end,
 
342
 
 
343
            %% eqvivivalent to httpc:request(get, {URL, []}, [], []),
 
344
            inets_test_lib:check_body(Body),
 
345
 
 
346
            HttpOptions2 = [], 
 
347
            Options2     = [{body_format, binary}], 
 
348
            case httpc:request(Method, Request, HttpOptions2, Options2) of
 
349
                {ok, {{_,200,_}, [_ | _], Bin}} when is_binary(Bin) ->
 
350
                    ok;
 
351
                {ok, {{_,200,_}, [_ | _], BadBin}} ->
 
352
                    tsf({body_format_not_binary, BadBin});
 
353
                {ok,  UnexpectedReply2} ->
 
354
                    tsf({unexpected_reply, UnexpectedReply2});
 
355
                {error, _} = Error2 ->
 
356
                    tsf({bad_reply, Error2})
 
357
            end;
 
358
        _ ->
 
359
            {skip, "Failed to start local http-server"}
 
360
    end.  
 
361
 
 
362
%%-------------------------------------------------------------------------
 
363
http_post(doc) ->
 
364
    ["Test http post request against local server. We do in this case"
 
365
    " only care about the client side of the the post. The server"
 
366
    " script will not actually use the post data."];
 
367
http_post(suite) ->
 
368
    [];
 
369
http_post(Config) when is_list(Config) ->
 
370
  case ?config(local_server, Config) of 
 
371
      ok -> 
 
372
          Port = ?config(local_port, Config),
 
373
          
 
374
          URL = case test_server:os_type() of
 
375
                    {win32, _} ->
 
376
                        ?URL_START ++ integer_to_list(Port) ++ 
 
377
                            "/cgi-bin/cgi_echo.exe";
 
378
                    _ ->
 
379
                        ?URL_START ++ integer_to_list(Port) ++ 
 
380
                            "/cgi-bin/cgi_echo"        
 
381
                
 
382
                end,
 
383
          %% Cgi-script expects the body length to be 100 
 
384
          Body = lists:duplicate(100, "1"),
 
385
          
 
386
          {ok, {{_,200,_}, [_ | _], [_ | _]}} =
 
387
              httpc:request(post, {URL, [{"expect","100-continue"}],
 
388
                                  "text/plain", Body}, [], []),
 
389
      
 
390
          {ok, {{_,504,_}, [_ | _], []}} =
 
391
              httpc:request(post, {URL, [{"expect","100-continue"}],
 
392
                                  "text/plain", "foobar"}, [], []);
 
393
      _ ->
 
394
          {skip, "Failed to start local http-server"}
 
395
  end.  
 
396
 
 
397
%%-------------------------------------------------------------------------
 
398
http_emulate_lower_versions(doc) ->
 
399
    ["Perform request as 0.9 and 1.0 clients."];
 
400
http_emulate_lower_versions(suite) ->
 
401
    [];
 
402
http_emulate_lower_versions(Config) when is_list(Config) ->
 
403
    case ?config(local_server, Config) of 
 
404
        ok ->
 
405
            Port = ?config(local_port, Config),
 
406
            URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
407
            {ok, Body0} =
 
408
                httpc:request(get, {URL, []}, [{version, "HTTP/0.9"}], []),
 
409
            inets_test_lib:check_body(Body0),
 
410
            {ok, {{"HTTP/1.0", 200, _}, [_ | _], Body1 = [_ | _]}} =
 
411
                httpc:request(get, {URL, []}, [{version, "HTTP/1.0"}], []),
 
412
            inets_test_lib:check_body(Body1),
 
413
            {ok, {{"HTTP/1.1", 200, _}, [_ | _], Body2 = [_ | _]}} =
 
414
                httpc:request(get, {URL, []}, [{version, "HTTP/1.1"}], []),
 
415
            inets_test_lib:check_body(Body2);
 
416
        _->
 
417
            {skip, "Failed to start local http-server"}
 
418
    end.
 
419
 
 
420
 
 
421
%%-------------------------------------------------------------------------
 
422
 
 
423
http_relaxed(doc) ->
 
424
    ["Test relaxed mode"];
 
425
http_relaxed(suite) ->
 
426
    [];
 
427
http_relaxed(Config) when is_list(Config) ->
 
428
    ok = httpc:set_options([{ipv6, disabled}]), % also test the old option 
 
429
    %% ok = httpc:set_options([{ipfamily, inet}]),
 
430
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
431
    
 
432
    URL = ?URL_START ++ integer_to_list(Port) ++ 
 
433
        "/missing_reason_phrase.html",
 
434
        
 
435
    {error, Reason} =
 
436
        httpc:request(get, {URL, []}, [{relaxed, false}], []),
 
437
 
 
438
    test_server:format("Not relaxed: ~p~n", [Reason]),
 
439
    
 
440
    {ok, {{_, 200, _}, [_ | _], [_ | _]}} =
 
441
        httpc:request(get, {URL, []}, [{relaxed, true}], []),
 
442
 
 
443
    DummyServerPid ! stop,
 
444
    ok = httpc:set_options([{ipv6, enabled}]),   
 
445
    %% ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
446
    ok.
 
447
 
 
448
 
 
449
%%-------------------------------------------------------------------------
 
450
http_dummy_pipe(doc) ->
 
451
    ["Test pipelining code."];
 
452
http_dummy_pipe(suite) ->
 
453
    [];
 
454
http_dummy_pipe(Config) when is_list(Config) ->
 
455
    ok = httpc:set_options([{ipfamily, inet}]),
 
456
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
457
    
 
458
    URL = ?URL_START ++ integer_to_list(Port) ++ "/foobar.html",
 
459
 
 
460
    test_pipeline(URL),
 
461
 
 
462
    DummyServerPid ! stop,
 
463
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
464
    ok.
 
465
 
 
466
http_inets_pipe(doc) ->
 
467
    ["Test pipelining code."];
 
468
http_inets_pipe(suite) ->
 
469
    [];
 
470
http_inets_pipe(Config) when is_list(Config) ->
 
471
    
 
472
    case ?config(local_server, Config) of 
 
473
        ok ->
 
474
            Port = ?config(local_port, Config),
 
475
            URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
476
            test_pipeline(URL); 
 
477
        _ ->
 
478
            {skip, "Failed to start local http-server"}
 
479
    end.
 
480
 
 
481
test_pipeline(URL) ->
 
482
    p("test_pipeline -> entry with"
 
483
      "~n   URL: ~p", [URL]),
 
484
 
 
485
    httpc:set_options([{pipeline_timeout, 50000}]),
 
486
    
 
487
    p("test_pipeline -> issue (async) request 1"), 
 
488
    {ok, RequestId1} = 
 
489
        httpc:request(get, {URL, []}, [], [{sync, false}]),
 
490
    test_server:format("RequestId1: ~p~n", [RequestId1]),
 
491
    p("test_pipeline -> RequestId1: ~p", [RequestId1]),
 
492
 
 
493
    %% Make sure pipeline is initiated
 
494
    p("test_pipeline -> sleep some", []),
 
495
    test_server:sleep(4000),
 
496
 
 
497
    p("test_pipeline -> issue (async) request 2"),
 
498
    {ok, RequestId2} = 
 
499
        httpc:request(get, {URL, []}, [], [{sync, false}]),
 
500
    tsp("RequestId2: ~p", [RequestId2]),
 
501
    p("test_pipeline -> RequestId2: ~p", [RequestId2]),
 
502
 
 
503
    p("test_pipeline -> issue (sync) request 3"),
 
504
    {ok, {{_,200,_}, [_ | _], [_ | _]}} = 
 
505
        httpc:request(get, {URL, []}, [], []),
 
506
 
 
507
    p("test_pipeline -> expect reply for (async) request 1 or 2"),
 
508
    receive 
 
509
        {http, {RequestId1, {{_, 200, _}, _, _}}} ->
 
510
            p("test_pipeline -> received reply for (async) request 1 - now wait for 2"),
 
511
            receive
 
512
                {http, {RequestId2, {{_, 200, _}, _, _}}} ->
 
513
                    p("test_pipeline -> received reply for (async) request 2"),
 
514
                    ok;
 
515
                {http, Msg1} ->
 
516
                    test_server:fail(Msg1)
 
517
            end;
 
518
        {http, {RequestId2, {{_, 200, _}, _, _}}} ->
 
519
            io:format("test_pipeline -> received reply for (async) request 2 - now wait for 1"),
 
520
            receive
 
521
                {http, {RequestId1, {{_, 200, _}, _, _}}} ->
 
522
                    io:format("test_pipeline -> received reply for (async) request 1"),
 
523
                    ok;
 
524
                {http, Msg2} ->
 
525
                    test_server:fail(Msg2)
 
526
                    end; 
 
527
        {http, Msg3} ->
 
528
            test_server:fail(Msg3)
 
529
        after 60000 ->
 
530
                receive Any1 ->
 
531
                        tsp("received crap after timeout: ~n   ~p", [Any1]),
 
532
                        test_server:fail({error, {timeout, Any1}})
 
533
                end
 
534
    end,
 
535
    
 
536
    p("test_pipeline -> sleep some"),
 
537
    test_server:sleep(4000),
 
538
 
 
539
    p("test_pipeline -> issue (async) request 4"),
 
540
    {ok, RequestId3} = 
 
541
        httpc:request(get, {URL, []}, [], [{sync, false}]),
 
542
    tsp("RequestId3: ~p", [RequestId3]),
 
543
    p("test_pipeline -> RequestId3: ~p", [RequestId3]),
 
544
 
 
545
    p("test_pipeline -> issue (async) request 5"),
 
546
    {ok, RequestId4} = 
 
547
        httpc:request(get, {URL, []}, [], [{sync, false}]),
 
548
    tsp("RequestId4: ~p~n", [RequestId4]),
 
549
    p("test_pipeline -> RequestId4: ~p", [RequestId4]),
 
550
 
 
551
    p("test_pipeline -> cancel (async) request 4"),
 
552
    ok = httpc:cancel_request(RequestId3),
 
553
 
 
554
    p("test_pipeline -> expect *no* reply for cancelled (async) request 4 (for 3 secs)"),
 
555
    receive 
 
556
        {http, {RequestId3, _}} ->
 
557
            test_server:fail(http_cancel_request_failed)
 
558
    after 3000 ->
 
559
            ok
 
560
    end,
 
561
 
 
562
    p("test_pipeline -> expect reply for (async) request 4"),
 
563
    Body = 
 
564
        receive 
 
565
           {http, {RequestId4, {{_, 200, _}, _, BinBody4}}} = Res ->
 
566
                p("test_pipeline -> received reply for (async) request 5"),
 
567
                tsp("Receive : ~p", [Res]),
 
568
                BinBody4;
 
569
            {http, Msg4} ->
 
570
                test_server:fail(Msg4)
 
571
        after 60000 ->
 
572
                receive Any2 ->
 
573
                        tsp("received crap after timeout: ~n   ~p", [Any2]),
 
574
                        test_server:fail({error, {timeout, Any2}})
 
575
                end
 
576
        end,
 
577
 
 
578
    p("test_pipeline -> check reply for (async) request 5"),
 
579
    inets_test_lib:check_body(binary_to_list(Body)),
 
580
   
 
581
    p("test_pipeline -> ensure no unexpected incomming"),
 
582
    receive 
 
583
        {http, Any} ->
 
584
            test_server:fail({unexpected_message, Any})
 
585
    after 500 ->
 
586
            ok
 
587
    end,
 
588
 
 
589
    p("test_pipeline -> done"),
 
590
    ok.
 
591
 
 
592
 
 
593
 
 
594
%%-------------------------------------------------------------------------
 
595
http_trace(doc) ->
 
596
    ["Perform a TRACE request that goes through a proxy."];
 
597
http_trace(suite) ->
 
598
    [];
 
599
http_trace(Config) when is_list(Config) ->
 
600
    case ?config(local_server, Config) of 
 
601
        ok ->
 
602
            Port = ?config(local_port, Config),
 
603
            URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
604
            case httpc:request(trace, {URL, []}, [], []) of
 
605
                {ok, {{_,200,_}, [_ | _], "TRACE /dummy.html" ++ _}} ->
 
606
                    ok;
 
607
                {ok, {{_,200,_}, [_ | _], WrongBody}} ->
 
608
                    test_server:fail({wrong_body, WrongBody});
 
609
                {ok, WrongReply} ->
 
610
                    test_server:fail({wrong_reply, WrongReply});
 
611
                Error ->
 
612
                    test_server:fail({failed, Error})
 
613
            end;
 
614
        _ ->
 
615
            {skip, "Failed to start local http-server"}
 
616
    end.  
 
617
%%-------------------------------------------------------------------------
 
618
http_async(doc) ->
 
619
    ["Test an asynchrony http request."];
 
620
http_async(suite) ->
 
621
    [];
 
622
http_async(Config) when is_list(Config) ->
 
623
    case ?config(local_server, Config) of 
 
624
        ok ->
 
625
            Port = ?config(local_port, Config),
 
626
            URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
627
            {ok, RequestId} = 
 
628
                httpc:request(get, {URL, []}, [], [{sync, false}]),
 
629
            
 
630
            Body = 
 
631
                receive 
 
632
                    {http, {RequestId, {{_, 200, _}, _, BinBody}}} ->
 
633
                        BinBody;
 
634
                    {http, Msg} ->
 
635
                        test_server:fail(Msg)
 
636
                end,
 
637
            
 
638
            inets_test_lib:check_body(binary_to_list(Body)),
 
639
            
 
640
            {ok, NewRequestId} = 
 
641
                httpc:request(get, {URL, []}, [], [{sync, false}]),
 
642
            ok = httpc:cancel_request(NewRequestId),
 
643
            receive 
 
644
                {http, {NewRequestId, _NewResult}} ->
 
645
                    test_server:fail(http_cancel_request_failed)
 
646
            after 3000 ->
 
647
                    ok
 
648
            end;
 
649
        _ ->
 
650
            {skip, "Failed to start local http-server"}
 
651
    end.  
 
652
 
 
653
%%-------------------------------------------------------------------------
 
654
http_save_to_file(doc) ->
 
655
    ["Test to save the http body to a file"];
 
656
http_save_to_file(suite) ->
 
657
    [];
 
658
http_save_to_file(Config) when is_list(Config) ->
 
659
    case ?config(local_server, Config) of 
 
660
        ok ->
 
661
            PrivDir = ?config(priv_dir, Config),
 
662
            FilePath = filename:join(PrivDir, "dummy.html"),
 
663
            Port = ?config(local_port, Config),
 
664
            URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
665
            {ok, saved_to_file} 
 
666
                = httpc:request(get, {URL, []}, [], [{stream, FilePath}]),
 
667
            {ok, Bin} = file:read_file(FilePath), 
 
668
            {ok, {{_,200,_}, [_ | _], Body}} = httpc:request(URL),
 
669
            Bin == Body;
 
670
        _ ->
 
671
            {skip, "Failed to start local http-server"}
 
672
    end.  
 
673
 
 
674
 
 
675
%%-------------------------------------------------------------------------
 
676
http_save_to_file_async(doc) ->
 
677
    ["Test to save the http body to a file"];
 
678
http_save_to_file_async(suite) ->
 
679
    [];
 
680
http_save_to_file_async(Config) when is_list(Config) ->
 
681
    case ?config(local_server, Config) of 
 
682
        ok ->
 
683
            PrivDir = ?config(priv_dir, Config),
 
684
            FilePath = filename:join(PrivDir, "dummy.html"),
 
685
            Port = ?config(local_port, Config),
 
686
            URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
687
            {ok, RequestId} = httpc:request(get, {URL, []}, [], 
 
688
                                           [{stream, FilePath}, 
 
689
                                            {sync, false}]),
 
690
            receive
 
691
                {http, {RequestId, saved_to_file}} ->
 
692
                    ok;
 
693
                {http, Msg} ->
 
694
                    test_server:fail(Msg)
 
695
            end,
 
696
 
 
697
            {ok, Bin} = file:read_file(FilePath), 
 
698
            {ok, {{_,200,_}, [_ | _], Body}} = httpc:request(URL),
 
699
            Bin == Body;
 
700
        _ ->
 
701
            {skip, "Failed to start local http-server"}
 
702
    end.  
 
703
%%-------------------------------------------------------------------------
 
704
http_headers(doc) ->
 
705
    ["Use as many request headers as possible not used in proxy_headers"];
 
706
http_headers(suite) ->
 
707
    [];
 
708
http_headers(Config) when is_list(Config) ->
 
709
    
 
710
    case ?config(local_server, Config) of 
 
711
        ok ->
 
712
            Port = ?config(local_port, Config),
 
713
            URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
714
            DocRoot = ?config(doc_root, Config),
 
715
            {ok, FileInfo} = 
 
716
                file:read_file_info(filename:join([DocRoot,"dummy.html"])),
 
717
            CreatedSec = 
 
718
                calendar:datetime_to_gregorian_seconds(
 
719
                  FileInfo#file_info.mtime),
 
720
            
 
721
            Mod = httpd_util:rfc1123_date(
 
722
                    calendar:gregorian_seconds_to_datetime(
 
723
                      CreatedSec-1)),
 
724
            
 
725
            Date = httpd_util:rfc1123_date({date(), time()}),
 
726
            
 
727
            {ok, {{_,200,_}, [_ | _], [_ | _]}} =
 
728
                httpc:request(get, {URL, [{"If-Modified-Since",
 
729
                                          Mod}, 
 
730
                                         {"From","webmaster@erlang.se"},
 
731
                                         {"Date", Date}
 
732
                                        ]}, [], []),
 
733
            
 
734
            Mod1 =  httpd_util:rfc1123_date(
 
735
                      calendar:gregorian_seconds_to_datetime(
 
736
                        CreatedSec+1)),
 
737
            
 
738
            {ok, {{_,200,_}, [_ | _], [_ | _]}} =
 
739
                httpc:request(get, {URL, [{"If-UnModified-Since",
 
740
                                          Mod1}
 
741
                                        ]}, [], []),
 
742
            
 
743
            Tag = httpd_util:create_etag(FileInfo),
 
744
            
 
745
            
 
746
            {ok, {{_,200,_}, [_ | _], [_ | _]}} =
 
747
                httpc:request(get, {URL, [{"If-Match",
 
748
                                          Tag}
 
749
                                        ]}, [], []),
 
750
 
 
751
            {ok, {{_,200,_}, [_ | _], _}} =
 
752
                     httpc:request(get, {URL, [{"If-None-Match",
 
753
                                               "NotEtag,NeihterEtag"},
 
754
                                              {"Connection", "Close"}
 
755
                                             ]}, [], []),
 
756
            ok;
 
757
                     _ ->
 
758
            {skip, "Failed to start local http-server"}
 
759
    end.
 
760
 
 
761
%%-------------------------------------------------------------------------
 
762
http_headers_dummy(doc) ->
 
763
    ["Test the code for handling headers we do not want/can send "
 
764
     "to a real server. Note it is not logical to send"
 
765
     "all of these headers together, we only want to test that" 
 
766
     "the code for handling headers will not crash."];
 
767
http_headers_dummy(suite) ->
 
768
    [];
 
769
http_headers_dummy(Config) when is_list(Config) -> 
 
770
    ok = httpc:set_options([{ipfamily, inet}]),
 
771
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
772
    
 
773
    URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy_headers.html",
 
774
    
 
775
    Foo = http_chunk:encode("foobar") ++ 
 
776
        binary_to_list(http_chunk:encode_last()),
 
777
    FooBar =  Foo ++ "\r\n\r\nOther:inets_test\r\n\r\n",
 
778
 
 
779
    UserPasswd = base64:encode_to_string("Alladin:Sesame"),
 
780
    Auth = "Basic " ++ UserPasswd,
 
781
 
 
782
    %% The dummy server will ignore the headers, we only want to test
 
783
    %% that the client header-handling code. This would not
 
784
    %% be a vaild http-request!
 
785
    {ok, {{_,200,_}, [_ | _], [_|_]}} = 
 
786
        httpc:request(post, 
 
787
                     {URL, 
 
788
                      [{"Via",
 
789
                        "1.0 fred, 1.1 nowhere.com (Apache/1.1)"}, 
 
790
                       {"Warning","1#pseudonym foobar"},
 
791
                       {"Vary","*"},
 
792
                       {"Upgrade","HTTP/2.0"},
 
793
                       {"Pragma", "1#no-cache"},
 
794
                       {"Cache-Control", "no-cache"},
 
795
                       {"Connection", "close"},
 
796
                       {"Date", "Sat, 29 Oct 1994 19:43:31 GMT"},
 
797
                       {"Accept", " text/plain; q=0.5, text/html"},
 
798
                       {"Accept-Language", "en"},
 
799
                       {"Accept-Encoding","chunked"},
 
800
                       {"Accept-Charset", "ISO8859-1"},
 
801
                       {"Authorization", Auth},
 
802
                       {"Expect", "1#100-continue"},
 
803
                       {"User-Agent","inets"},
 
804
                       {"Transfer-Encoding","chunked"},
 
805
                       {"Range", " bytes=0-499"},
 
806
                       {"If-Range", "Sat, 29 Oct 1994 19:43:31 GMT"},
 
807
                       {"If-Match", "*"},
 
808
                       {"Content-Type", "text/plain"},
 
809
                       {"Content-Encoding", "chunked"},
 
810
                       {"Content-Length", "6"},
 
811
                       {"Content-Language", "en"},
 
812
                       {"Content-Location", "http://www.foobar.se"},
 
813
                       {"Content-MD5", 
 
814
                        "104528739076276072743283077410617235478"},
 
815
                       {"Content-Range", "bytes 0-499/1234"},
 
816
                       {"Allow", "GET"},
 
817
                       {"Proxy-Authorization", Auth},
 
818
                       {"Expires", "Sat, 29 Oct 1994 19:43:31 GMT"},
 
819
                       {"Upgrade", "HTTP/2.0"},
 
820
                       {"Last-Modified", "Sat, 29 Oct 1994 19:43:31 GMT"},
 
821
                       {"Trailer","1#User-Agent"}
 
822
                      ], "text/plain", FooBar}, 
 
823
                     [], []),
 
824
    DummyServerPid ! stop,
 
825
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
826
    ok.
 
827
    
 
828
 
 
829
%%-------------------------------------------------------------------------
 
830
http_bad_response(doc) ->
 
831
    ["Test what happens when the server does not follow the protocol"];
 
832
http_bad_response(suite) ->
 
833
    [];
 
834
http_bad_response(Config) when is_list(Config) ->
 
835
    ok = httpc:set_options([{ipfamily, inet}]),
 
836
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
837
    
 
838
    URL = ?URL_START ++ integer_to_list(Port) ++ "/missing_crlf.html",
 
839
    
 
840
    URL1 = ?URL_START ++ integer_to_list(Port) ++ "/wrong_statusline.html",
 
841
    
 
842
    {error, timeout} = httpc:request(get, {URL, []}, [{timeout, 400}], []),
 
843
      
 
844
    {error, Reason} = httpc:request(URL1),
 
845
    
 
846
    test_server:format("Wrong Statusline: ~p~n", [Reason]),
 
847
 
 
848
    DummyServerPid ! stop,
 
849
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
850
    ok.
 
851
 
 
852
 
 
853
%%-------------------------------------------------------------------------
 
854
ssl_head(doc) ->
 
855
    ["Same as http_head/1 but over ssl sockets."];
 
856
ssl_head(suite) ->
 
857
    [];
 
858
ssl_head(Config) when is_list(Config) ->   
 
859
    ssl_head(ssl, Config).
 
860
 
 
861
ossl_head(doc) ->
 
862
    ["Same as http_head/1 but over ssl sockets."];
 
863
ossl_head(suite) ->
 
864
    [];
 
865
ossl_head(Config) when is_list(Config) ->   
 
866
    ssl_head(ossl, Config).
 
867
 
 
868
essl_head(doc) ->
 
869
    ["Same as http_head/1 but over ssl sockets."];
 
870
essl_head(suite) ->
 
871
    [];
 
872
essl_head(Config) when is_list(Config) ->   
 
873
    ssl_head(essl, Config).
 
874
 
 
875
ssl_head(SslTag, Config) ->
 
876
    tsp("ssl_head -> entry with"
 
877
        "~n   SslTag: ~p"
 
878
        "~n   Config: ~p", [SslTag, Config]), 
 
879
    case ?config(local_ssl_server, Config) of 
 
880
        ok ->
 
881
            DataDir    = ?config(data_dir, Config),
 
882
            Port       = ?config(local_ssl_port, Config),
 
883
            URL        = ?SSL_URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
884
            CertFile   = filename:join(DataDir, "ssl_client_cert.pem"),
 
885
            SSLOptions = [{certfile, CertFile}, {keyfile, CertFile}],
 
886
            SSLConfig     = 
 
887
                case SslTag of
 
888
                    ssl ->
 
889
                        SSLOptions;
 
890
                    ossl ->
 
891
                        {ossl, SSLOptions};
 
892
                    essl ->
 
893
                        {essl, SSLOptions}
 
894
                end,
 
895
            tsp("ssl_head -> make request using: "
 
896
                "~n   URL:        ~p"
 
897
                "~n   SslTag:     ~p"
 
898
                "~n   SSLOptions: ~p", [URL, SslTag, SSLOptions]),
 
899
            {ok, {{_,200, _}, [_ | _], []}} =
 
900
                httpc:request(head, {URL, []}, [{ssl, SSLConfig}], []);
 
901
        {ok, _} ->
 
902
            {skip, "local http-server not started"};
 
903
        _ ->
 
904
            {skip, "SSL not started"}
 
905
    end.  
 
906
 
 
907
    
 
908
%%-------------------------------------------------------------------------
 
909
ssl_get(doc) ->
 
910
    ["Same as http_get/1 but over ssl sockets."];
 
911
ssl_get(suite) ->
 
912
    [];
 
913
ssl_get(Config) when is_list(Config) ->
 
914
    ssl_get(ssl, Config).
 
915
 
 
916
ossl_get(doc) ->
 
917
    ["Same as http_get/1 but over ssl sockets."];
 
918
ossl_get(suite) ->
 
919
    [];
 
920
ossl_get(Config) when is_list(Config) ->
 
921
    ssl_get(ossl, Config).
 
922
 
 
923
essl_get(doc) ->
 
924
    ["Same as http_get/1 but over ssl sockets."];
 
925
essl_get(suite) ->
 
926
    [];
 
927
essl_get(Config) when is_list(Config) ->
 
928
    ssl_get(essl, Config).
 
929
 
 
930
ssl_get(SslTag, Config) when is_list(Config) ->
 
931
    case ?config(local_ssl_server, Config) of 
 
932
        ok ->
 
933
            DataDir    = ?config(data_dir, Config),
 
934
            Port       = ?config(local_ssl_port, Config),
 
935
            URL        = ?SSL_URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
936
            CertFile   = filename:join(DataDir, "ssl_client_cert.pem"),
 
937
            SSLOptions = [{certfile, CertFile}, {keyfile, CertFile}],
 
938
            SSLConfig  = 
 
939
                case SslTag of
 
940
                    ssl ->
 
941
                        SSLOptions;
 
942
                    ossl ->
 
943
                        {ossl, SSLOptions};
 
944
                    essl ->
 
945
                        {essl, SSLOptions}
 
946
                end,
 
947
            tsp("ssl_get -> make request using: "
 
948
                "~n   URL:        ~p"
 
949
                "~n   SslTag:     ~p"
 
950
                "~n   SSLOptions: ~p", [URL, SslTag, SSLOptions]),
 
951
            {ok, {{_,200, _}, [_ | _], Body = [_ | _]}} =
 
952
                httpc:request(get, {URL, []}, [{ssl, SSLConfig}], []),
 
953
            inets_test_lib:check_body(Body);
 
954
         {ok, _} ->
 
955
             {skip, "Failed to start local http-server"}; 
 
956
         _ ->
 
957
             {skip, "Failed to start SSL"}
 
958
     end.
 
959
 
 
960
 
 
961
%%-------------------------------------------------------------------------
 
962
ssl_trace(doc) ->
 
963
    ["Same as http_trace/1 but over ssl sockets."];
 
964
ssl_trace(suite) ->
 
965
    [];
 
966
ssl_trace(Config) when is_list(Config) ->
 
967
    ssl_trace(ssl, Config).
 
968
 
 
969
ossl_trace(doc) ->
 
970
    ["Same as http_trace/1 but over ssl sockets."];
 
971
ossl_trace(suite) ->
 
972
    [];
 
973
ossl_trace(Config) when is_list(Config) ->
 
974
    ssl_trace(ossl, Config).
 
975
 
 
976
essl_trace(doc) ->
 
977
    ["Same as http_trace/1 but over ssl sockets."];
 
978
essl_trace(suite) ->
 
979
    [];
 
980
essl_trace(Config) when is_list(Config) ->
 
981
    ssl_trace(essl, Config).
 
982
 
 
983
ssl_trace(SslTag, Config) when is_list(Config) ->
 
984
    case ?config(local_ssl_server, Config) of 
 
985
        ok ->
 
986
            DataDir    = ?config(data_dir, Config),
 
987
            Port       = ?config(local_ssl_port, Config),
 
988
            URL        = ?SSL_URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
989
            CertFile   = filename:join(DataDir, "ssl_client_cert.pem"),
 
990
            SSLOptions = [{certfile, CertFile}, {keyfile, CertFile}],
 
991
            SSLConfig  = 
 
992
                case SslTag of
 
993
                    ssl ->
 
994
                        SSLOptions;
 
995
                    ossl ->
 
996
                        {ossl, SSLOptions};
 
997
                    essl ->
 
998
                        {essl, SSLOptions}
 
999
                end,
 
1000
            tsp("ssl_trace -> make request using: "
 
1001
                "~n   URL:        ~p"
 
1002
                "~n   SslTag:     ~p"
 
1003
                "~n   SSLOptions: ~p", [URL, SslTag, SSLOptions]),
 
1004
            case httpc:request(trace, {URL, []}, [{ssl, SSLConfig}], []) of
 
1005
                {ok, {{_,200, _}, [_ | _], "TRACE /dummy.html" ++ _}} ->
 
1006
                    ok;
 
1007
                {ok, {{_,200,_}, [_ | _], WrongBody}} ->
 
1008
                    tsf({wrong_body,  WrongBody});
 
1009
                {ok, WrongReply} ->
 
1010
                    tsf({wrong_reply, WrongReply});
 
1011
                Error ->
 
1012
                    tsf({failed, Error})
 
1013
            end;
 
1014
        {ok, _} ->
 
1015
            {skip, "Failed to start local http-server"}; 
 
1016
        _ ->
 
1017
            {skip, "Failed to start SSL"}
 
1018
    end.
 
1019
 
 
1020
 
 
1021
%%-------------------------------------------------------------------------
 
1022
http_redirect(doc) ->
 
1023
    ["Test redirect with dummy server as httpd does not implement"
 
1024
     " server redirect"];
 
1025
http_redirect(suite) ->
 
1026
    [];
 
1027
http_redirect(Config) when is_list(Config) ->
 
1028
    tsp("http_redirect -> entry with"
 
1029
        "~n   Config: ~p", [Config]),
 
1030
    case ?config(local_server, Config) of 
 
1031
        ok ->
 
1032
            tsp("http_redirect -> set ipfamily option to inet"),
 
1033
            ok = httpc:set_options([{ipfamily, inet}]),
 
1034
 
 
1035
            tsp("http_redirect -> start dummy server inet"),
 
1036
            {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
1037
            tsp("http_redirect -> server port = ~p", [Port]),
 
1038
    
 
1039
            URL300 = ?URL_START ++ integer_to_list(Port) ++ "/300.html",
 
1040
    
 
1041
            tsp("http_redirect -> issue request 1: "
 
1042
                "~n   ~p", [URL300]),
 
1043
            {ok, {{_,200,_}, [_ | _], [_|_]}} 
 
1044
                = httpc:request(get, {URL300, []}, [], []),
 
1045
            
 
1046
            tsp("http_redirect -> issue request 2: "
 
1047
                "~n   ~p", [URL300]),
 
1048
            {ok, {{_,300,_}, [_ | _], _}} = 
 
1049
                httpc:request(get, {URL300, []}, [{autoredirect, false}], []),
 
1050
 
 
1051
            URL301 = ?URL_START ++ integer_to_list(Port) ++ "/301.html",
 
1052
 
 
1053
            tsp("http_redirect -> issue request 3: "
 
1054
                "~n   ~p", [URL301]),
 
1055
            {ok, {{_,200,_}, [_ | _], [_|_]}} 
 
1056
                = httpc:request(get, {URL301, []}, [], []),
 
1057
            
 
1058
            tsp("http_redirect -> issue request 4: "
 
1059
                "~n   ~p", [URL301]),
 
1060
            {ok, {{_,200,_}, [_ | _], []}} 
 
1061
                = httpc:request(head, {URL301, []}, [], []),
 
1062
            
 
1063
            tsp("http_redirect -> issue request 5: "
 
1064
                "~n   ~p", [URL301]),
 
1065
            {ok, {{_,301,_}, [_ | _], [_|_]}} 
 
1066
                = httpc:request(post, {URL301, [],"text/plain", "foobar"},
 
1067
                               [], []),
 
1068
 
 
1069
            URL302 = ?URL_START ++ integer_to_list(Port) ++ "/302.html",
 
1070
         
 
1071
            tsp("http_redirect -> issue request 6: "
 
1072
                "~n   ~p", [URL302]),
 
1073
            {ok, {{_,200,_}, [_ | _], [_|_]}} 
 
1074
                = httpc:request(get, {URL302, []}, [], []),      
 
1075
            case httpc:request(get, {URL302, []}, [], []) of
 
1076
                {ok, Reply7} ->
 
1077
                    case Reply7 of
 
1078
                        {{_,200,_}, [_ | _], [_|_]} ->
 
1079
                            tsp("http_redirect -> "
 
1080
                                "expected reply for request 7"), 
 
1081
                            ok;
 
1082
                        {StatusLine, Headers, Body} ->
 
1083
                            tsp("http_redirect -> "
 
1084
                                "unexpected reply for request 7: "
 
1085
                                "~n   StatusLine: ~p"
 
1086
                                "~n   Headers:    ~p"
 
1087
                                "~n   Body:       ~p", 
 
1088
                                [StatusLine, Headers, Body]),
 
1089
                            tsf({unexpected_reply, Reply7})
 
1090
                    end;
 
1091
                Error7 ->
 
1092
                    tsp("http_redirect -> "
 
1093
                        "unexpected result for request 7: "
 
1094
                        "~n   Error7:       ~p", 
 
1095
                        [Error7]),
 
1096
                    tsf({unexpected_result, Error7})
 
1097
            end,
 
1098
            
 
1099
            tsp("http_redirect -> issue request 7: "
 
1100
                "~n   ~p", [URL302]),
 
1101
            {ok, {{_,200,_}, [_ | _], []}} 
 
1102
                = httpc:request(head, {URL302, []}, [], []),     
 
1103
            
 
1104
            tsp("http_redirect -> issue request 8: "
 
1105
                "~n   ~p", [URL302]),
 
1106
            {ok, {{_,302,_}, [_ | _], [_|_]}} 
 
1107
                = httpc:request(post, {URL302, [],"text/plain", "foobar"},
 
1108
                               [], []),
 
1109
   
 
1110
            URL307 = ?URL_START ++ integer_to_list(Port) ++ "/307.html",
 
1111
 
 
1112
            tsp("http_redirect -> issue request 9: "
 
1113
                "~n   ~p", [URL307]),
 
1114
            {ok, {{_,200,_}, [_ | _], [_|_]}} 
 
1115
                = httpc:request(get, {URL307, []}, [], []),
 
1116
        
 
1117
            tsp("http_redirect -> issue request 10: "
 
1118
                "~n   ~p", [URL307]),
 
1119
            {ok, {{_,200,_}, [_ | _], []}} 
 
1120
                = httpc:request(head, {URL307, []}, [], []),
 
1121
            
 
1122
            tsp("http_redirect -> issue request 11: "
 
1123
                "~n   ~p", [URL307]),
 
1124
            {ok, {{_,307,_}, [_ | _], [_|_]}} 
 
1125
                = httpc:request(post, {URL307, [],"text/plain", "foobar"},
 
1126
                               [], []),
 
1127
            
 
1128
            tsp("http_redirect -> stop dummy server"),
 
1129
            DummyServerPid ! stop,
 
1130
            tsp("http_redirect -> reset ipfamily option (to inet6fb4)"),
 
1131
            ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1132
            tsp("http_redirect -> done"),
 
1133
            ok;
 
1134
 
 
1135
        _ ->
 
1136
            {skip, "Failed to start local http-server"}
 
1137
    end.
 
1138
 
 
1139
 
 
1140
 
 
1141
%%-------------------------------------------------------------------------
 
1142
http_redirect_loop(doc) ->
 
1143
    ["Test redirect loop detection"];
 
1144
http_redirect_loop(suite) ->
 
1145
    [];
 
1146
http_redirect_loop(Config) when is_list(Config) ->
 
1147
    ok = httpc:set_options([{ipfamily, inet}]),
 
1148
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
1149
    
 
1150
    URL = ?URL_START ++ integer_to_list(Port) ++ "/redirectloop.html",
 
1151
    
 
1152
    {ok, {{_,300,_}, [_ | _], _}} 
 
1153
        = httpc:request(get, {URL, []}, [], []),
 
1154
    DummyServerPid ! stop,
 
1155
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1156
    ok.
 
1157
 
 
1158
%%-------------------------------------------------------------------------
 
1159
http_internal_server_error(doc) ->
 
1160
    ["Test 50X codes"];
 
1161
http_internal_server_error(suite) ->
 
1162
    [];
 
1163
http_internal_server_error(Config) when is_list(Config) ->
 
1164
    ok = httpc:set_options([{ipfamily, inet}]),
 
1165
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
1166
    
 
1167
    URL500 = ?URL_START ++ integer_to_list(Port) ++ "/500.html",
 
1168
    
 
1169
    {ok, {{_,500,_}, [_ | _], _}} 
 
1170
        = httpc:request(get, {URL500, []}, [], []),
 
1171
 
 
1172
 
 
1173
    URL503 = ?URL_START ++ integer_to_list(Port) ++ "/503.html",
 
1174
 
 
1175
    %% Used to be able to make the service available after retry.
 
1176
    ets:new(unavailable, [named_table, public, set]),
 
1177
    ets:insert(unavailable, {503, unavailable}),
 
1178
    
 
1179
    {ok, {{_,200, _}, [_ | _], [_|_]}} =
 
1180
        httpc:request(get, {URL503, []}, [], []),
 
1181
    
 
1182
    ets:insert(unavailable, {503, long_unavailable}),
 
1183
 
 
1184
    {ok, {{_,503, _}, [_ | _], [_|_]}} =
 
1185
        httpc:request(get, {URL503, []}, [], []),
 
1186
 
 
1187
    ets:delete(unavailable),
 
1188
    DummyServerPid ! stop,
 
1189
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1190
    ok.
 
1191
 
 
1192
 
 
1193
%%-------------------------------------------------------------------------
 
1194
http_userinfo(doc) ->
 
1195
    ["Test user info e.i. http://user:passwd@host:port/"];
 
1196
http_userinfo(suite) ->
 
1197
    [];
 
1198
http_userinfo(Config) when is_list(Config) ->
 
1199
    ok = httpc:set_options([{ipfamily, inet}]),
 
1200
 
 
1201
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
1202
    
 
1203
    URLAuth = "http://alladin:sesame@localhost:" 
 
1204
        ++ integer_to_list(Port) ++ "/userinfo.html",
 
1205
    
 
1206
    {ok, {{_,200,_}, [_ | _], _}} 
 
1207
        = httpc:request(get, {URLAuth, []}, [], []),
 
1208
 
 
1209
    URLUnAuth = "http://alladin:foobar@localhost:" 
 
1210
        ++ integer_to_list(Port) ++ "/userinfo.html",
 
1211
    
 
1212
    {ok, {{_,401, _}, [_ | _], _}} =
 
1213
        httpc:request(get, {URLUnAuth, []}, [], []),
 
1214
    
 
1215
    DummyServerPid ! stop,
 
1216
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1217
    ok.
 
1218
 
 
1219
 
 
1220
%%-------------------------------------------------------------------------
 
1221
http_cookie(doc) ->
 
1222
    ["Test cookies."];
 
1223
http_cookie(suite) ->
 
1224
    [];
 
1225
http_cookie(Config) when is_list(Config) ->
 
1226
    ok = httpc:set_options([{cookies, enabled}, {ipfamily, inet}]),
 
1227
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
1228
    
 
1229
    URLStart = ?URL_START  
 
1230
        ++ integer_to_list(Port),
 
1231
    
 
1232
    URLCookie = URLStart ++ "/cookie.html",
 
1233
   
 
1234
    {ok, {{_,200,_}, [_ | _], [_|_]}} 
 
1235
        = httpc:request(get, {URLCookie, []}, [], []),
 
1236
 
 
1237
    ets:new(cookie, [named_table, public, set]),
 
1238
    ets:insert(cookie, {cookies, true}),
 
1239
 
 
1240
    {ok, {{_,200,_}, [_ | _], [_|_]}} 
 
1241
        = httpc:request(get, {URLStart ++ "/", []}, [], []),
 
1242
    
 
1243
    ets:delete(cookie),
 
1244
 
 
1245
    ok = httpc:set_options([{cookies, disabled}]), 
 
1246
    DummyServerPid ! stop,
 
1247
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1248
    ok.
 
1249
 
 
1250
%%-------------------------------------------------------------------------
 
1251
proxy_options(doc) ->
 
1252
    ["Perform a OPTIONS request that goes through a proxy."];
 
1253
proxy_options(suite) ->
 
1254
    [];
 
1255
proxy_options(Config) when is_list(Config) ->
 
1256
    case ?config(skip, Config) of 
 
1257
        undefined ->
 
1258
            case httpc:request(options, {?PROXY_URL, []}, [], []) of
 
1259
                {ok, {{_,200,_}, Headers, _}} ->
 
1260
                    case lists:keysearch("allow", 1, Headers) of
 
1261
                        {value, {"allow", _}} ->
 
1262
                            ok;
 
1263
                        _ ->
 
1264
                            test_server:fail(http_options_request_failed)
 
1265
                    end;
 
1266
                Unexpected ->
 
1267
                    test_server:fail({unexpected_result, Unexpected})
 
1268
            end;
 
1269
        Reason ->
 
1270
            {skip, Reason}
 
1271
    end.
 
1272
 
 
1273
 
 
1274
%%-------------------------------------------------------------------------
 
1275
proxy_head(doc) ->
 
1276
     ["Perform a HEAD request that goes through a proxy."];
 
1277
proxy_head(suite) ->
 
1278
    [];
 
1279
proxy_head(Config) when is_list(Config) ->
 
1280
    case ?config(skip, Config) of 
 
1281
        undefined ->
 
1282
            case httpc:request(head, {?PROXY_URL, []}, [], []) of
 
1283
                {ok, {{_,200, _}, [_ | _], []}} ->
 
1284
                    ok;
 
1285
                Unexpected ->
 
1286
                    test_server:fail({unexpected_result, Unexpected})
 
1287
            end;
 
1288
        Reason ->
 
1289
            {skip, Reason}
 
1290
    end.
 
1291
 
 
1292
 
 
1293
%%-------------------------------------------------------------------------
 
1294
proxy_get(doc) ->
 
1295
    ["Perform a GET request that goes through a proxy."];
 
1296
proxy_get(suite) ->
 
1297
    [];
 
1298
proxy_get(Config) when is_list(Config) ->
 
1299
    case ?config(skip, Config) of 
 
1300
        undefined ->
 
1301
            case httpc:request(get, {?PROXY_URL, []}, [], []) of
 
1302
                {ok, {{_,200,_}, [_ | _], Body = [_ | _]}} ->
 
1303
                    inets_test_lib:check_body(Body);
 
1304
                Unexpected ->
 
1305
                    test_server:fail({unexpected_result, Unexpected})
 
1306
            end;
 
1307
        Reason ->
 
1308
            {skip, Reason}
 
1309
    end.
 
1310
 
 
1311
%%-------------------------------------------------------------------------
 
1312
proxy_emulate_lower_versions(doc) ->
 
1313
    ["Perform requests as 0.9 and 1.0 clients."];
 
1314
proxy_emulate_lower_versions(suite) ->
 
1315
    [];
 
1316
proxy_emulate_lower_versions(Config) when is_list(Config) ->
 
1317
    case ?config(skip, Config) of 
 
1318
        undefined ->
 
1319
            Result09 = pelv_get("HTTP/0.9"), 
 
1320
            case Result09 of
 
1321
                {ok, [_| _] = Body0} ->
 
1322
                    inets_test_lib:check_body(Body0),
 
1323
                    ok;
 
1324
                _ ->
 
1325
                    tsf({unexpected_result, "HTTP/0.9", Result09})
 
1326
            end,
 
1327
            
 
1328
            %% We do not check the version here as many servers
 
1329
            %% do not behave according to the rfc and send
 
1330
            %% 1.1 in its response.
 
1331
            Result10 = pelv_get("HTTP/1.0"), 
 
1332
            case Result10 of
 
1333
                {ok,{{_, 200, _}, [_ | _], Body1 = [_ | _]}} ->
 
1334
                    inets_test_lib:check_body(Body1),
 
1335
                    ok;
 
1336
                _ ->
 
1337
                    tsf({unexpected_result, "HTTP/1.0", Result10})
 
1338
            end,
 
1339
 
 
1340
            Result11 = pelv_get("HTTP/1.1"), 
 
1341
            case Result11 of
 
1342
                {ok, {{"HTTP/1.1", 200, _}, [_ | _], Body2 = [_ | _]}} ->
 
1343
                    inets_test_lib:check_body(Body2);
 
1344
                _ ->
 
1345
                    tsf({unexpected_result, "HTTP/1.1", Result11})
 
1346
            end;
 
1347
                
 
1348
        Reason ->
 
1349
            {skip, Reason}
 
1350
    end.
 
1351
 
 
1352
pelv_get(Version) ->
 
1353
    httpc:request(get, {?PROXY_URL, []}, [{version, Version}], []).
 
1354
 
 
1355
%%-------------------------------------------------------------------------
 
1356
proxy_trace(doc) ->
 
1357
    ["Perform a TRACE request that goes through a proxy."];
 
1358
proxy_trace(suite) ->
 
1359
    [];
 
1360
proxy_trace(Config) when is_list(Config) ->
 
1361
    %%{ok, {{_,200,_}, [_ | _], "TRACE " ++ _}} =
 
1362
    %%  httpc:request(trace, {?PROXY_URL, []}, [], []),
 
1363
    {skip, "HTTP TRACE is no longer allowed on the ?PROXY_URL server due "
 
1364
     "to security reasons"}.
 
1365
 
 
1366
 
 
1367
%%-------------------------------------------------------------------------
 
1368
proxy_post(doc) ->
 
1369
    ["Perform a POST request that goes through a proxy. Note the server"
 
1370
     " will reject the request this is a test of the sending of the"
 
1371
     " request."];
 
1372
proxy_post(suite) ->
 
1373
    [];
 
1374
proxy_post(Config) when is_list(Config) ->
 
1375
    case ?config(skip, Config) of 
 
1376
        undefined ->
 
1377
            case httpc:request(post, {?PROXY_URL, [], 
 
1378
                                     "text/plain", "foobar"}, [],[]) of
 
1379
                {ok, {{_,405,_}, [_ | _], [_ | _]}} ->
 
1380
                    ok;
 
1381
                Unexpected ->
 
1382
                    test_server:fail({unexpected_result, Unexpected})
 
1383
            end;
 
1384
        Reason ->
 
1385
            {skip, Reason}
 
1386
    end.
 
1387
 
 
1388
 
 
1389
%%-------------------------------------------------------------------------
 
1390
proxy_put(doc) ->
 
1391
    ["Perform a PUT request that goes through a proxy. Note the server"
 
1392
     " will reject the request this is a test of the sending of the"
 
1393
     " request."];
 
1394
proxy_put(suite) ->
 
1395
    [];
 
1396
proxy_put(Config) when is_list(Config) ->
 
1397
    case ?config(skip, Config) of 
 
1398
        undefined -> 
 
1399
            case httpc:request(put, {"http://www.erlang.org/foobar.html", [], 
 
1400
                                    "html", "<html> <body><h1> foo </h1>" 
 
1401
                                    "<p>bar</p> </body></html>"}, [], []) of
 
1402
                {ok, {{_,405,_}, [_ | _], [_ | _]}} ->
 
1403
                    ok;
 
1404
                Unexpected ->
 
1405
                    test_server:fail({unexpected_result, Unexpected})
 
1406
            end;
 
1407
        Reason ->
 
1408
            {skip, Reason}
 
1409
    end.
 
1410
 
 
1411
 
 
1412
%%-------------------------------------------------------------------------
 
1413
proxy_delete(doc) ->
 
1414
    ["Perform a DELETE request that goes through a proxy. Note the server"
 
1415
     " will reject the request this is a test of the sending of the"
 
1416
     " request. But as the file does not exist the return code will"
 
1417
     " be 404 not found."];
 
1418
proxy_delete(suite) ->
 
1419
    [];
 
1420
proxy_delete(Config) when is_list(Config) ->
 
1421
    case ?config(skip, Config) of 
 
1422
        undefined -> 
 
1423
            URL = ?PROXY_URL ++ "/foobar.html",
 
1424
            case httpc:request(delete, {URL, []}, [], []) of
 
1425
                {ok, {{_,404,_}, [_ | _], [_ | _]}} ->
 
1426
                    ok;
 
1427
                Unexpected ->
 
1428
                    test_server:fail({unexpected_result, Unexpected})
 
1429
            end;
 
1430
        Reason ->
 
1431
            {skip, Reason}
 
1432
    end.
 
1433
 
 
1434
 
 
1435
%%-------------------------------------------------------------------------
 
1436
proxy_headers(doc) ->
 
1437
    ["Use as many request headers as possible"];
 
1438
proxy_headers(suite) ->
 
1439
    [];
 
1440
proxy_headers(Config) when is_list(Config) ->
 
1441
    case ?config(skip, Config) of 
 
1442
        undefined ->
 
1443
            {ok, {{_,200,_}, [_ | _], [_ | _]}} 
 
1444
                = httpc:request(get, {?PROXY_URL,
 
1445
                                     [
 
1446
                                      {"Accept",
 
1447
                                       "text/*, text/html,"
 
1448
                                       " text/html;level=1,"
 
1449
                                       " */*"}, 
 
1450
                                      {"Accept-Charset", 
 
1451
                                       "iso-8859-5, unicode-1-1;"
 
1452
                                       "q=0.8"},
 
1453
                                      {"Accept-Encoding", "*"},
 
1454
                                      {"Accept-Language", 
 
1455
                                       "sv, en-gb;q=0.8,"
 
1456
                                       " en;q=0.7"},
 
1457
                                      {"User-Agent", "inets"},
 
1458
                                      {"Max-Forwards","5"},
 
1459
                                      {"Referer", 
 
1460
                                       "http://otp.ericsson.se:8000"
 
1461
                                       "/product/internal"}
 
1462
                             ]}, [], []),
 
1463
            ok;
 
1464
        Reason ->
 
1465
            {skip, Reason}
 
1466
    end.
 
1467
 
 
1468
%%-------------------------------------------------------------------------
 
1469
proxy_auth(doc) ->
 
1470
    ["Test the code for sending of proxy authorization."];
 
1471
proxy_auth(suite) ->
 
1472
    [];
 
1473
proxy_auth(Config) when is_list(Config) ->
 
1474
    %% Our proxy seems to ignore the header, however our proxy
 
1475
    %% does not requirer an auth header, but we want to know
 
1476
    %% atleast the code for sending the header does not crash!
 
1477
    case ?config(skip, Config) of 
 
1478
        undefined ->        
 
1479
            case httpc:request(get, {?PROXY_URL, []}, 
 
1480
                              [{proxy_auth, {"foo", "bar"}}], []) of
 
1481
                {ok, {{_,200, _}, [_ | _], [_|_]}} ->
 
1482
                    ok;
 
1483
                Unexpected ->
 
1484
                    test_server:fail({unexpected_result, Unexpected})
 
1485
            end;
 
1486
        Reason ->
 
1487
            {skip, Reason}
 
1488
    end.  
 
1489
 
 
1490
 
 
1491
%%-------------------------------------------------------------------------
 
1492
http_server_does_not_exist(doc) ->
 
1493
    ["Test that we get an error message back when the server "
 
1494
     "does note exist."];
 
1495
http_server_does_not_exist(suite) ->
 
1496
    [];
 
1497
http_server_does_not_exist(Config) when is_list(Config) ->
 
1498
    {error, _} = 
 
1499
        httpc:request(get, {"http://localhost:" ++ 
 
1500
                           integer_to_list(?NOT_IN_USE_PORT) 
 
1501
                           ++ "/", []},[], []),
 
1502
    ok.
 
1503
 
 
1504
 
 
1505
%%-------------------------------------------------------------------------
 
1506
page_does_not_exist(doc) ->
 
1507
    ["Test that we get a 404 when the page is not found."];
 
1508
page_does_not_exist(suite) ->
 
1509
    [];
 
1510
page_does_not_exist(Config) when is_list(Config) ->
 
1511
    Port = ?config(local_port, Config),
 
1512
    URL = ?URL_START ++ integer_to_list(Port) ++ "/doesnotexist.html",
 
1513
    {ok, {{_,404,_}, [_ | _], [_ | _]}} 
 
1514
        = httpc:request(get, {URL, []}, [], []),
 
1515
    ok.
 
1516
 
 
1517
 
 
1518
%%-------------------------------------------------------------------------
 
1519
proxy_page_does_not_exist(doc) ->
 
1520
    ["Test that we get a 404 when the page is not found."];
 
1521
proxy_page_does_not_exist(suite) ->
 
1522
    [];
 
1523
proxy_page_does_not_exist(Config) when is_list(Config) ->
 
1524
    case ?config(skip, Config) of 
 
1525
        undefined ->
 
1526
            URL = ?PROXY_URL ++ "/doesnotexist.html",
 
1527
            {ok, {{_,404,_}, [_ | _], [_ | _]}} = 
 
1528
                httpc:request(get, {URL, []}, [], []),
 
1529
            ok;
 
1530
        Reason ->
 
1531
            {skip, Reason}
 
1532
    end.
 
1533
 
 
1534
 
 
1535
%%-------------------------------------------------------------------------
 
1536
 
 
1537
proxy_https_not_supported(doc) ->
 
1538
    [];
 
1539
proxy_https_not_supported(suite) ->
 
1540
    [];
 
1541
proxy_https_not_supported(Config) when is_list(Config) ->
 
1542
    Result = httpc:request(get, {"https://login.yahoo.com", []}, [], []),
 
1543
    case Result of
 
1544
        {error, Reason} ->
 
1545
            %% ok so far
 
1546
            case Reason of
 
1547
                {failed_connecting, Why} ->
 
1548
                    %% ok, now check why
 
1549
                    case Why of
 
1550
                        https_through_proxy_is_not_currently_supported ->
 
1551
                            ok;
 
1552
                        _ ->
 
1553
                            tsf({unexpected_why, Why})
 
1554
                    end;
 
1555
                _ ->
 
1556
                    tsf({unexpected_reason, Reason})
 
1557
            end;
 
1558
        _ ->
 
1559
            tsf({unexpected_result, Result})
 
1560
    end,
 
1561
    ok.
 
1562
 
 
1563
 
 
1564
%%-------------------------------------------------------------------------
 
1565
 
 
1566
http_stream(doc) ->
 
1567
    ["Test the option stream for asynchrony requests"];
 
1568
http_stream(suite) ->
 
1569
    [];
 
1570
http_stream(Config) when is_list(Config) ->
 
1571
    Port = ?config(local_port, Config),
 
1572
    URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
1573
    {ok, {{_,200,_}, [_ | _], Body}} = 
 
1574
        httpc:request(get, {URL, []}, [], []),
 
1575
    
 
1576
    {ok, RequestId} =
 
1577
        httpc:request(get, {URL, []}, [], [{sync, false}, 
 
1578
                                          {stream, self}]),
 
1579
    
 
1580
    receive 
 
1581
        {http, {RequestId, stream_start, _Headers}} ->
 
1582
            ok;
 
1583
        {http, Msg} ->
 
1584
            test_server:fail(Msg)
 
1585
    end,
 
1586
 
 
1587
    StreamedBody = receive_streamed_body(RequestId, <<>>),
 
1588
    
 
1589
    Body == binary_to_list(StreamedBody).
 
1590
 
 
1591
 
 
1592
%%-------------------------------------------------------------------------
 
1593
http_stream_once(doc) ->
 
1594
    ["Test the option stream for asynchrony requests"];
 
1595
http_stream_once(suite) ->
 
1596
    [];
 
1597
http_stream_once(Config) when is_list(Config) ->
 
1598
    p("http_stream_once -> entry with"
 
1599
      "~n   Config: ~p", [Config]),
 
1600
      
 
1601
    p("http_stream_once -> set ipfamily to inet", []),
 
1602
    ok = httpc:set_options([{ipfamily, inet}]),
 
1603
    p("http_stream_once -> start dummy server", []),
 
1604
    {DummyServerPid, Port} = dummy_server(self(), ipv4),    
 
1605
    
 
1606
    PortStr =  integer_to_list(Port),
 
1607
    p("http_stream_once -> once", []),
 
1608
    once(?URL_START ++ PortStr ++ "/once.html"),
 
1609
    p("http_stream_once -> once_chunked", []),
 
1610
    once(?URL_START ++ PortStr ++ "/once_chunked.html"),
 
1611
    p("http_stream_once -> dummy", []),
 
1612
    once(?URL_START ++ PortStr ++ "/dummy.html"),
 
1613
    
 
1614
    p("http_stream_once -> stop dummy server", []),
 
1615
    DummyServerPid ! stop,
 
1616
    p("http_stream_once -> set ipfamily to inet6fb4", []),
 
1617
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1618
    p("http_stream_once -> done", []),
 
1619
    ok.
 
1620
  
 
1621
once(URL) ->
 
1622
    p("once -> issue sync request for ~p", [URL]),
 
1623
    {ok, {{_,200,_}, [_ | _], Body}} = 
 
1624
        httpc:request(get, {URL, []}, [], []),
 
1625
    
 
1626
    p("once -> issue async (self stream) request for ~p", [URL]),
 
1627
    {ok, RequestId} =
 
1628
        httpc:request(get, {URL, []}, [], [{sync, false}, 
 
1629
                                          {stream, {self, once}}]),
 
1630
    
 
1631
    p("once -> await stream_start reply for (async) request ~p", [RequestId]),
 
1632
    NewPid = 
 
1633
        receive 
 
1634
            {http, {RequestId, stream_start, _Headers, Pid}} ->
 
1635
                p("once -> received stream_start reply for (async) request ~p: ~p", 
 
1636
                  [RequestId, Pid]),
 
1637
                Pid;
 
1638
            {http, Msg} ->
 
1639
                test_server:fail(Msg)
 
1640
        end,
 
1641
 
 
1642
    tsp("once -> request handler: ~p", [NewPid]),
 
1643
 
 
1644
    p("once -> await stream reply for (async) request ~p", [RequestId]),
 
1645
    BodyPart = 
 
1646
        receive 
 
1647
            {http, {RequestId, stream, BinBodyPart}} ->
 
1648
                p("once -> received stream reply for (async) request ~p: "
 
1649
                  "~n~p", [RequestId, binary_to_list(BinBodyPart)]),
 
1650
                BinBodyPart
 
1651
        end,
 
1652
 
 
1653
    tsp("once -> first body part '~p' received", [binary_to_list(BodyPart)]),
 
1654
 
 
1655
    StreamedBody = receive_streamed_body(RequestId, BinBodyPart, NewPid),
 
1656
    
 
1657
    Body = binary_to_list(StreamedBody),
 
1658
 
 
1659
    p("once -> done when Bode: ~p", [Body]),
 
1660
    ok.
 
1661
 
 
1662
 
 
1663
%%-------------------------------------------------------------------------
 
1664
proxy_stream(doc) ->
 
1665
    ["Test the option stream for asynchrony requests"];
 
1666
proxy_stream(suite) ->
 
1667
    [];
 
1668
proxy_stream(Config) when is_list(Config) ->
 
1669
    case ?config(skip, Config) of 
 
1670
        undefined ->
 
1671
            {ok, {{_,200,_}, [_ | _], Body}} = 
 
1672
                httpc:request(get, {?PROXY_URL, []}, [], []),
 
1673
            
 
1674
            {ok, RequestId} =
 
1675
                httpc:request(get, {?PROXY_URL, []}, [], 
 
1676
                             [{sync, false}, {stream, self}]),
 
1677
            
 
1678
            receive 
 
1679
                {http, {RequestId, stream_start, _Headers}} ->
 
1680
                    ok;
 
1681
                {http, Msg} ->
 
1682
                    test_server:fail(Msg)
 
1683
            end,
 
1684
            
 
1685
            StreamedBody = receive_streamed_body(RequestId, <<>>),
 
1686
            
 
1687
            Body == binary_to_list(StreamedBody);
 
1688
        Reason ->
 
1689
            {skip, Reason}
 
1690
    end.
 
1691
 
 
1692
 
 
1693
%%-------------------------------------------------------------------------
 
1694
parse_url(doc) ->
 
1695
    ["Test that an url is parsed correctly"];
 
1696
parse_url(suite) ->
 
1697
    [];
 
1698
parse_url(Config) when is_list(Config) ->
 
1699
    %% ipv6
 
1700
    {http,[],"2010:836B:4179::836B:4179",80,"/foobar.html",[]}
 
1701
        = http_uri:parse("http://[2010:836B:4179::836B:4179]/foobar.html"),
 
1702
    {error,
 
1703
     {malformed_url,"http://2010:836B:4179::836B:4179/foobar.html"}} =
 
1704
        http_uri:parse("http://2010:836B:4179::836B:4179/foobar.html"), 
 
1705
 
 
1706
    %% ipv4
 
1707
    {http,[],"127.0.0.1",80,"/foobar.html",[]} =
 
1708
        http_uri:parse("http://127.0.0.1/foobar.html"),
 
1709
    
 
1710
    %% host
 
1711
    {http,[],"localhost",8888,"/foobar.html",[]} = 
 
1712
        http_uri:parse("http://localhost:8888/foobar.html"),
 
1713
    
 
1714
    %% Userinfo
 
1715
    {http,"nisse:foobar","localhost",8888,"/foobar.html",[]} =
 
1716
        http_uri:parse("http://nisse:foobar@localhost:8888/foobar.html"),
 
1717
    
 
1718
    %% Scheme error
 
1719
    {error,no_scheme} =  http_uri:parse("localhost/foobar.html"),
 
1720
    {error,{not_supported_scheme,localhost}} =
 
1721
        http_uri:parse("localhost:8888/foobar.html"),
 
1722
    
 
1723
    %% Query
 
1724
    {http,[],"localhost",8888,"/foobar.html","?foo=bar&foobar=42"} =
 
1725
        http_uri:parse("http://localhost:8888/foobar.html?foo=bar&foobar=42"),
 
1726
    
 
1727
    %%  Esc chars
 
1728
    {http,[],"www.somedomain.com",80,"/%2Eabc",[]} =
 
1729
        http_uri:parse("http://www.somedomain.com/%2Eabc"),
 
1730
    {http,[],"www.somedomain.com",80,"/%252Eabc",[]} = 
 
1731
        http_uri:parse("http://www.somedomain.com/%252Eabc"),
 
1732
    {http,[],"www.somedomain.com",80,"/%25abc",[]} =
 
1733
        http_uri:parse("http://www.somedomain.com/%25abc"),
 
1734
    {http,[],"www.somedomain.com",80,"/%25abc", "?foo=bar"} =
 
1735
        http_uri:parse("http://www.somedomain.com/%25abc?foo=bar"),
 
1736
    ok.    
 
1737
 
 
1738
 
 
1739
%%-------------------------------------------------------------------------
 
1740
ipv6() ->
 
1741
    [{require,ipv6_hosts}].
 
1742
ipv6(doc) ->
 
1743
    ["Test ipv6."];
 
1744
ipv6(suite) ->
 
1745
    [];
 
1746
ipv6(Config) when is_list(Config) ->
 
1747
    {ok, Hostname} = inet:gethostname(),
 
1748
    
 
1749
    case lists:member(list_to_atom(Hostname), 
 
1750
                      ct:get_config(ipv6_hosts)) of
 
1751
        true ->
 
1752
            {DummyServerPid, Port} = dummy_server(self(), ipv6),
 
1753
            
 
1754
            URL = "http://[" ++ ?IPV6_LOCAL_HOST ++ "]:" ++ 
 
1755
                integer_to_list(Port) ++ "/foobar.html",
 
1756
            {ok, {{_,200,_}, [_ | _], [_|_]}} =
 
1757
                httpc:request(get, {URL, []}, [], []),
 
1758
            
 
1759
            DummyServerPid ! stop,
 
1760
            ok;
 
1761
        false ->
 
1762
            {skip, "Host does not support IPv6"}
 
1763
    end.
 
1764
 
 
1765
 
 
1766
%%-------------------------------------------------------------------------
 
1767
headers_as_is(doc) ->
 
1768
    ["Test the option headers_as_is"];
 
1769
headers_as_is(suite) ->
 
1770
    [];
 
1771
headers_as_is(Config) when is_list(Config) ->
 
1772
    Port = ?config(local_port, Config),
 
1773
    URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
1774
    {ok, {{_,200,_}, [_|_], [_|_]}} =
 
1775
        httpc:request(get, {URL, [{"Host", "localhost"},{"Te", ""}]}, 
 
1776
                     [], [{headers_as_is, true}]),
 
1777
     
 
1778
    {ok, {{_,400,_}, [_|_], [_|_]}} = 
 
1779
        httpc:request(get, {URL, [{"Te", ""}]},[], [{headers_as_is, true}]),
 
1780
    ok.
 
1781
 
 
1782
 
 
1783
%%-------------------------------------------------------------------------
 
1784
options(doc) ->
 
1785
    ["Test the option parameters."];
 
1786
options(suite) ->
 
1787
    [];
 
1788
options(Config) when is_list(Config) ->
 
1789
    case ?config(local_server, Config) of 
 
1790
        ok ->
 
1791
            Port = ?config(local_port, Config),
 
1792
            URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
1793
            {ok, {{_,200,_}, [_ | _], Bin}} 
 
1794
                = httpc:request(get, {URL, []}, [{foo, bar}], 
 
1795
                               %% Ignore unknown options
 
1796
                               [{body_format, binary}, {foo, bar}]),
 
1797
 
 
1798
            true = is_binary(Bin),
 
1799
            {ok, {200, [_|_]}} 
 
1800
                = httpc:request(get, {URL, []}, [{timeout, infinity}],
 
1801
                               [{full_result, false}]);
 
1802
        _ ->
 
1803
            {skip, "Failed to start local http-server"}
 
1804
    end.  
 
1805
 
 
1806
 
 
1807
%%-------------------------------------------------------------------------
 
1808
http_invalid_http(doc) ->
 
1809
    ["Test parse error"];
 
1810
http_invalid_http(suite) ->
 
1811
    [];
 
1812
http_invalid_http(Config) when is_list(Config) ->
 
1813
    ok = httpc:set_options([{ipfamily, inet}]),
 
1814
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
1815
    
 
1816
    URL = ?URL_START ++ integer_to_list(Port) ++ "/invalid_http.html",
 
1817
    
 
1818
    {error, {could_not_parse_as_http, _} = Reason} =
 
1819
        httpc:request(get, {URL, []}, [], []),
 
1820
    
 
1821
    test_server:format("Parse error: ~p ~n", [Reason]),
 
1822
    DummyServerPid ! stop,
 
1823
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1824
    ok.
 
1825
 
 
1826
 
 
1827
%%-------------------------------------------------------------------------
 
1828
 
 
1829
hexed_query_otp_6191(doc) ->
 
1830
    [];
 
1831
hexed_query_otp_6191(suite) ->
 
1832
    [];
 
1833
hexed_query_otp_6191(Config) when is_list(Config) ->
 
1834
    Google = "www.google.com",
 
1835
    GoogleSearch = "http://" ++ Google ++ "/search",
 
1836
    Search1 = "?hl=en&q=a%D1%85%D1%83%D0%B9&btnG=Google+Search", 
 
1837
    URI1    = GoogleSearch ++ Search1,
 
1838
    Search2 = "?hl=en&q=%25%25", 
 
1839
    URI2    = GoogleSearch ++ Search2,
 
1840
    Search3 = "?hl=en&q=%foo",
 
1841
    URI3    = GoogleSearch ++ Search3, 
 
1842
 
 
1843
    {http, [], Google, 80, "/search", _} = http_uri:parse(URI1),
 
1844
    {http, [], Google, 80, "/search", _} = http_uri:parse(URI2),
 
1845
    {http, [], Google, 80, "/search", _} = http_uri:parse(URI3),
 
1846
    ok.
 
1847
 
 
1848
 
 
1849
%%-------------------------------------------------------------------------
 
1850
 
 
1851
empty_body_otp_6243(doc) ->
 
1852
    ["An empty body was not returned directly. There was a delay for several"
 
1853
     "seconds."];
 
1854
empty_body_otp_6243(suite) ->
 
1855
    [];
 
1856
empty_body_otp_6243(Config) when is_list(Config) ->
 
1857
    Port = ?config(local_port, Config),
 
1858
    URL = ?URL_START ++ integer_to_list(Port) ++ "/empty.html",
 
1859
    {ok, {{_,200,_}, [_ | _], []}} =
 
1860
        httpc:request(get, {URL, []}, [{timeout, 500}], []).
 
1861
 
 
1862
 
 
1863
%%-------------------------------------------------------------------------
 
1864
 
 
1865
transfer_encoding_otp_6807(doc) ->
 
1866
    ["Transfer encoding is case insensitive"];
 
1867
transfer_encoding_otp_6807(suite) ->
 
1868
    [];
 
1869
transfer_encoding_otp_6807(Config) when is_list(Config) ->
 
1870
    ok = httpc:set_options([{ipfamily, inet}]),
 
1871
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
1872
    
 
1873
    URL = ?URL_START ++ integer_to_list(Port) ++ 
 
1874
        "/capital_transfer_encoding.html",
 
1875
    {ok, {{_,200,_}, [_|_], [_ | _]}} = httpc:request(URL),
 
1876
    DummyServerPid ! stop,
 
1877
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1878
    ok.
 
1879
 
 
1880
 
 
1881
%%-------------------------------------------------------------------------
 
1882
 
 
1883
proxy_not_modified_otp_6821(doc) ->
 
1884
    ["If unmodified no body should be returned"];
 
1885
proxy_not_modified_otp_6821(suite) ->
 
1886
    [];
 
1887
proxy_not_modified_otp_6821(Config) when is_list(Config) ->
 
1888
    case ?config(skip, Config) of 
 
1889
        undefined ->
 
1890
            provocate_not_modified_bug(?PROXY_URL);
 
1891
        Reason ->
 
1892
            {skip, Reason}
 
1893
    end.
 
1894
 
 
1895
 
 
1896
%%-------------------------------------------------------------------------
 
1897
 
 
1898
empty_response_header_otp_6830(doc) ->
 
1899
    ["Test the case that the HTTP server does not send any headers"];
 
1900
empty_response_header_otp_6830(suite) ->
 
1901
    [];
 
1902
empty_response_header_otp_6830(Config) when is_list(Config) ->
 
1903
    ok = httpc:set_options([{ipfamily, inet}]),
 
1904
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
1905
    
 
1906
    URL = ?URL_START ++ integer_to_list(Port) ++ "/no_headers.html",
 
1907
    {ok, {{_,200,_}, [], [_ | _]}} = httpc:request(URL),
 
1908
    DummyServerPid ! stop,
 
1909
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1910
    ok.
 
1911
 
 
1912
 
 
1913
%%-------------------------------------------------------------------------
 
1914
 
 
1915
no_content_204_otp_6982(doc) ->
 
1916
    ["Test the case that the HTTP 204 no content header"];
 
1917
no_content_204_otp_6982(suite) ->
 
1918
    [];
 
1919
no_content_204_otp_6982(Config) when is_list(Config) ->
 
1920
    ok = httpc:set_options([{ipfamily, inet}]),
 
1921
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
1922
    
 
1923
    URL = ?URL_START ++ integer_to_list(Port) ++ "/no_content.html",
 
1924
    {ok, {{_,204,_}, [], []}} = httpc:request(URL),
 
1925
    DummyServerPid ! stop,
 
1926
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1927
    ok.
 
1928
 
 
1929
 
 
1930
%%-------------------------------------------------------------------------
 
1931
 
 
1932
missing_CR_otp_7304(doc) ->
 
1933
    ["Test the case that the HTTP server uses only LF instead of CRLF" 
 
1934
     "as delimitor"];
 
1935
missing_CR_otp_7304(suite) ->
 
1936
    [];
 
1937
missing_CR_otp_7304(Config) when is_list(Config) ->
 
1938
    ok = httpc:set_options([{ipfamily, inet}]),
 
1939
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
1940
    
 
1941
    URL = ?URL_START ++ integer_to_list(Port) ++ "/missing_CR.html",
 
1942
    {ok, {{_,200,_}, _, [_ | _]}} = httpc:request(URL),
 
1943
    DummyServerPid ! stop,
 
1944
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1945
    ok.
 
1946
 
 
1947
 
 
1948
%%-------------------------------------------------------------------------
 
1949
 
 
1950
 
 
1951
otp_7883_1(doc) ->
 
1952
    ["OTP-7883-sync"];
 
1953
otp_7883_1(suite) ->
 
1954
    [];
 
1955
otp_7883_1(Config) when is_list(Config) ->
 
1956
    ok = httpc:set_options([{ipfamily, inet}]),
 
1957
 
 
1958
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
1959
    
 
1960
    URL = ?URL_START ++ integer_to_list(Port) ++ "/just_close.html",
 
1961
    {error, socket_closed_remotely} = httpc:request(URL),
 
1962
    DummyServerPid ! stop,
 
1963
 
 
1964
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1965
    ok.
 
1966
 
 
1967
otp_7883_2(doc) ->
 
1968
    ["OTP-7883-async"];
 
1969
otp_7883_2(suite) ->
 
1970
    [];
 
1971
otp_7883_2(Config) when is_list(Config) ->
 
1972
    ok = httpc:set_options([{ipfamily, inet}]),
 
1973
 
 
1974
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
1975
    
 
1976
    URL = ?URL_START ++ integer_to_list(Port) ++ "/just_close.html",
 
1977
    Method      = get,
 
1978
    Request     = {URL, []}, 
 
1979
    HttpOptions = [], 
 
1980
    Options     = [{sync, false}], 
 
1981
    Profile     = httpc:default_profile(), 
 
1982
    {ok, RequestId} = 
 
1983
        httpc:request(Method, Request, HttpOptions, Options, Profile),
 
1984
    ok = 
 
1985
        receive
 
1986
            {http, {RequestId, {error, socket_closed_remotely}}} ->
 
1987
                ok
 
1988
    end,
 
1989
    DummyServerPid ! stop,
 
1990
 
 
1991
    ok = httpc:set_options([{ipfamily, inet6fb4}]), 
 
1992
    ok.
 
1993
 
 
1994
 
 
1995
%%-------------------------------------------------------------------------
 
1996
 
 
1997
 
 
1998
otp_8154_1(doc) ->
 
1999
    ["OTP-8154"];
 
2000
otp_8154_1(suite) ->
 
2001
    [];
 
2002
otp_8154_1(Config) when is_list(Config) ->
 
2003
    start_inets(),
 
2004
    ReqSeqNumServer = start_sequence_number_server(),
 
2005
    RespSeqNumServer = start_sequence_number_server(),
 
2006
    {ok, Server, Port} = start_slow_server(RespSeqNumServer),
 
2007
    Clients = run_clients(105, Port, ReqSeqNumServer),
 
2008
    %% ok = wait_for_clients(Clients),
 
2009
    ok = wait4clients(Clients, timer:minutes(3)),
 
2010
    Server ! shutdown,
 
2011
    RespSeqNumServer ! shutdown,
 
2012
    ReqSeqNumServer ! shutdown,
 
2013
    ok.
 
2014
 
 
2015
start_inets() ->
 
2016
    inets:start(),
 
2017
    ok.
 
2018
 
 
2019
 
 
2020
%% -----------------------------------------------------
 
2021
%% A sequence number handler
 
2022
%% The purpose is to be able to pair requests with responses.
 
2023
 
 
2024
start_sequence_number_server() ->
 
2025
    proc_lib:spawn(fun() -> loop_sequence_number(1) end).
 
2026
 
 
2027
loop_sequence_number(N) ->
 
2028
    receive
 
2029
        shutdown ->
 
2030
            ok;
 
2031
        {From, get_next} ->
 
2032
            From ! {next_is, N},
 
2033
            loop_sequence_number(N + 1)
 
2034
    end.
 
2035
 
 
2036
get_next_sequence_number(SeqNumServer) ->
 
2037
    SeqNumServer ! {self(), get_next},
 
2038
    receive {next_is, N} -> N end.
 
2039
 
 
2040
%% -----------------------------------------------------
 
2041
%% Client part
 
2042
%% Sends requests randomly parallel
 
2043
 
 
2044
run_clients(NumClients, ServerPort, SeqNumServer) ->
 
2045
    io:format("start clients when"
 
2046
              "~n   NumClients:   ~w"
 
2047
              "~n   ServerPort:   ~w"
 
2048
              "~n   SeqNumServer: ~w"
 
2049
              "~n", [NumClients, ServerPort, SeqNumServer]),
 
2050
    set_random_seed(),
 
2051
    lists:map(
 
2052
      fun(Id) ->
 
2053
              io:format("starting client ~w~n", [Id]),
 
2054
              Req = f("req~3..0w", [get_next_sequence_number(SeqNumServer)]),
 
2055
              Url = f(?URL_START ++ "~w/~s", [ServerPort, Req]),
 
2056
              Pid = proc_lib:spawn(
 
2057
                      fun() ->
 
2058
                              io:format("[~w] client started - "
 
2059
                                        "issue request~n", [Id]),
 
2060
                              case httpc:request(Url) of
 
2061
                                  {ok, {{_,200,_}, _, Resp}} ->
 
2062
                                      io:format("[~w] 200 response: "
 
2063
                                                "~p~n", [Id, Resp]),
 
2064
                                      case lists:prefix(Req++"->", Resp) of
 
2065
                                          true -> exit(normal);
 
2066
                                          false -> exit({bad_resp,Req,Resp})
 
2067
                                      end;
 
2068
                                  {ok, {{_,EC,Reason},_,Resp}}  ->
 
2069
                                      io:format("[~w] ~w response: "
 
2070
                                                "~s~n~s~n", 
 
2071
                                                [Id, EC, Reason, Resp]),
 
2072
                                      exit({bad_resp,Req,Resp});
 
2073
                                  Crap ->
 
2074
                                      io:format("[~w] bad response: ~p", 
 
2075
                                                [Id, Crap]),
 
2076
                                      exit({bad_resp, Req, Crap})
 
2077
                              end
 
2078
                      end),
 
2079
              MRef = erlang:monitor(process, Pid),
 
2080
              timer:sleep(10 + random:uniform(1334)),
 
2081
              {Id, Pid, MRef}
 
2082
 
 
2083
      end,
 
2084
      lists:seq(1, NumClients)).
 
2085
 
 
2086
%% wait_for_clients(Clients) ->
 
2087
%%     lists:foreach(
 
2088
%%       fun({Id, Pid, MRef}) ->
 
2089
%%            io:format("waiting for client ~w termination~n", [Id]),
 
2090
%%            receive
 
2091
%%                {'DOWN', MRef, process, Pid, normal} ->
 
2092
%%                    io:format("waiting for clients: "
 
2093
%%                              "normal exit from ~w (~p)~n", 
 
2094
%%                              [Id, Pid]),
 
2095
%%                    ok;
 
2096
%%                {'DOWN', MRef, process, Pid, Reason} ->
 
2097
%%                    io:format("waiting for clients: "
 
2098
%%                              "unexpected exit from ~w (~p):"
 
2099
%%                              "~n   Reason: ~p"
 
2100
%%                              "~n", [Id, Pid, Reason]),
 
2101
%%                    erlang:error(Reason)
 
2102
%%            end
 
2103
%%       end,
 
2104
%%       Clients).
 
2105
 
 
2106
 
 
2107
wait4clients([], _Timeout) ->
 
2108
    ok;
 
2109
wait4clients(Clients, Timeout) when Timeout > 0 ->
 
2110
    io:format("wait4clients -> entry with"
 
2111
              "~n   length(Clients): ~w"
 
2112
              "~n   Timeout:         ~w"
 
2113
              "~n", [length(Clients), Timeout]),
 
2114
    T = t(),
 
2115
    receive
 
2116
        {'DOWN', _MRef, process, Pid, normal} ->
 
2117
            case lists:keysearch(Pid, 2, Clients) of
 
2118
                {value, {Id, _, _}} ->
 
2119
                    io:format("receive normal exit message "
 
2120
                              "from client ~p (~p)", [Id, Pid]),
 
2121
                    NewClients = 
 
2122
                        lists:keydelete(Id, 1, Clients),
 
2123
                    wait4clients(NewClients, 
 
2124
                                 Timeout - (t() - T));
 
2125
                false ->
 
2126
                    io:format("receive normal exit message "
 
2127
                              "from unknown process: ~p", [Pid]),
 
2128
                    wait4clients(Clients, Timeout - (t() - T))
 
2129
            end;
 
2130
 
 
2131
        {'DOWN', _MRef, process, Pid, Reason} ->
 
2132
            case lists:keysearch(Pid, 2, Clients) of
 
2133
                {value, {Id, _, _}} ->
 
2134
                    io:format("receive bad exit message "
 
2135
                              "from client ~p (~p):"
 
2136
                              "~n   ~p", [Id, Pid, Reason]),
 
2137
                    erlang:error({bad_client_termination, Id, Reason});
 
2138
                false ->
 
2139
                    io:format("receive normal exit message "
 
2140
                              "from unknown process: ~p", [Pid]),
 
2141
                    wait4clients(Clients, Timeout - (t() - T))
 
2142
            end
 
2143
 
 
2144
    after Timeout ->
 
2145
            erlang:error({client_timeout, Clients})  
 
2146
    end;
 
2147
wait4clients(Clients, _) ->
 
2148
    erlang:error({client_timeout, Clients}).
 
2149
                    
 
2150
                    
 
2151
%% Time in milli seconds
 
2152
t() ->
 
2153
    {A,B,C} = erlang:now(),
 
2154
    A*1000000000+B*1000+(C div 1000).
 
2155
 
 
2156
 
 
2157
%% -----------------------------------------------------
 
2158
%% Webserver part:
 
2159
%% Implements a web server that sends responses one character
 
2160
%% at a time, with random delays between the characters.
 
2161
 
 
2162
start_slow_server(SeqNumServer) ->
 
2163
    io:format("start slow server when"
 
2164
              "~n   SeqNumServer: ~w"
 
2165
              "~n", [SeqNumServer]),
 
2166
    proc_lib:start(
 
2167
      erlang, apply, [fun() -> init_slow_server(SeqNumServer) end, []]).
 
2168
 
 
2169
init_slow_server(SeqNumServer) ->
 
2170
    io:format("[webserver ~w] init slow server"
 
2171
              "~n", [SeqNumServer]),
 
2172
    {ok, LSock} = gen_tcp:listen(0, [binary, {packet,0}, {active,true},
 
2173
                                     {backlog, 100}]),
 
2174
    io:format("[webserver ~w] LSock: ~p"
 
2175
              "~n", [SeqNumServer, LSock]),
 
2176
    {ok, {_IP, Port}} = inet:sockname(LSock),
 
2177
    io:format("[webserver ~w] Port: ~w"
 
2178
              "~n", [SeqNumServer, Port]),
 
2179
    proc_lib:init_ack({ok, self(), Port}),
 
2180
    loop_slow_server(LSock, SeqNumServer).
 
2181
 
 
2182
loop_slow_server(LSock, SeqNumServer) ->
 
2183
    io:format("[webserver ~w] entry with"
 
2184
              "~n   LSock: ~p"
 
2185
              "~n", [SeqNumServer, LSock]),
 
2186
    Master = self(),
 
2187
    Acceptor = proc_lib:spawn(
 
2188
                 fun() -> client_handler(Master, LSock, SeqNumServer) end),
 
2189
    io:format("[webserver ~w] acceptor started"
 
2190
              "~n   Acceptor: ~p"
 
2191
              "~n", [SeqNumServer, Acceptor]),
 
2192
    receive
 
2193
        {accepted, Acceptor} ->
 
2194
            io:format("[webserver ~w] accepted"
 
2195
                      "~n", [SeqNumServer]),
 
2196
            loop_slow_server(LSock, SeqNumServer);
 
2197
        shutdown ->
 
2198
            gen_tcp:close(LSock),
 
2199
            exit(Acceptor, kill)
 
2200
    end.
 
2201
 
 
2202
 
 
2203
%% Handle one client connection
 
2204
client_handler(Master, LSock, SeqNumServer) ->
 
2205
    io:format("[acceptor ~w] await accept"
 
2206
              "~n", [SeqNumServer]),
 
2207
    {ok, CSock} = gen_tcp:accept(LSock),
 
2208
    io:format("[acceptor ~w] accepted"
 
2209
              "~n   CSock: ~p"
 
2210
              "~n", [SeqNumServer, CSock]),
 
2211
    Master ! {accepted, self()},
 
2212
    set_random_seed(),
 
2213
    loop_client(1, CSock, SeqNumServer).
 
2214
 
 
2215
loop_client(N, CSock, SeqNumServer) ->
 
2216
    %% Await request, don't bother parsing it too much,
 
2217
    %% assuming the entire request arrives in one packet.
 
2218
    io:format("[acceptor ~w] await request"
 
2219
              "~n   N: ~p"
 
2220
              "~n", [SeqNumServer, N]),
 
2221
    receive
 
2222
        {tcp, CSock, Req} ->
 
2223
            ReqNum = parse_req_num(Req),
 
2224
            RespSeqNum = get_next_sequence_number(SeqNumServer),
 
2225
            Response = f("~s->resp~3..0w/~2..0w", [ReqNum, RespSeqNum, N]),
 
2226
            Txt = f("Slow server (~p) got ~p, answering with ~p",
 
2227
                    [self(), Req, Response]),
 
2228
            io:format("~s...~n", [Txt]),
 
2229
            slowly_send_response(CSock, Response),
 
2230
            case parse_connection_type(Req) of
 
2231
                keep_alive ->
 
2232
                    io:format("~s...done~n", [Txt]),
 
2233
                    loop_client(N+1, CSock, SeqNumServer);
 
2234
                close ->
 
2235
                    io:format("~s...done (closing)~n", [Txt]),
 
2236
                    gen_tcp:close(CSock)
 
2237
            end
 
2238
    end.
 
2239
 
 
2240
slowly_send_response(CSock, Answer) ->
 
2241
    Response = f("HTTP/1.1 200 OK\r\nContent-Length: ~w\r\n\r\n~s",
 
2242
                 [length(Answer), Answer]),
 
2243
    lists:foreach(
 
2244
      fun(Char) ->
 
2245
              timer:sleep(random:uniform(500)),
 
2246
              gen_tcp:send(CSock, <<Char>>)
 
2247
      end,
 
2248
      Response).
 
2249
 
 
2250
parse_req_num(Request) ->
 
2251
    Opts = [caseless,{capture,all_but_first,list}],
 
2252
    {match, [ReqNum]} = re:run(Request, "GET /(.*) HTTP", Opts),
 
2253
    ReqNum.
 
2254
 
 
2255
parse_connection_type(Request) ->
 
2256
    Opts = [caseless,{capture,all_but_first,list}],
 
2257
    {match,[CType]} = re:run(Request, "connection: *(keep-alive|close)", Opts),
 
2258
    case string:to_lower(CType) of
 
2259
        "close" -> close;
 
2260
        "keep-alive" -> keep_alive
 
2261
    end.
 
2262
 
 
2263
 
 
2264
set_random_seed() ->
 
2265
    {_, _, Micros} = now(),
 
2266
    A = erlang:phash2([make_ref(), self(), Micros]),
 
2267
    random:seed(A, A, A).
 
2268
 
 
2269
f(F, A) -> lists:flatten(io_lib:format(F,A)).
 
2270
 
 
2271
 
 
2272
 
 
2273
 
 
2274
%%-------------------------------------------------------------------------
 
2275
 
 
2276
 
 
2277
 
 
2278
otp_8106_pid(doc) ->
 
2279
    ["OTP-8106 - deliver reply info using \"other\" pid"];
 
2280
otp_8106_pid(suite) ->
 
2281
    [];
 
2282
otp_8106_pid(Config) when is_list(Config) ->
 
2283
    case ?config(local_server, Config) of 
 
2284
        ok ->
 
2285
            ReceiverPid = create_receiver(pid),
 
2286
            Receiver    = ReceiverPid, 
 
2287
            
 
2288
            otp8106(ReceiverPid, Receiver, Config), 
 
2289
 
 
2290
            stop_receiver(ReceiverPid), 
 
2291
            
 
2292
            ok;
 
2293
        _ ->
 
2294
            {skip, "Failed to start local http-server"}
 
2295
    end.  
 
2296
 
 
2297
 
 
2298
otp_8106_fun(doc) ->
 
2299
    ["OTP-8106 - deliver reply info using fun"];
 
2300
otp_8106_fun(suite) ->
 
2301
    [];
 
2302
otp_8106_fun(Config) when is_list(Config) ->
 
2303
    case ?config(local_server, Config) of 
 
2304
        ok ->
 
2305
            ReceiverPid = create_receiver(function),
 
2306
            Receiver = otp_8106_deliver_fun(ReceiverPid), 
 
2307
            
 
2308
            otp8106(ReceiverPid, Receiver, Config), 
 
2309
 
 
2310
            stop_receiver(ReceiverPid), 
 
2311
            
 
2312
            ok;
 
2313
        _ ->
 
2314
            {skip, "Failed to start local http-server"}
 
2315
    end.  
 
2316
 
 
2317
 
 
2318
otp_8106_mfa(doc) ->
 
2319
    ["OTP-8106 - deliver reply info using mfa callback"];
 
2320
otp_8106_mfa(suite) ->
 
2321
    [];
 
2322
otp_8106_mfa(Config) when is_list(Config) ->
 
2323
    case ?config(local_server, Config) of 
 
2324
        ok ->
 
2325
            ReceiverPid = create_receiver(mfa),
 
2326
            Receiver    = {?MODULE, otp_8106_deliver, [mfa, ReceiverPid]}, 
 
2327
            
 
2328
            otp8106(ReceiverPid, Receiver, Config), 
 
2329
 
 
2330
            stop_receiver(ReceiverPid), 
 
2331
            
 
2332
            ok;
 
2333
        _ ->
 
2334
            {skip, "Failed to start local http-server"}
 
2335
    end.  
 
2336
 
 
2337
 
 
2338
 otp8106(ReceiverPid, Receiver, Config) ->
 
2339
     Port        = ?config(local_port, Config),
 
2340
     URL         = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
2341
     Request     = {URL, []}, 
 
2342
     HTTPOptions = [], 
 
2343
     Options     = [{sync, false}, {receiver, Receiver}], 
 
2344
 
 
2345
     {ok, RequestId} = 
 
2346
         httpc:request(get, Request, HTTPOptions, Options),
 
2347
 
 
2348
     Body = 
 
2349
         receive 
 
2350
             {reply, ReceiverPid, {RequestId, {{_, 200, _}, _, B}}} ->
 
2351
                 B;
 
2352
             {reply, ReceiverPid, Msg} ->
 
2353
                 tsf(Msg);
 
2354
             {bad_reply, ReceiverPid, Msg} ->
 
2355
                 tsf(Msg)
 
2356
         end,
 
2357
 
 
2358
     inets_test_lib:check_body(binary_to_list(Body)),
 
2359
     ok.
 
2360
 
 
2361
 
 
2362
create_receiver(Type) ->
 
2363
    Parent = self(), 
 
2364
    Receiver = fun() -> receiver(Type, Parent) end,
 
2365
    spawn_link(Receiver).
 
2366
 
 
2367
stop_receiver(Pid) ->
 
2368
    Pid ! {stop, self()}.
 
2369
 
 
2370
receiver(Type, Parent) ->
 
2371
    receive
 
2372
        {stop, Parent} ->
 
2373
            exit(normal);
 
2374
 
 
2375
        {http, ReplyInfo} when (Type =:= pid) ->
 
2376
            Parent ! {reply, self(), ReplyInfo},
 
2377
            receiver(Type, Parent);
 
2378
 
 
2379
        {Type, ReplyInfo} ->
 
2380
            Parent ! {reply, self(), ReplyInfo},
 
2381
            receiver(Type, Parent);
 
2382
        
 
2383
        Crap ->
 
2384
            Parent ! {reply, self(), {bad_reply, Crap}},
 
2385
            receiver(Type, Parent)
 
2386
    end.
 
2387
 
 
2388
 
 
2389
otp_8106_deliver_fun(ReceiverPid) ->
 
2390
    fun(ReplyInfo) -> otp_8106_deliver(ReplyInfo, function, ReceiverPid) end.
 
2391
             
 
2392
otp_8106_deliver(ReplyInfo, Type, ReceiverPid) -> 
 
2393
    ReceiverPid ! {Type, ReplyInfo},
 
2394
    ok.
 
2395
 
 
2396
 
 
2397
 
 
2398
%%-------------------------------------------------------------------------
 
2399
 
 
2400
otp_8056(doc) ->
 
2401
    "OTP-8056";
 
2402
otp_8056(suite) ->
 
2403
    [];
 
2404
otp_8056(Config) when is_list(Config) ->
 
2405
    Method      = get,
 
2406
    Port        = ?config(local_port, Config),
 
2407
    URL         = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
2408
    Request     = {URL, []}, 
 
2409
    HTTPOptions = [], 
 
2410
    Options1    = [{sync, true}, {stream, {self, once}}], 
 
2411
    Options2    = [{sync, true}, {stream, self}], 
 
2412
    {error, streaming_error} = httpc:request(Method, Request, 
 
2413
                                             HTTPOptions, Options1), 
 
2414
    tsp("request 1 failed as expected"),
 
2415
    {error, streaming_error} = httpc:request(Method, Request, 
 
2416
                                             HTTPOptions, Options2), 
 
2417
    tsp("request 2 failed as expected"),
 
2418
    ok.
 
2419
 
 
2420
 
 
2421
%%-------------------------------------------------------------------------
 
2422
 
 
2423
otp_8352(doc) ->
 
2424
    "OTP-8352";
 
2425
otp_8352(suite) ->
 
2426
    [];
 
2427
otp_8352(Config) when is_list(Config) ->
 
2428
    tsp("otp_8352 -> entry with"
 
2429
        "~n   Config: ~p", [Config]),
 
2430
    case ?config(local_server, Config) of 
 
2431
        ok ->
 
2432
            tsp("local-server running"),
 
2433
 
 
2434
            tsp("initial profile info(1): ~p", [httpc:info()]),
 
2435
            
 
2436
            MaxSessions      = 5,
 
2437
            MaxKeepAlive     = 10, 
 
2438
            KeepAliveTimeout = timer:minutes(2), 
 
2439
            ConnOptions = [{max_sessions,          MaxSessions}, 
 
2440
                           {max_keep_alive_length, MaxKeepAlive}, 
 
2441
                           {keep_alive_timeout,    KeepAliveTimeout}], 
 
2442
            httpc:set_options(ConnOptions), 
 
2443
 
 
2444
            Method       = get, 
 
2445
            Port         = ?config(local_port, Config),
 
2446
            URL          = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
2447
            Request      = {URL, []}, 
 
2448
            Timeout      = timer:seconds(1), 
 
2449
            ConnTimeout  = Timeout + timer:seconds(1), 
 
2450
            HttpOptions1 = [{timeout, Timeout}, {connect_timeout, ConnTimeout}], 
 
2451
            Options1     = [{socket_opts, [{tos,    87}, 
 
2452
                                           {recbuf, 16#FFFF}, 
 
2453
                                           {sndbuf, 16#FFFF}]}], 
 
2454
            case httpc:request(Method, Request, HttpOptions1, Options1) of
 
2455
                {ok, {{_,200,_}, [_ | _], ReplyBody1 = [_ | _]}} ->
 
2456
                    %% equivaliant to httpc:request(get, {URL, []}, [], []),
 
2457
                    inets_test_lib:check_body(ReplyBody1);
 
2458
                {ok, UnexpectedReply1} ->
 
2459
                    tsf({unexpected_reply, UnexpectedReply1});
 
2460
                {error, _} = Error1 ->
 
2461
                    tsf({bad_reply, Error1})
 
2462
            end,
 
2463
 
 
2464
            tsp("profile info (2): ~p", [httpc:info()]),
 
2465
 
 
2466
            HttpOptions2 = [], 
 
2467
            Options2     = [{socket_opts, [{tos,    84}, 
 
2468
                                           {recbuf, 32#1FFFF}, 
 
2469
                                           {sndbuf, 32#1FFFF}]}], 
 
2470
            case httpc:request(Method, Request, HttpOptions2, Options2) of
 
2471
                {ok, {{_,200,_}, [_ | _], ReplyBody2 = [_ | _]}} ->
 
2472
                    %% equivaliant to httpc:request(get, {URL, []}, [], []),
 
2473
                    inets_test_lib:check_body(ReplyBody2);
 
2474
                {ok,  UnexpectedReply2} ->
 
2475
                    tsf({unexpected_reply, UnexpectedReply2});
 
2476
                {error, _} = Error2 ->
 
2477
                    tsf({bad_reply, Error2})
 
2478
            end,
 
2479
            tsp("profile info (3): ~p", [httpc:info()]),
 
2480
            ok;
 
2481
 
 
2482
        _ ->
 
2483
            {skip, "Failed to start local http-server"}
 
2484
    end.  
 
2485
 
 
2486
 
 
2487
%%-------------------------------------------------------------------------
 
2488
 
 
2489
otp_8371(doc) ->
 
2490
    ["OTP-8371"];
 
2491
otp_8371(suite) ->
 
2492
    [];
 
2493
otp_8371(Config) when is_list(Config) ->
 
2494
    ok = httpc:set_options([{ipv6, disabled}]), % also test the old option 
 
2495
    {DummyServerPid, Port} = dummy_server(self(), ipv4),
 
2496
    
 
2497
    URL = ?URL_START ++ integer_to_list(Port) ++ 
 
2498
        "/ensure_host_header_with_port.html",
 
2499
        
 
2500
    case httpc:request(get, {URL, []}, [], []) of
 
2501
        {ok, Result} ->
 
2502
            case Result of
 
2503
                {{_, 200, _}, _Headers, Body} ->
 
2504
                    tsp("expected response with"
 
2505
                        "~n   Body: ~p", [Body]),
 
2506
                    ok;
 
2507
                {StatusLine, Headers, Body} ->
 
2508
                    tsp("expected response with"
 
2509
                        "~n   StatusLine: ~p"
 
2510
                        "~n   Headers:    ~p"
 
2511
                        "~n   Body:       ~p", [StatusLine, Headers, Body]),
 
2512
                    tsf({unexpected_result, 
 
2513
                         [{status_line, StatusLine}, 
 
2514
                          {headers,     Headers}, 
 
2515
                          {body,        Body}]});
 
2516
                _ ->
 
2517
                    tsf({unexpected_result, Result})
 
2518
            end;
 
2519
        Error ->
 
2520
            tsf({request_failed, Error})
 
2521
    end,
 
2522
 
 
2523
    DummyServerPid ! stop,
 
2524
    ok = httpc:set_options([{ipv6, enabled}]),   
 
2525
    ok.
 
2526
 
 
2527
 
 
2528
%%-------------------------------------------------------------------------
 
2529
 
 
2530
otp_8739(doc) ->
 
2531
    ["OTP-8739"];
 
2532
otp_8739(suite) ->
 
2533
    [];
 
2534
otp_8739(Config) when is_list(Config) ->
 
2535
    {_DummyServerPid, Port} = otp_8739_dummy_server(),
 
2536
    URL = ?URL_START ++ integer_to_list(Port) ++ "/dummy.html",
 
2537
    Method      = get,
 
2538
    Request     = {URL, []}, 
 
2539
    HttpOptions = [{connect_timeout, 500}, {timeout, 1}], 
 
2540
    Options     = [{sync, true}], 
 
2541
    case http:request(Method, Request, HttpOptions, Options) of
 
2542
        {error, timeout} ->
 
2543
            %% And now we check the size of the handler db
 
2544
            Info = httpc:info(),
 
2545
            tsp("Info: ~p", [Info]),
 
2546
            {value, {handlers, Handlers}} = 
 
2547
                lists:keysearch(handlers, 1, Info),
 
2548
            case Handlers of
 
2549
                [] ->
 
2550
                    ok;
 
2551
                _ ->
 
2552
                    tsf({unexpected_handlers, Handlers})
 
2553
            end;
 
2554
        Unexpected ->
 
2555
            tsf({unexpected, Unexpected})
 
2556
    end.
 
2557
 
 
2558
 
 
2559
otp_8739_dummy_server() ->
 
2560
    Parent = self(), 
 
2561
    Pid = spawn_link(fun() -> otp_8739_dummy_server_init(Parent) end),
 
2562
    receive
 
2563
        {port, Port} ->
 
2564
            {Pid, Port}
 
2565
    end.
 
2566
 
 
2567
otp_8739_dummy_server_init(Parent) ->
 
2568
    {ok, ListenSocket} = 
 
2569
        gen_tcp:listen(0, [binary, inet, {packet, 0},
 
2570
                           {reuseaddr,true},
 
2571
                           {active, false}]),
 
2572
    {ok, Port} = inet:port(ListenSocket),
 
2573
    Parent ! {port, Port},
 
2574
    otp_8739_dummy_server_main(Parent, ListenSocket).
 
2575
 
 
2576
otp_8739_dummy_server_main(Parent, ListenSocket) ->
 
2577
    case gen_tcp:accept(ListenSocket) of
 
2578
        {ok, Sock} ->
 
2579
            %% Ignore the request, and simply wait for the socket to close
 
2580
            receive
 
2581
                {tcp_closed, Sock} ->
 
2582
                    (catch gen_tcp:close(ListenSocket)),
 
2583
                    exit(normal);
 
2584
                {tcp_error, Sock, Reason} ->
 
2585
                    tsp("socket error: ~p", [Reason]),
 
2586
                    (catch gen_tcp:close(ListenSocket)),
 
2587
                    exit(normal)
 
2588
            after 10000 ->
 
2589
                    %% Just in case
 
2590
                    (catch gen_tcp:close(Sock)),
 
2591
                    (catch gen_tcp:close(ListenSocket)),
 
2592
                    exit(timeout)
 
2593
            end;
 
2594
        Error ->
 
2595
            exit(Error)
 
2596
    end.
 
2597
 
 
2598
                       
 
2599
    
 
2600
%%--------------------------------------------------------------------
 
2601
%% Internal functions
 
2602
%%--------------------------------------------------------------------
 
2603
setup_server_dirs(ServerRoot, DocRoot, DataDir) ->   
 
2604
    ConfDir = filename:join(ServerRoot, "conf"),
 
2605
    CgiDir =  filename:join(ServerRoot, "cgi-bin"),
 
2606
    ok = file:make_dir(ServerRoot),
 
2607
    ok = file:make_dir(DocRoot),
 
2608
    ok = file:make_dir(ConfDir),
 
2609
    ok = file:make_dir(CgiDir),
 
2610
 
 
2611
    {ok, Files} = file:list_dir(DataDir),
 
2612
    
 
2613
    lists:foreach(fun(File) -> case lists:suffix(".html", File) of
 
2614
                                   true ->
 
2615
                                       inets_test_lib:copy_file(File, 
 
2616
                                                                DataDir, 
 
2617
                                                                DocRoot);
 
2618
                                   false ->
 
2619
                                       ok
 
2620
                               end
 
2621
                  end, Files),
 
2622
    
 
2623
    Cgi = case test_server:os_type() of
 
2624
              {win32, _} ->
 
2625
                  "cgi_echo.exe";
 
2626
              _ ->
 
2627
                  "cgi_echo"
 
2628
          end,
 
2629
    
 
2630
    inets_test_lib:copy_file(Cgi, DataDir, CgiDir),
 
2631
    inets_test_lib:copy_file("mime.types", DataDir, ConfDir).
 
2632
 
 
2633
create_config(FileName, ComType, Port, PrivDir, ServerRoot, DocRoot, 
 
2634
              SSLDir) ->
 
2635
    MaxHdrSz     = io_lib:format("~p", [256]),
 
2636
    MaxHdrAct    = io_lib:format("~p", [close]),
 
2637
    SSL =
 
2638
        case ComType of
 
2639
            ssl ->
 
2640
                [cline(["SSLCertificateFile ", 
 
2641
                        filename:join(SSLDir, "ssl_server_cert.pem")]),
 
2642
                 cline(["SSLCertificateKeyFile ",
 
2643
                        filename:join(SSLDir, "ssl_server_cert.pem")]),
 
2644
                 cline(["SSLVerifyClient 0"])];
 
2645
            _ ->
 
2646
                []
 
2647
        end,
 
2648
 
 
2649
    Mod_order = "Modules mod_alias mod_auth mod_esi mod_actions mod_cgi" 
 
2650
        " mod_include mod_dir mod_get mod_head" 
 
2651
        " mod_log mod_disk_log mod_trace",
 
2652
            
 
2653
    HttpConfig = [
 
2654
                  cline(["Port ", integer_to_list(Port)]),
 
2655
                  cline(["ServerName ", "httpc_test"]),
 
2656
                  cline(["SocketType ", atom_to_list(ComType)]),
 
2657
                  cline([Mod_order]),
 
2658
                  cline(["ServerRoot ", ServerRoot]),
 
2659
                  cline(["DocumentRoot ", DocRoot]),
 
2660
                  cline(["MaxHeaderSize ",MaxHdrSz]),
 
2661
                  cline(["MaxHeaderAction ",MaxHdrAct]),
 
2662
                  cline(["DirectoryIndex ", "index.html "]),
 
2663
                  cline(["DefaultType ", "text/plain"]),
 
2664
                  cline(["ScriptAlias /cgi-bin/ ", 
 
2665
                         filename:join(ServerRoot, "cgi-bin"), "/"]),
 
2666
                  SSL],
 
2667
    ConfigFile = filename:join([PrivDir,FileName]),
 
2668
    {ok, Fd} = file:open(ConfigFile, [write]),
 
2669
    ok = file:write(Fd, lists:flatten(HttpConfig)),
 
2670
    ok = file:close(Fd).
 
2671
 
 
2672
cline(List) ->
 
2673
    lists:flatten([List, "\r\n"]).
 
2674
 
 
2675
is_proxy_available(Proxy, Port) ->
 
2676
    case gen_tcp:connect(Proxy, Port, []) of
 
2677
        {ok, Socket} ->
 
2678
            gen_tcp:close(Socket),
 
2679
            true;
 
2680
        _ ->
 
2681
            false
 
2682
    end.
 
2683
 
 
2684
receive_streamed_body(RequestId, Body) ->
 
2685
    receive 
 
2686
        {http, {RequestId, stream, BinBodyPart}} ->
 
2687
            receive_streamed_body(RequestId, 
 
2688
                                  <<Body/binary, BinBodyPart/binary>>);
 
2689
        {http, {RequestId, stream_end, _Headers}} ->
 
2690
            Body;
 
2691
        {http, Msg} ->      
 
2692
            test_server:fail(Msg)
 
2693
    end.
 
2694
 
 
2695
receive_streamed_body(RequestId, Body, Pid) ->
 
2696
    httpc:stream_next(Pid),
 
2697
    test_server:format("~p:receive_streamed_body -> requested next stream ~n", [?MODULE]),
 
2698
    receive 
 
2699
        {http, {RequestId, stream, BinBodyPart}} ->
 
2700
            receive_streamed_body(RequestId, 
 
2701
                                  <<Body/binary, BinBodyPart/binary>>, 
 
2702
                                  Pid);
 
2703
        {http, {RequestId, stream_end, _Headers}} ->
 
2704
            Body;
 
2705
        {http, Msg} ->      
 
2706
            test_server:fail(Msg)
 
2707
    end.
 
2708
 
 
2709
 
 
2710
 
 
2711
dummy_server(Caller, IpV) ->
 
2712
    Pid = spawn(httpc_SUITE, dummy_server_init, [Caller, IpV]),
 
2713
    receive
 
2714
        {port, Port} ->
 
2715
            {Pid, Port}
 
2716
    end.
 
2717
 
 
2718
dummy_server_init(Caller, IpV) ->
 
2719
    {ok, ListenSocket} = 
 
2720
        case IpV of 
 
2721
            ipv4 ->
 
2722
                gen_tcp:listen(0, [binary, inet, {packet, 0},
 
2723
                                   {reuseaddr,true},
 
2724
                                   {active, false}]);
 
2725
            ipv6 ->
 
2726
                gen_tcp:listen(0, [binary, inet6, {packet, 0},
 
2727
                                   {reuseaddr,true},
 
2728
                                   {active, false}])
 
2729
        end,
 
2730
    {ok, Port} = inet:port(ListenSocket),
 
2731
    tsp("dummy_server_init -> Port: ~p", [Port]),
 
2732
    Caller ! {port, Port},
 
2733
    dummy_server_loop({httpd_request, parse, [?HTTP_MAX_HEADER_SIZE]},
 
2734
                      [], ListenSocket).
 
2735
 
 
2736
dummy_server_loop(MFA, Handlers, ListenSocket) ->
 
2737
    receive
 
2738
        stop ->
 
2739
            lists:foreach(fun(Handler) -> Handler ! stop end, Handlers)
 
2740
    after 0 ->
 
2741
            {ok, Socket} = gen_tcp:accept(ListenSocket),
 
2742
            HandlerPid  = dummy_request_handler(MFA, Socket),
 
2743
            gen_tcp:controlling_process(Socket, HandlerPid),
 
2744
            HandlerPid ! controller,
 
2745
            dummy_server_loop(MFA, [HandlerPid | Handlers],
 
2746
                              ListenSocket)
 
2747
    end.
 
2748
 
 
2749
dummy_request_handler(MFA, Socket) ->
 
2750
    spawn(httpc_SUITE, dummy_request_handler_init, [MFA, Socket]).
 
2751
 
 
2752
dummy_request_handler_init(MFA, Socket) ->
 
2753
    receive 
 
2754
        controller ->
 
2755
            inet:setopts(Socket, [{active, true}])
 
2756
    end,
 
2757
    dummy_request_handler_loop(MFA, Socket).
 
2758
    
 
2759
dummy_request_handler_loop({Module, Function, Args}, Socket) ->
 
2760
    tsp("dummy_request_handler_loop -> entry with"
 
2761
        "~n   Module:   ~p"
 
2762
        "~n   Function: ~p"
 
2763
        "~n   Args:     ~p", [Module, Function, Args]),
 
2764
    receive 
 
2765
        {tcp, _, Data} ->
 
2766
            tsp("dummy_request_handler_loop -> Data ~p", [Data]),
 
2767
            case handle_request(Module, Function, [Data | Args], Socket) of
 
2768
                stop ->
 
2769
                    gen_tcp:close(Socket);
 
2770
                NewMFA ->
 
2771
                    dummy_request_handler_loop(NewMFA, Socket)
 
2772
            end;
 
2773
        stop ->
 
2774
            gen_tcp:close(Socket)
 
2775
    end.
 
2776
 
 
2777
handle_request(Module, Function, Args, Socket) ->
 
2778
    tsp("handle_request -> entry with"
 
2779
        "~n   Module:   ~p"
 
2780
        "~n   Function: ~p"
 
2781
        "~n   Args:     ~p", [Module, Function, Args]),
 
2782
    case Module:Function(Args) of
 
2783
        {ok, Result} ->
 
2784
            tsp("handle_request -> ok"
 
2785
                "~n   Result: ~p", [Result]),
 
2786
            case (catch handle_http_msg(Result, Socket)) of
 
2787
                stop ->
 
2788
                    stop;
 
2789
                <<>> ->
 
2790
                    tsp("handle_request -> empty data"),
 
2791
                    {httpd_request, parse, [[<<>>, ?HTTP_MAX_HEADER_SIZE]]};
 
2792
                Data -> 
 
2793
                    handle_request(httpd_request, parse, 
 
2794
                                   [Data |[?HTTP_MAX_HEADER_SIZE]], Socket)
 
2795
            end;
 
2796
        NewMFA ->
 
2797
            tsp("handle_request -> "
 
2798
                "~n   NewMFA: ~p", [NewMFA]),
 
2799
            NewMFA
 
2800
    end.
 
2801
 
 
2802
handle_http_msg({_, RelUri, _, {_, Headers}, Body}, Socket) ->
 
2803
    tsp("handle_http_msg -> entry with: "
 
2804
        "~n   RelUri:  ~p"
 
2805
        "~n   Headers: ~p"
 
2806
        "~n   Body:    ~p", [RelUri, Headers, Body]),
 
2807
    NextRequest = 
 
2808
        case RelUri of
 
2809
            "/dummy_headers.html" ->
 
2810
                <<>>;
 
2811
            "/no_headers.html" ->
 
2812
                stop;
 
2813
            "/just_close.html" ->
 
2814
                stop;
 
2815
            _ ->
 
2816
                ContentLength = content_length(Headers),    
 
2817
                case size(Body) - ContentLength of
 
2818
                    0 ->
 
2819
                        <<>>;
 
2820
                    _ ->
 
2821
                        <<_BodyThisReq:ContentLength/binary, 
 
2822
                          Next/binary>> = Body,
 
2823
                        Next
 
2824
                end
 
2825
        end,
 
2826
   
 
2827
    tsp("handle_http_msg -> NextRequest: ~p", [NextRequest]),
 
2828
    case (catch ets:lookup(cookie, cookies)) of 
 
2829
        [{cookies, true}]->
 
2830
            tsp("handle_http_msg -> check cookies ~p", []),
 
2831
            check_cookie(Headers);
 
2832
        _ ->
 
2833
            ok
 
2834
    end,
 
2835
    
 
2836
    DefaultResponse = "HTTP/1.1 200 ok\r\n" ++
 
2837
        "Content-Length:32\r\n\r\n"
 
2838
        "<HTML><BODY>foobar</BODY></HTML>",
 
2839
 
 
2840
    Msg = 
 
2841
        case RelUri of
 
2842
            "/just_close.html" ->
 
2843
                close; 
 
2844
            "/no_content.html" ->
 
2845
                "HTTP/1.0 204 No Content\r\n\r\n";
 
2846
            "/no_headers.html" ->
 
2847
                "HTTP/1.0 200 OK\r\n\r\nTEST";
 
2848
            "/ensure_host_header_with_port.html" ->
 
2849
                %% tsp("handle_http_msg -> validate host with port"),
 
2850
                case ensure_host_header_with_port(Headers) of
 
2851
                    true ->
 
2852
                        B = 
 
2853
                            "<HTML><BODY>" ++ 
 
2854
                            "host with port" ++ 
 
2855
                            "</BODY></HTML>", 
 
2856
                        Len = integer_to_list(length(B)), 
 
2857
                        "HTTP/1.1 200 ok\r\n" ++
 
2858
                            "Content-Length:" ++ Len ++ "\r\n\r\n" ++ B;
 
2859
                    false ->
 
2860
                        B = 
 
2861
                            "<HTML><BODY>" ++ 
 
2862
                            "Internal Server Error - host without port" ++
 
2863
                            "</BODY></HTML>", 
 
2864
                        Len = integer_to_list(length(B)), 
 
2865
                        "HTTP/1.1 500 Internal Server Error\r\n" ++
 
2866
                            "Content-Length:" ++ Len ++ "\r\n\r\n" ++ B
 
2867
                end;
 
2868
            "/300.html" ->
 
2869
                NewUri = ?URL_START ++
 
2870
                    integer_to_list(?IP_PORT) ++ "/dummy.html",
 
2871
                "HTTP/1.1 300 Multiple Choices\r\n" ++
 
2872
                    "Location:" ++ NewUri ++  "\r\n" ++
 
2873
                    "Content-Length:0\r\n\r\n";
 
2874
            "/301.html" ->
 
2875
                NewUri = ?URL_START ++
 
2876
                    integer_to_list(?IP_PORT) ++ "/dummy.html",
 
2877
                "HTTP/1.1 301 Moved Permanently\r\n" ++
 
2878
                    "Location:" ++ NewUri ++  "\r\n" ++
 
2879
                    "Content-Length:80\r\n\r\n" ++
 
2880
                    "<HTML><BODY><a href=" ++ NewUri ++
 
2881
                    ">New place</a></BODY></HTML>";
 
2882
            "/302.html" ->
 
2883
                NewUri = ?URL_START ++
 
2884
                    integer_to_list(?IP_PORT) ++ "/dummy.html",
 
2885
                "HTTP/1.1 302 Found \r\n" ++
 
2886
                    "Location:" ++ NewUri ++  "\r\n" ++
 
2887
                    "Content-Length:80\r\n\r\n" ++
 
2888
                    "<HTML><BODY><a href=" ++ NewUri ++
 
2889
                    ">New place</a></BODY></HTML>";
 
2890
            "/307.html" ->
 
2891
                NewUri = ?URL_START ++
 
2892
                    integer_to_list(?IP_PORT) ++ "/dummy.html",
 
2893
                "HTTP/1.1 307 Temporary Rediect \r\n" ++
 
2894
                    "Location:" ++ NewUri ++  "\r\n" ++
 
2895
                    "Content-Length:80\r\n\r\n" ++
 
2896
                    "<HTML><BODY><a href=" ++ NewUri ++
 
2897
                    ">New place</a></BODY></HTML>";
 
2898
            "/500.html" ->
 
2899
                "HTTP/1.1 500 Internal Server Error\r\n" ++
 
2900
                    "Content-Length:47\r\n\r\n" ++
 
2901
                    "<HTML><BODY>Internal Server Error</BODY></HTML>";
 
2902
            "/503.html" ->
 
2903
                case ets:lookup(unavailable, 503) of
 
2904
                    [{503, unavailable}] -> 
 
2905
                        ets:insert(unavailable, {503, available}),
 
2906
                        "HTTP/1.1 503 Service Unavailable\r\n" ++
 
2907
                            "Retry-After:5\r\n" ++
 
2908
                            "Content-Length:47\r\n\r\n" ++
 
2909
                            "<HTML><BODY>Internal Server Error</BODY></HTML>";
 
2910
                    [{503, available}]   ->
 
2911
                        DefaultResponse;
 
2912
                    [{503, long_unavailable}]  ->
 
2913
                        "HTTP/1.1 503 Service Unavailable\r\n" ++
 
2914
                            "Retry-After:120\r\n" ++
 
2915
                            "Content-Length:47\r\n\r\n" ++
 
2916
                            "<HTML><BODY>Internal Server Error</BODY></HTML>"
 
2917
                end;
 
2918
            "/redirectloop.html" -> %% Create a potential endless loop!
 
2919
                {ok, Port} = inet:port(Socket),
 
2920
                NewUri = ?URL_START ++
 
2921
                    integer_to_list(Port) ++ "/redirectloop.html",
 
2922
                "HTTP/1.1 300 Multiple Choices\r\n" ++
 
2923
                    "Location:" ++ NewUri ++  "\r\n" ++
 
2924
                    "Content-Length:0\r\n\r\n";
 
2925
            "/userinfo.html" ->
 
2926
                Challange = "HTTP/1.1 401 Unauthorized \r\n" ++
 
2927
                    "WWW-Authenticate:Basic" ++"\r\n" ++
 
2928
                    "Content-Length:0\r\n\r\n",
 
2929
                case auth_header(Headers) of
 
2930
                    {ok, Value} ->
 
2931
                        handle_auth(Value, Challange, DefaultResponse);
 
2932
                    _ ->
 
2933
                        Challange
 
2934
                end;
 
2935
            "/dummy_headers.html" ->
 
2936
                %% The client will only care about the Transfer-Encoding
 
2937
                %% header the rest of these headers are left to the
 
2938
                %% user to evaluate. This is not a valid response 
 
2939
                %% it only tests that the header handling code works.
 
2940
                Head = "HTTP/1.1 200 ok\r\n" ++
 
2941
                    "Content-Length:32\r\n" ++
 
2942
                    "Pragma:1#no-cache\r\n"  ++
 
2943
                    "Via:1.0 fred, 1.1 nowhere.com (Apache/1.1)\r\n"  ++
 
2944
                    "Warning:1#pseudonym foobar\r\n"  ++
 
2945
                    "Vary:*\r\n"  ++
 
2946
                    "Trailer:Other:inets_test\r\n"  ++
 
2947
                    "Upgrade:HTTP/2.0\r\n"  ++
 
2948
                    "Age:4711\r\n" ++ 
 
2949
                    "Transfer-Encoding:chunked\r\n" ++
 
2950
                    "Content-Encoding:foo\r\n" ++
 
2951
                    "Content-Language:en\r\n"  ++
 
2952
                    "Content-Location:http://www.foobar.se\r\n"  ++
 
2953
                    "Content-MD5:104528739076276072743283077410617235478\r\n" 
 
2954
                    ++
 
2955
                    "Content-Range:Sat, 29 Oct 1994 19:43:31 GMT\r\n"  ++
 
2956
                    "Expires:Sat, 29 Oct 1994 19:43:31 GMT\r\n"  ++
 
2957
                    "Proxy-Authenticate:#1Basic"  ++
 
2958
                    "\r\n\r\n",
 
2959
                gen_tcp:send(Socket, Head),
 
2960
                gen_tcp:send(Socket, http_chunk:encode("<HTML><BODY>fo")),
 
2961
                gen_tcp:send(Socket, http_chunk:encode("obar</BODY></HTML>")),
 
2962
                http_chunk:encode_last();
 
2963
            "/capital_transfer_encoding.html" ->
 
2964
                Head =  "HTTP/1.1 200 ok\r\n" ++
 
2965
                    "Transfer-Encoding:Chunked\r\n\r\n",
 
2966
                gen_tcp:send(Socket, Head),
 
2967
                gen_tcp:send(Socket, http_chunk:encode("<HTML><BODY>fo")),
 
2968
                gen_tcp:send(Socket, http_chunk:encode("obar</BODY></HTML>")),
 
2969
                http_chunk:encode_last();
 
2970
            "/cookie.html" ->
 
2971
                "HTTP/1.1 200 ok\r\n" ++
 
2972
                    "set-cookie:" ++ "test_cookie=true; path=/;" ++
 
2973
                    "max-age=60000\r\n" ++
 
2974
                    "Content-Length:32\r\n\r\n"++
 
2975
                    "<HTML><BODY>foobar</BODY></HTML>";
 
2976
            "/missing_crlf.html" ->
 
2977
                "HTTP/1.1 200 ok" ++
 
2978
                    "Content-Length:32\r\n" ++
 
2979
                    "<HTML><BODY>foobar</BODY></HTML>";
 
2980
            "/wrong_statusline.html" ->
 
2981
                "ok 200 HTTP/1.1\r\n\r\n" ++
 
2982
                    "Content-Length:32\r\n\r\n" ++
 
2983
                    "<HTML><BODY>foobar</BODY></HTML>";
 
2984
            "/once_chunked.html" ->
 
2985
                Head =  "HTTP/1.1 200 ok\r\n" ++
 
2986
                    "Transfer-Encoding:Chunked\r\n\r\n",
 
2987
                gen_tcp:send(Socket, Head),
 
2988
                gen_tcp:send(Socket, http_chunk:encode("<HTML><BODY>fo")),
 
2989
                gen_tcp:send(Socket, 
 
2990
                             http_chunk:encode("obar</BODY></HTML>")),
 
2991
                http_chunk:encode_last();
 
2992
            "/once.html" ->
 
2993
                Head =  "HTTP/1.1 200 ok\r\n" ++
 
2994
                    "Content-Length:32\r\n\r\n", 
 
2995
                gen_tcp:send(Socket, Head), 
 
2996
                gen_tcp:send(Socket, "<HTML><BODY>fo"),
 
2997
                test_server:sleep(1000),
 
2998
                gen_tcp:send(Socket, "ob"),
 
2999
                test_server:sleep(1000),
 
3000
                gen_tcp:send(Socket, "ar</BODY></HTML>");
 
3001
            "/invalid_http.html" ->
 
3002
                "HTTP/1.1 301\r\nDate:Sun, 09 Dec 2007 13:04:18 GMT\r\n" ++ 
 
3003
                    "Transfer-Encoding:chunked\r\n\r\n";
 
3004
            "/missing_reason_phrase.html" ->
 
3005
                "HTTP/1.1 200\r\n" ++
 
3006
                    "Content-Length: 32\r\n\r\n"
 
3007
                    "<HTML><BODY>foobar</BODY></HTML>";
 
3008
            "/missing_CR.html" ->
 
3009
                "HTTP/1.1 200 ok\n" ++
 
3010
                    "Content-Length:32\r\n\n"
 
3011
                    "<HTML><BODY>foobar</BODY></HTML>";
 
3012
            _ ->
 
3013
                DefaultResponse
 
3014
        end,
 
3015
    
 
3016
    tsp("handle_http_msg -> Msg: ~p", [Msg]),
 
3017
    case Msg of
 
3018
        ok ->
 
3019
            %% Previously, this resulted in an {error, einval}. Now what?
 
3020
            ok;
 
3021
        close ->
 
3022
            %% Nothing to send, just close
 
3023
            gen_tcp:close(Socket);
 
3024
        _ when is_list(Msg) orelse is_binary(Msg) ->
 
3025
            gen_tcp:send(Socket, Msg)
 
3026
    end,
 
3027
    tsp("handle_http_msg -> done"),
 
3028
    NextRequest.
 
3029
 
 
3030
ensure_host_header_with_port([]) ->
 
3031
    false;
 
3032
ensure_host_header_with_port(["host: " ++ Host| _]) ->
 
3033
    case string:tokens(Host, [$:]) of
 
3034
        [ActualHost, Port] ->
 
3035
            tsp("ensure_host_header_with_port -> "
 
3036
                "~n   ActualHost: ~p"
 
3037
                "~n   Port:       ~p", [ActualHost, Port]),
 
3038
            true;
 
3039
        _ ->
 
3040
            false
 
3041
    end;
 
3042
ensure_host_header_with_port([_|T]) ->
 
3043
    ensure_host_header_with_port(T).
 
3044
 
 
3045
auth_header([]) ->
 
3046
    auth_header_not_found;
 
3047
auth_header(["authorization:" ++ Value | _]) ->
 
3048
    {ok, string:strip(Value)};
 
3049
auth_header([_ | Tail]) ->
 
3050
    auth_header(Tail).
 
3051
 
 
3052
handle_auth("Basic " ++ UserInfo, Challange, DefaultResponse) ->
 
3053
    case string:tokens(base64:decode_to_string(UserInfo), ":") of
 
3054
        ["alladin", "sesame"] = Auth ->
 
3055
            test_server:format("Auth: ~p~n", [Auth]),
 
3056
            DefaultResponse;
 
3057
        Other ->
 
3058
            test_server:format("UnAuth: ~p~n", [Other]),
 
3059
            Challange
 
3060
    end.
 
3061
 
 
3062
check_cookie([]) ->
 
3063
    test_server:fail(no_cookie_header);
 
3064
check_cookie(["cookie:" ++ _Value | _]) ->
 
3065
    ok;
 
3066
check_cookie([_Head | Tail]) ->
 
3067
   check_cookie(Tail).
 
3068
 
 
3069
content_length([]) ->
 
3070
    0;
 
3071
content_length(["content-length:" ++ Value | _]) ->
 
3072
    list_to_integer(string:strip(Value));
 
3073
content_length([_Head | Tail]) ->
 
3074
   content_length(Tail).
 
3075
 
 
3076
provocate_not_modified_bug(Url) ->
 
3077
    Timeout = 15000, %% 15s should be plenty
 
3078
 
 
3079
    {ok, {{_, 200, _}, ReplyHeaders, _Body}} =
 
3080
        httpc:request(get, {Url, []}, [{timeout, Timeout}], []),
 
3081
    Etag = pick_header(ReplyHeaders, "ETag"),
 
3082
    Last = pick_header(ReplyHeaders, "last-modified"),
 
3083
    
 
3084
    case httpc:request(get, {Url, [{"If-None-Match", Etag},
 
3085
                                  {"If-Modified-Since", Last}]},
 
3086
                      [{timeout, 15000}],
 
3087
                      []) of
 
3088
        {ok, {{_, 304, _}, _, _}} -> %% The expected reply
 
3089
            page_unchanged;
 
3090
        {ok, {{_, 200, _}, _, _}} -> 
 
3091
            %% If the page has changed since the        
 
3092
            %% last request we retry to
 
3093
            %% trigger the bug
 
3094
            provocate_not_modified_bug(Url);
 
3095
        {error, timeout} ->
 
3096
            %% Not what we expected. Tcpdump can be used to
 
3097
            %% verify that we receive the complete http-reply
 
3098
            %% but still time out.
 
3099
            incorrect_result
 
3100
    end.
 
3101
 
 
3102
pick_header(Headers, Name) ->
 
3103
    case lists:keysearch(string:to_lower(Name), 1,
 
3104
                         [{string:to_lower(X), Y} || {X, Y} <- Headers]) of
 
3105
        false ->
 
3106
            [];
 
3107
        {value, {_Key, Val}} ->
 
3108
            Val
 
3109
    end.
 
3110
 
 
3111
 
 
3112
not_implemented_yet() ->
 
3113
    exit(not_implemented_yet).
 
3114
 
 
3115
 
 
3116
p(F) ->
 
3117
    p(F, []).
 
3118
 
 
3119
p(F, A) ->
 
3120
    io:format("~p ~w:" ++ F ++ "~n", [self(), ?MODULE | A]).
 
3121
 
 
3122
tsp(F) ->
 
3123
    tsp(F, []).
 
3124
tsp(F, A) ->
 
3125
    test_server:format("~p ~p:" ++ F ++ "~n", [self(), ?MODULE | A]).
 
3126
 
 
3127
tsf(Reason) ->
 
3128
    test_server:fail(Reason).