Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
6121-inets-httpc_SUITE-refactor.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 6121-inets-httpc_SUITE-refactor.patch of Package erlang
From 07fdbd64c2cd34d9518d178397d0b1de206d2f9a Mon Sep 17 00:00:00 2001 From: Jakub Witczak <kuba@erlang.org> Date: Thu, 6 Apr 2023 17:40:47 +0200 Subject: [PATCH 1/4] inets: httpc_SUITE refactor --- lib/inets/test/http_test_lib.erl | 1 + lib/inets/test/httpc_SUITE.erl | 107 +++++++++++++----------------- lib/inets/test/inets_test_lib.erl | 1 + lib/inets/test/make_certs.erl | 1 + 4 files changed, 49 insertions(+), 61 deletions(-) diff --git a/lib/inets/test/http_test_lib.erl b/lib/inets/test/http_test_lib.erl index f647370f01..f307f8d713 100644 --- a/lib/inets/test/http_test_lib.erl +++ b/lib/inets/test/http_test_lib.erl @@ -27,6 +27,7 @@ %% Note: This directive should only be used in test suites. -compile(export_all). +-compile(nowarn_export_all). -define(SOCKET_BACKLOG, 100). dummy_server(SocketType, Inet, Extra) -> diff --git a/lib/inets/test/httpc_SUITE.erl b/lib/inets/test/httpc_SUITE.erl index 9e43deb598..b9ccbff3ec 100644 --- a/lib/inets/test/httpc_SUITE.erl +++ b/lib/inets/test/httpc_SUITE.erl @@ -73,7 +73,8 @@ groups() -> %% process_leak_on_keepalive is depending on stream_fun_server_close %% and it shall be the last test case in the suite otherwise cookie %% will fail. - {sim_http, [], only_simulated() ++ server_closing_connection() ++ [process_leak_on_keepalive]}, + {sim_http, [], only_simulated() ++ server_closing_connection() ++ + [process_leak_on_keepalive]}, {http_internal, [], real_requests_esi()}, {http_unix_socket, [], simulated_unix_socket()}, {https, [], real_requests()}, @@ -221,6 +222,7 @@ sim_mixed() -> %%-------------------------------------------------------------------- init_per_suite(Config) -> + logger:set_primary_config(level, warning), PrivDir = proplists:get_value(priv_dir, Config), DataDir = proplists:get_value(data_dir, Config), inets_test_lib:start_apps([inets]), @@ -241,8 +243,6 @@ init_per_group(misc = Group, Config) -> Inet = inet_version(), ok = httpc:set_options([{ipfamily, Inet}]), Config; - - init_per_group(Group, Config0) when Group =:= sim_https; Group =:= https; Group =:= sim_mixed -> catch crypto:stop(), @@ -290,7 +290,7 @@ end_per_group(http_unix_socket, Config) -> %% it, dummy server waits in gen_tcp:accept and will not process stop request httpc:request(get, {"http://localhost/v1/kv/foo", []}, [], []), receive - {stopped, DummyServerPid} -> + {stopped, _DummyServerPid} -> ok end, file:delete(?UNIX_SOCKET), @@ -384,19 +384,15 @@ end_per_testcase(Case, Config) httpc:request(url(group_name(Config), "/just_close.html", Config)), ok; true -> - ct:pal("Not cleaning up because test case status was ~p", [Status]), + ct:log("Not cleaning up because test case status was ~p", [Status]), ok end; - end_per_testcase(_Case, _Config) -> ok. - - %%-------------------------------------------------------------------- %% Test Cases -------------------------------------------------------- %%-------------------------------------------------------------------- - head() -> [{doc, "Test http head request against local server."}]. @@ -1055,7 +1051,7 @@ bad_response(Config) when is_list(Config) -> {error, timeout} = httpc:request(get, {URL0, []}, [{timeout, 400}], []), {error, Reason} = httpc:request(URL1), - ct:print("Wrong Statusline: ~p~n", [Reason]). + ct:log("Wrong Statusline: ~p~n", [Reason]). %%------------------------------------------------------------------------- timeout_redirect() -> @@ -1104,7 +1100,7 @@ invalid_http(Config) when is_list(Config) -> {error, {could_not_parse_as_http, _} = Reason} = httpc:request(get, {URL, []}, [], []), - ct:print("Parse error: ~p ~n", [Reason]). + ct:log("Parse error: ~p ~n", [Reason]). %%------------------------------------------------------------------------- @@ -1119,7 +1115,7 @@ invalid_chunk_size(Config) when is_list(Config) -> {error, {chunk_size, _} = Reason} = httpc:request(get, {URL, []}, [], []), - ct:print("Parse error: ~p ~n", [Reason]). + ct:log("Parse error: ~p ~n", [Reason]). %%------------------------------------------------------------------------- @@ -1147,7 +1143,7 @@ relaxed(Config) when is_list(Config) -> {error, Reason} = httpc:request(get, {URL, []}, [{relaxed, false}], []), - ct:print("Not relaxed: ~p~n", [Reason]), + ct:log("Not relaxed: ~p~n", [Reason]), {ok, {{_, 200, _}, [_ | _], [_ | _]}} = httpc:request(get, {URL, []}, [{relaxed, true}], []). @@ -1395,7 +1391,7 @@ binary_url(Config) -> %%------------------------------------------------------------------------- -iolist_body(Config) -> +iolist_body(_Config) -> {ok, ListenSocket} = gen_tcp:listen(0, [{active,once}, binary]), {ok,{_,Port}} = inet:sockname(ListenSocket), @@ -1593,7 +1589,7 @@ timeout_memory_leak(Config) when is_list(Config) -> {error, timeout} -> %% And now we check the size of the handler db Info = httpc:info(), - ct:print("Info: ~p", [Info]), + ct:log("Info: ~p", [Info]), {value, {handlers, Handlers}} = lists:keysearch(handlers, 1, Info), case Handlers of @@ -1786,7 +1782,7 @@ stream_fun_server_close(Config) when is_list(Config) -> {ok, RequestId} = httpc:request(get, Request, [], [{sync, false}, {receiver, Fun}]), receive {RequestId, {error, Reason}} -> - ct:pal("Close ~p", [Reason]), + ct:log("Close ~p", [Reason]), ok after 13000 -> ct:fail(did_not_receive_close) @@ -2005,12 +2001,12 @@ url(https, End, Config) -> Port = proplists:get_value(port, Config), {ok,Host} = inet:gethostname(), ?TLS_URL_START ++ Host ++ ":" ++ integer_to_list(Port) ++ End; -url(sim_http, End, Config) -> - url(http, End, Config); -url(http_internal, End, Config) -> +url(Group, End, Config) when Group == sim_http; + Group == http_internal -> url(http, End, Config); url(sim_https, End, Config) -> url(https, End, Config). + url(http, UserInfo, End, Config) -> Port = proplists:get_value(port, Config), ?URL_START ++ UserInfo ++ integer_to_list(Port) ++ End; @@ -2075,39 +2071,29 @@ server_start(_, HttpdConfig) -> {value, {_, _, Info}} = lists:keysearch(Pid, 2, Serv), proplists:get_value(port, Info). -server_config(http, Config) -> +server_config(base, Config) -> ServerRoot = proplists:get_value(server_root, Config), [{port, 0}, {server_name,"httpc_test"}, {server_root, ServerRoot}, {document_root, proplists:get_value(doc_root, Config)}, - {bind_address, any}, - {ipfamily, inet_version()}, - {mime_type, "text/plain"}, - {script_alias, {"/cgi-bin/", filename:join(ServerRoot, "cgi-bin") ++ "/"}} - ]; -server_config(http_ipv6, Config) -> + {mime_type, "text/plain"}]; +server_config(base_http, Config) -> ServerRoot = proplists:get_value(server_root, Config), - [{port, 0}, - {server_name,"httpc_test"}, - {server_root, ServerRoot}, - {document_root, proplists:get_value(doc_root, Config)}, - {bind_address, {0,0,0,0,0,0,0,1}}, - {ipfamily, inet6}, - {mime_type, "text/plain"}, - {script_alias, {"/cgi-bin/", filename:join(ServerRoot, "cgi-bin") ++ "/"}} - ]; + server_config(base, Config) ++ + [{script_alias, + {"/cgi-bin/", filename:join(ServerRoot, "cgi-bin") ++ "/"}}]; +server_config(http, Config) -> + server_config(base_http, Config) ++ + [{bind_address, any}, + {ipfamily, inet_version()}]; +server_config(http_ipv6, Config) -> + server_config(base_http, Config) ++ + [{bind_address, {0,0,0,0,0,0,0,1}}, + {ipfamily, inet6}]; server_config(http_internal, Config) -> - ServerRoot = proplists:get_value(server_root, Config), - [{port, 0}, - {server_name,"httpc_test"}, - {server_root, ServerRoot}, - {document_root, proplists:get_value(doc_root, Config)}, - {bind_address, any}, - {ipfamily, inet_version()}, - {mime_type, "text/plain"}, - {erl_script_alias, {"", [httpc_SUITE]}} - ]; + server_config(http, Config) ++ + [{erl_script_alias, {"", [httpc_SUITE]}}]; server_config(https, Config) -> [{socket_type, {essl, ssl_config(Config)}} | server_config(http, Config)]; server_config(sim_https, Config) -> @@ -2115,7 +2101,6 @@ server_config(sim_https, Config) -> server_config(http_unix_socket, _Config) -> Socket = ?UNIX_SOCKET, [{unix_socket, Socket}]; - server_config(_, _) -> []. @@ -2184,7 +2169,7 @@ keep_alive_requests(Request, Profile) -> httpc:request(get, Request, [], [{sync, false}], Profile), ok = httpc:cancel_request(RequestIdB1, Profile), - ct:print("Cancel ~p~n", [RequestIdB1]), + ct:log("Cancel ~p~n", [RequestIdB1]), receive_replys([RequestIdB0, RequestIdB2]). @@ -2352,7 +2337,7 @@ handle_request(Module, Function, Args, Socket) -> end. handle_http_msg({Method, RelUri, _, {_, Headers}, Body}, Socket, _) -> - ct:print("Request: ~p ~p", [Method, RelUri]), + ct:log("Request: ~p ~p", [Method, RelUri]), NextRequest = case RelUri of @@ -2399,9 +2384,9 @@ handle_http_msg({Method, RelUri, _, {_, Headers}, Body}, Socket, _) -> _ when is_list(Msg) orelse is_binary(Msg) -> case Msg of [] -> - ct:print("Empty Msg", []); + ct:log("Empty Msg", []); _ -> - ct:print("Response: ~p", [Msg]), + ct:log("Response: ~p", [Msg]), send(Socket, Msg) end end, @@ -2461,10 +2446,10 @@ content_type_header([_|T]) -> handle_auth("Basic " ++ UserInfo, Challenge, DefaultResponse) -> case string:tokens(base64:decode_to_string(UserInfo), ":") of ["alladin", "sesame"] = Auth -> - ct:print("Auth: ~p~n", [Auth]), + ct:log("Auth: ~p~n", [Auth]), DefaultResponse; Other -> - ct:print("UnAuth: ~p~n", [Other]), + ct:log("UnAuth: ~p~n", [Other]), Challenge end. @@ -2977,7 +2962,7 @@ receive_streamed_body(RequestId, Body) -> receive_streamed_body(RequestId, Body, Pid) -> httpc:stream_next(Pid), - ct:print("~p:receive_streamed_body -> requested next stream ~n", [?MODULE]), + ct:log("~p:receive_streamed_body -> requested next stream ~n", [?MODULE]), receive {http, {RequestId, stream, BinBodyPart}} -> %% Make sure the httpc hasn't sent us the next 'stream' @@ -3033,19 +3018,19 @@ run_clients(NumClients, ServerPort, SeqNumServer) -> fun() -> case httpc:request(Url) of {ok, {{_,200,_}, _, Resp}} -> - ct:print("[~w] 200 response: " + ct:log("[~w] 200 response: " "~p~n", [Id, Resp]), case lists:prefix(Req++"->", Resp) of true -> exit(normal); false -> exit({bad_resp,Req,Resp}) end; {ok, {{_,EC,Reason},_,Resp}} -> - ct:print("[~w] ~w response: " + ct:pal("[~w] ~w response: " "~s~n~s~n", [Id, EC, Reason, Resp]), exit({bad_resp,Req,Resp}); Crap -> - ct:print("[~w] bad response: ~p", + ct:pal("[~w] bad response: ~p", [Id, Crap]), exit({bad_resp, Req, Crap}) end @@ -3123,14 +3108,14 @@ loop_client(N, CSock, SeqNumServer) -> Response = lists:flatten(io_lib:format("~s->resp~3..0w/~2..0w", [ReqNum, RespSeqNum, N])), Txt = lists:flatten(io_lib:format("Slow server (~p) got ~p, answering with ~p", [self(), Req, Response])), - ct:print("~s...~n", [Txt]), + ct:log("~s...~n", [Txt]), slowly_send_response(CSock, Response), case parse_connection_type(Req) of keep_alive -> - ct:print("~s...done~n", [Txt]), + ct:log("~s...done~n", [Txt]), loop_client(N+1, CSock, SeqNumServer); close -> - ct:print("~s...done (closing)~n", [Txt]), + ct:log("~s...done (closing)~n", [Txt]), gen_tcp:close(CSock) end end. @@ -3180,7 +3165,7 @@ otp_8739(Config) when is_list(Config) -> {error, timeout} -> %% And now we check the size of the handler db Info = httpc:info(), - ct:print("Info: ~p", [Info]), + ct:log("Info: ~p", [Info]), {value, {handlers, Handlers}} = lists:keysearch(handlers, 1, Info), case Handlers of @@ -3247,7 +3232,7 @@ receive_stream_n(Ref, N) -> {http, {Ref, stream_start, _}} -> receive_stream_n(Ref, N); {http, {Ref,stream, Data}} -> - ct:pal("Data: ~p", [Data]), + ct:log("Data: ~p", [Data]), receive_stream_n(Ref, N-1) end. diff --git a/lib/inets/test/inets_test_lib.erl b/lib/inets/test/inets_test_lib.erl index c5c292cf4f..324832ca21 100644 --- a/lib/inets/test/inets_test_lib.erl +++ b/lib/inets/test/inets_test_lib.erl @@ -26,6 +26,7 @@ %% Note: This directive should only be used in test suites. -compile(export_all). +-compile(nowarn_export_all). %% -- Misc os command and stuff diff --git a/lib/inets/test/make_certs.erl b/lib/inets/test/make_certs.erl index 7215a59823..71f508fc61 100644 --- a/lib/inets/test/make_certs.erl +++ b/lib/inets/test/make_certs.erl @@ -20,6 +20,7 @@ -module(make_certs). -compile([export_all]). +-compile(nowarn_export_all). %-export([all/1, all/2, rootCA/2, intermediateCA/3, endusers/3, enduser/3, revoke/3, gencrl/2, verify/3]). -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor