Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
  • Loading branch information
u3s committed Aug 16, 2023
2 parents c5e33cf + 43664f8 commit b5e045c
Show file tree
Hide file tree
Showing 5 changed files with 115 additions and 116 deletions.
75 changes: 39 additions & 36 deletions lib/inets/test/httpc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ all() ->

groups() ->
[
{http, [], real_requests()},
{http, [parallel], real_requests()},
{http_ipv6, [], [request_options]},
%% process_leak_on_keepalive is depending on stream_fun_server_close
%% and it shall be the last test case in the suite otherwise cookie
Expand All @@ -80,8 +80,8 @@ groups() ->
{http_unix_socket, [], simulated_unix_socket()},
{https, [], [def_ssl_opt | real_requests()]},
{sim_https, [], only_simulated()},
{misc, [], misc()},
{sim_mixed, [], sim_mixed()}
{misc, [parallel], misc()},
{sim_mixed, [parallel], sim_mixed()}
].

real_requests()->
Expand Down Expand Up @@ -347,13 +347,13 @@ init_per_testcase(pipeline, Config) ->
httpc:set_options([{pipeline_timeout, 50000},
{max_pipeline_length, 3}], pipeline),

Config;
[{profile, pipeline} | Config];
init_per_testcase(persistent_connection, Config) ->
inets:start(httpc, [{profile, persistent}]),
inets:start(httpc, [{profile, persistent_connection}]),
httpc:set_options([{keep_alive_timeout, 50000},
{max_keep_alive_length, 3}], persistent),

Config;
[{profile, persistent_connection} | Config];
init_per_testcase(Case, Config) when Case == wait_for_whole_response;
Case == remote_socket_close_parallel ->
ct:timetrap({seconds, 60*3}),
Expand All @@ -364,13 +364,16 @@ init_per_testcase(Case, Config) when Case == post;
Case == post_stream ->
ct:timetrap({seconds, 30}),
Config;
init_per_testcase(Case, Config) when Case == timeout_memory_leak ->
{ok, _Pid} = inets:start(httpc, [{profile, Case}]),
[{profile, Case} | Config];
init_per_testcase(_Case, Config) ->
Config.

end_per_testcase(pipeline, _Config) ->
inets:stop(httpc, pipeline);
end_per_testcase(persistent_connection, _Config) ->
inets:stop(httpc, persistent);
end_per_testcase(Case, Config) when Case == timeout_memory_leak;
Case == pipeline;
Case == persistent_connection ->
inets:stop(httpc, ?config(profile, Config));
end_per_testcase(Case, Config)
when Case == server_closing_connection_on_first_response;
Case == server_closing_connection_on_second_response ->
Expand Down Expand Up @@ -562,11 +565,11 @@ pipeline(Config) when is_list(Config) ->

persistent_connection(Config) when is_list(Config) ->
Request = {url(group_name(Config), "/dummy.html", Config), []},
{ok, _} = httpc:request(get, Request, [?SSL_NO_VERIFY], [], persistent),
{ok, _} = httpc:request(get, Request, [?SSL_NO_VERIFY], [], persistent_connection),

%% Make sure pipeline session is registered
ct:sleep(4000),
keep_alive_requests(Request, persistent).
keep_alive_requests(Request, persistent_connection).

%%-------------------------------------------------------------------------
async() ->
Expand Down Expand Up @@ -868,18 +871,17 @@ cookie(Config) when is_list(Config) ->
{ok, {{_,200,_}, [_ | _], [_|_]}}
= httpc:request(get, Request0, [?SSL_NO_VERIFY], []),

%% Populate table to be used by the "dummy" server
ets:new(cookie, [named_table, public, set]),
ets:insert(cookie, {cookies, true}),

Request1 = {url(group_name(Config), "/", Config), []},

{ok, {{_,200,_}, [_ | _], [_|_]}}
= httpc:request(get, Request1, [?SSL_NO_VERIFY], []),
{ok, {{_,200,_}, [_ | _], [_|_]}} = global:trans(
{cookies, verify},
fun() -> httpc:request(get, Request1, [?SSL_NO_VERIFY], []) end,
[node()],
100
),

[{session_cookies, [_|_]}] = httpc:which_cookies(httpc:default_profile()),

ets:delete(cookie),
ok = httpc:set_options([{cookies, disabled}]).


Expand All @@ -896,16 +898,15 @@ cookie_profile(Config) when is_list(Config) ->
{ok, {{_,200,_}, [_ | _], [_|_]}}
= httpc:request(get, Request0, [?SSL_NO_VERIFY], [], cookie_test),

%% Populate table to be used by the "dummy" server
ets:new(cookie, [named_table, public, set]),
ets:insert(cookie, {cookies, true}),

Request1 = {url(group_name(Config), "/", Config), []},

{ok, {{_,200,_}, [_ | _], [_|_]}}
= httpc:request(get, Request1, [?SSL_NO_VERIFY], [], cookie_test),
{ok, {{_,200,_}, [_ | _], [_|_]}} = global:trans(
{cookies, verify},
fun() -> httpc:request(get, Request1, [?SSL_NO_VERIFY], [], cookie_test) end,
[node()],
100
),

ets:delete(cookie),
inets:stop(httpc, cookie_test).

%%-------------------------------------------------------------------------
Expand Down Expand Up @@ -1553,8 +1554,8 @@ inet_opts(Config) when is_list(Config) ->
httpc:set_options(ConnOptions),

Request = {url(group_name(Config), "/dummy.html", Config), []},
Timeout = timer:seconds(1),
ConnTimeout = Timeout + timer:seconds(1),
Timeout = timer:seconds(5),
ConnTimeout = Timeout + timer:seconds(5),
HttpOptions = [{timeout, Timeout}, {connect_timeout, ConnTimeout}, ?SSL_NO_VERIFY],
Options0 = [{socket_opts, [{tos, 87},
{recbuf, 16#FFFF},
Expand Down Expand Up @@ -1594,12 +1595,13 @@ timeout_memory_leak() ->
[{doc, "Check OTP-8739"}].
timeout_memory_leak(Config) when is_list(Config) ->
{_DummyServerPid, Port} = otp_8739_dummy_server(),
{ok,Host} = inet:gethostname(),
{ok, Host} = inet:gethostname(),
Request = {?URL_START ++ Host ++ ":" ++ integer_to_list(Port) ++ "/dummy.html", []},
case httpc:request(get, Request, [{connect_timeout, 500}, {timeout, 1}], [{sync, true}]) of
Profile = ?config(profile, Config),
case httpc:request(get, Request, [{connect_timeout, 500}, {timeout, 1}], [{sync, true}], Profile) of
{error, timeout} ->
%% And now we check the size of the handler db
Info = httpc:info(),
Info = httpc:info(Profile),
ct:log("Info: ~p", [Info]),
{value, {handlers, Handlers}} =
lists:keysearch(handlers, 1, Info),
Expand Down Expand Up @@ -2450,11 +2452,12 @@ handle_http_msg({Method, RelUri, _, {_, Headers}, Body}, Socket, _) ->
end
end,

case (catch ets:lookup(cookie, cookies)) of
[{cookies, true}]->
check_cookie(Headers);
_ ->
ok
case global:trans({cookies, verify}, fun() -> unset end, [node()], 0) of
aborted->
% somebody has the lock and wants us to check
check_cookie(Headers);
unset ->
ok
end,

{ok, {_, Port}} = sockname(Socket),
Expand Down
Loading

0 comments on commit b5e045c

Please sign in to comment.