Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
6761-inets-Do-not-print-test-progress-logs-to-t...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 6761-inets-Do-not-print-test-progress-logs-to-terminal.patch of Package erlang
From ef8d5b4c69f637d7e1cc76b4e6d127be5dcc1d5f Mon Sep 17 00:00:00 2001 From: Johannes Christ <jc@jchri.st> Date: Sat, 23 Sep 2023 15:12:01 +0200 Subject: [PATCH] inets: Do not print test progress logs to terminal The motivation here is to rely on the Common Test HTML logs to store and contain these logs and keep the terminal clean of output that cannot be attributed to specific running test cases, allowing Common Test to supply wanted logging information on the terminal. Related to #7375. --- lib/inets/test/httpc_SUITE.erl | 16 ++++++++-------- lib/inets/test/httpd_SUITE.erl | 6 +++--- lib/inets/test/httpd_bench_SUITE.erl | 6 +++--- lib/inets/test/httpd_test_lib.erl | 2 +- lib/inets/test/inets_socketwrap_SUITE.erl | 8 ++++---- lib/inets/test/inets_test_lib.erl | 2 +- 6 files changed, 20 insertions(+), 20 deletions(-) diff --git a/lib/inets/test/httpc_SUITE.erl b/lib/inets/test/httpc_SUITE.erl index de4d9329ec..03eb9cdc07 100644 --- a/lib/inets/test/httpc_SUITE.erl +++ b/lib/inets/test/httpc_SUITE.erl @@ -1964,25 +1964,25 @@ loop(Cnt, Acc, Config) -> _ -> %% queue is expected to be empty queue_check(), - ct:pal("~n~s|", [Acc ++ "x"]), + ct:log("~n~s|", [Acc ++ "x"]), fail end; {ok, NotOk} -> - ct:pal("200 OK was not received~n~p", [NotOk]), + ct:log("200 OK was not received~n~p", [NotOk]), fail; Error -> - ct:pal("Error: ~p",[Error]), + ct:log("Error: ~p",[Error]), fail end. queue_check() -> receive {http, {ReqId, {_Result, _Head, Data}}} when is_binary(Data) -> - ct:pal("Unexpected data received: ~p ", + ct:log("Unexpected data received: ~p ", [ReqId]), queue_check(); X -> - ct:pal("Caught unexpected something else: ~p",[X]), + ct:log("Caught unexpected something else: ~p",[X]), queue_check() after 5000 -> done @@ -2272,7 +2272,7 @@ receive_replys([ID|IDs]) -> {http, {ID, {{_, 200, _}, [_|_], _}}} -> receive_replys(IDs); {http, {Other, {{_, 200, _}, [_|_], _}}} -> - ct:pal("~p",[{recived_canceld_id, Other}]) + ct:log("~p",[{recived_canceld_id, Other}]) end. @@ -2978,12 +2978,12 @@ run_clients(NumClients, ServerPort, SeqNumServer) -> false -> exit({bad_resp,Req,Resp}) end; {ok, {{_,EC,Reason},_,Resp}} -> - ct:pal("[~w] ~w response: " + ct:log("[~w] ~w response: " "~s~n~s~n", [Id, EC, Reason, Resp]), exit({bad_resp,Req,Resp}); Crap -> - ct:pal("[~w] bad response: ~p", + ct:log("[~w] bad response: ~p", [Id, Crap]), exit({bad_resp, Req, Crap}) end diff --git a/lib/inets/test/httpd_SUITE.erl b/lib/inets/test/httpd_SUITE.erl index 4a9f01baf1..4ebd191aed 100644 --- a/lib/inets/test/httpd_SUITE.erl +++ b/lib/inets/test/httpd_SUITE.erl @@ -579,7 +579,7 @@ verify_href(Config) when is_list(Config) -> Version = proplists:get_value(http_version, Config), Host = proplists:get_value(host, Config), Go = fun(Path, User, Password, Opts) -> - ct:pal("Navigating to ~p", [Path]), + ct:log("Navigating to ~p", [Path]), auth_status(auth_request(Path, User, Password, Version, Host), Config, Opts) end, @@ -1658,7 +1658,7 @@ non_disturbing(Config) when is_list(Config)-> Transport = type(Type), receive {Transport, Socket, Msg} -> - ct:pal("Received message ~p~n", [Msg]), + ct:log("Received message ~p~n", [Msg]), ok after 2000 -> ct:fail(timeout) @@ -2087,7 +2087,7 @@ server_config(http_limit, Config) -> {disable_chunked_transfer_encoding_send, true}, %% Make sure option checking code is run {max_content_length, 100000002}] ++ server_config(http, Config), - ct:pal("Received message ~p~n", [Conf]), + ct:log("Received message ~p~n", [Conf]), Conf; server_config(http_custom, Config) -> [{customize, ?MODULE}] ++ server_config(http, Config); diff --git a/lib/inets/test/httpd_bench_SUITE.erl b/lib/inets/test/httpd_bench_SUITE.erl index 85cd67f18e..a723039ff0 100644 --- a/lib/inets/test/httpd_bench_SUITE.erl +++ b/lib/inets/test/httpd_bench_SUITE.erl @@ -88,7 +88,7 @@ init_per_suite(Config) -> init_ssl(Config), [{iter, 10}, {server_node, Node}, {server_host, Host} | Config] catch E:R:ST -> - ct:pal("~p:~p:~p",[E,R,ST]), + ct:log("~p:~p:~p",[E,R,ST]), {skipped, "Benchmark machines only"} end. @@ -306,7 +306,7 @@ run_test(Client, File, Config) -> Pid ! go, receive {Pid,{{tps, Tps}, {mbps, MBps}}} -> - ct:pal("Tps: ~p Bps~p", [Tps, MBps]), + ct:log("Tps: ~p Bps~p", [Tps, MBps]), {ok, {Tps, MBps}} end. @@ -425,7 +425,7 @@ wget_client(Config) -> wget_client([KeepAlive, WgetFile, _URL, Protocol, ProtocolOpts, _], _) -> process_flag(trap_exit, true), Cmd = wget_N(KeepAlive, WgetFile, Protocol, ProtocolOpts), - %%ct:pal("Wget cmd: ~p", [Cmd]), + %%ct:log("Wget cmd: ~p", [Cmd]), Port = open_port({spawn, Cmd}, [stderr_to_stdout]), wait_for_wget(Port). diff --git a/lib/inets/test/httpd_test_lib.erl b/lib/inets/test/httpd_test_lib.erl index 678ffeaae7..ce42bb3e61 100644 --- a/lib/inets/test/httpd_test_lib.erl +++ b/lib/inets/test/httpd_test_lib.erl @@ -216,7 +216,7 @@ request(#state{mfa = {Module, Function, Args}, {Socket, closed} -> exit({test_failed, connection_closed}) after TimeOut -> - ct:pal("~p ~w[~w]request -> timeout" + ct:log("~p ~w[~w]request -> timeout" "~p~n", [self(), ?MODULE, ?LINE, Args]), ct:fail(connection_timed_out) end. diff --git a/lib/inets/test/inets_socketwrap_SUITE.erl b/lib/inets/test/inets_socketwrap_SUITE.erl index e3851237e9..c80a8879a9 100644 --- a/lib/inets/test/inets_socketwrap_SUITE.erl +++ b/lib/inets/test/inets_socketwrap_SUITE.erl @@ -71,16 +71,16 @@ start_httpd_fd(Config) when is_list(Conf Skip; {Node, NodeArg} -> InetPort = inets_test_lib:inet_port(node()), - ct:pal("Node: ~p Port ~p~n", [Node, InetPort]), + ct:log("Node: ~p Port ~p~n", [Node, InetPort]), Wrapper = filename:join(DataDir, "setuid_socket_wrap"), Args = ["-s","-httpd_80,0:" ++ integer_to_list(InetPort), "-p",os:find_executable("erl"),"--" | NodeArg], - ct:pal("cmd: ~p ~p~n", [Wrapper, Args]), + ct:log("cmd: ~p ~p~n", [Wrapper, Args]), case open_port({spawn_executable, Wrapper}, [stderr_to_stdout,{args,Args}]) of Port when is_port(Port) -> wait_node_up(Node, 10), - ct:pal("~p", [rpc:call(Node, init, get_argument, [httpd_80])]), + ct:log("~p", [rpc:call(Node, init, get_argument, [httpd_80])]), {ok, _} = rpc:call(Node, application, ensure_all_started, [inets]), {ok, Pid} = rpc:call(Node, inets, start, [httpd, HttpdConf]), [{port, InetPort}] = rpc:call(Node, httpd, info, [Pid, [port]]), @@ -112,7 +112,7 @@ setup_node_info(Node) -> wait_node_up(Node, 0) -> ct:fail({failed_to_start_node, Node}); wait_node_up(Node, N) -> - ct:pal("(Node ~p: net_adm:ping(~p)~n", [node(), Node]), + ct:log("(Node ~p: net_adm:ping(~p)~n", [node(), Node]), case net_adm:ping(Node) of pong -> ok; diff --git a/lib/inets/test/inets_test_lib.erl b/lib/inets/test/inets_test_lib.erl index 324832ca21..fc28fbe303 100644 --- a/lib/inets/test/inets_test_lib.erl +++ b/lib/inets/test/inets_test_lib.erl @@ -547,7 +547,7 @@ tsp(F) -> tsp(F, []). tsp(F, A) -> Timestamp = inets_lib:formated_timestamp(), - ct:pal("*** ~s ~p ~p " ++ F ++ "~n", + ct:log("*** ~s ~p ~p " ++ F ++ "~n", [Timestamp, node(), self() | A]). tsf(Reason) -> -- 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