Skip to content

Commit

Permalink
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
ct: cte_track for trackig CT progress
Browse files Browse the repository at this point in the history
- event handling module for tracking CT execution progress
- displays additional terminal summary at the end of test run
- optionally displays execution progress on terminal
- its output can be redirected to file
u3s committed Nov 20, 2023
1 parent 2074661 commit 52e1081
Showing 6 changed files with 235 additions and 8 deletions.
1 change: 1 addition & 0 deletions lib/common_test/src/Makefile
Original file line number Diff line number Diff line change
@@ -71,6 +71,7 @@ MODULES= \
ct_config_xml \
ct_slave \
ct_hooks_lock\
cte_track\
cth_log_redirect\
cth_surefire \
ct_netconfc \
1 change: 1 addition & 0 deletions lib/common_test/src/common_test.app.src
Original file line number Diff line number Diff line change
@@ -54,6 +54,7 @@
ct_config_plain,
ct_config_xml,
ct_slave,
cte_track,
cth_log_redirect,
cth_conn_log,
cth_surefire,
227 changes: 227 additions & 0 deletions lib/common_test/src/cte_track.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,227 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2023. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
%% You may obtain a copy of the License at
%%
%% http://www.apache.org/licenses/LICENSE-2.0
%%
%% Unless required by applicable law or agreed to in writing, software
%% distributed under the License is distributed on an "AS IS" BASIS,
%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
%% See the License for the specific language governing permissions and
%% limitations under the License.
%%
%% %CopyrightEnd%
%%

-module(cte_track).
%% module for tracking CT execution progress
%% test spec addition example: {event_handler, {cte_track, [{mode, live_details}]}}.
-behaviour(gen_event).

%% gen_event callbacks
-export([init/1, handle_event/2, handle_call/2,
handle_info/2, terminate/2, code_change/3]).

-include_lib("common_test/include/ct_event.hrl").

%%====================================================================
%% gen_event callbacks
%%====================================================================
init(InitArgs) ->
Device =
case proplists:get_value(file, InitArgs) of
undefined ->
user;
Path when is_list(Path) ->
{ok, D} = file:open(Path, [write]),
D
end,
{ok, #{device => Device,
mode => proplists:get_value(mode, InitArgs),
suite => undefined, group => undefined,
ok => 0, skipped => [], failed => [], auto_skipped => [],
start_time => get_seconds()}}.

handle_event(#event{name = tc_start,
data = {Suite, init_per_suite}},
State = #{mode := Mode, device := D}) ->
case lists:member(Mode, [live, live_details]) of
true ->
print(D, "~p [", [Suite]);
_ ->
ok
end,
{ok, maps:put(suite, Suite, State)};
handle_event(#event{name = tc_start,
data = {_Suite, {init_per_group, GroupName, _}}},
State) ->
{ok, maps:put(group, GroupName, State)};
handle_event(#event{name = tc_done,
data = {_, end_per_suite, _}},
State0 = #{mode := Mode, device := D,
ok := Ok, skipped := Skipped, failed := Failed}) ->
case lists:member(Mode, [live, live_details]) of
true ->
print(D, "] (~p ok ~p failed ~p skipped)~n",
[Ok, length(Failed), length(Skipped)]);
_ ->
ok
end,
State1 = maps:put(suite, undefined, State0),
State = maps:put(group, undefined, State1),
{ok, State};
handle_event(#event{name = tc_done,
data = {_Suite, Case, ok}},
State = #{mode := Mode, device := D})
when is_atom(Case) ->
case lists:member(Mode, [live, live_details]) of
true ->
print(D, ".");
_ ->
ok
end,
OkAcc = maps:get(ok, State),
{ok, maps:put(ok, OkAcc + 1, State)};
handle_event(#event{name = tc_done,
data = {_Suite, Case,
{SkipOrFailed, Reason}}},
State = #{suite := Suite, group := Group})
when is_atom(Case) ->
{ok, handle_not_ok(Suite, Group, Case, SkipOrFailed, Reason, State)};
handle_event(#event{name = tc_done, data = {_Suite, {Case, _, _}, {skipped, Reason}}},
State = #{suite := Suite, group := Group})
when Case == init_per_group; Case == end_per_group ->
{ok, handle_not_ok(Suite, Group, Case, skipped, Reason, State)};
handle_event(#event{name = tc_done, data = {_Suite, {Case, _, _}, ok}},
State)
when Case == init_per_group; Case == end_per_group->
{ok, State};
handle_event(#event{name = tc_done, data = Data},
State = #{device := D}) ->
print(D, "~n~nUnandled interesting event:~nName = tc_done~nData = ~p~n~n",
[Data]),
{ok, State};
handle_event(#event{name = Name, data = {Suite, {Case, Group}, Comment}},
State) when Name == tc_user_skip; Name == tc_auto_skip ->
{ok, handle_not_ok(Suite, Group, Case, skipped, Comment, State)};
handle_event(#event{name = Name, data = {Suite, Case, Comment}},
State) when Name == tc_user_skip; Name == tc_auto_skip ->
{ok, handle_not_ok(Suite, undefined, Case, skipped, Comment, State)};
handle_event(#event{name = test_done},
State = #{ok := Ok, skipped := Skipped, auto_skipped := ASkipped,
failed := Failed, start_time := StartTime,
device := D}) ->
print_line(D),
PrintCategory =
fun(Result, List) ->
[print_entry(D, Result, I) ||
I <- lists:reverse(List)]
end,
PrintCategory(skipped, Skipped ++ ASkipped),
PrintCategory(failed, Failed),
print(D, "~n"),
print(D, "# EVENTS SUMMARY, ~p ok, ~p skipped, ~p failed (~p total in " ++
get_nice_time(get_seconds() - StartTime) ++ ") ~n",
[Ok, length(Skipped), length(Failed),
Ok + length(Skipped) + length(Failed)]),
print_line(D),
print(D, "~n"),
{ok,State};
handle_event(#event{name = Name, data = Data}, State = #{device := D}) ->
NotInteresting = [start_logging, start_write_file, finished_write_file,
test_stats, start_make, finished_make, tc_logfile,
test_start, start_info, tc_start, stop_logging],
case lists:member(Name, NotInteresting) of
false ->
print(D, "~n~nUnandled interesting event:~nName = ~p~nData = ~p~n~n",
[Name, Data]);
_ ->
ok
end,
{ok,State}.

handle_call(_Req, State) ->
Reply = ok,
{ok, Reply, State}.

handle_info(_Info, State) ->
{ok, State}.

terminate(stop, #{device := user}) ->
ok;
terminate(stop, #{device := Device}) ->
file:close(Device),
ok;
terminate(Reason, #{device := D}) ->
print(D, "~n > Interesting terminate reason = ~p~n", [Reason]),
ok.

code_change(_OldVsn, State, _Extra) ->
{ok, State}.

%%--------------------------------------------------------------------
print(Device, Fmt) ->
print(Device, Fmt, []).
print_line(Device) ->
print(Device, "======================================================================~n").
print(Device, Fmt, Args) ->
io:fwrite(Device, Fmt, Args).

handle_not_ok(Suite, Group, Case, SkipOrFailed, Reason,
State0 = #{mode := Mode, device := D}) ->
SkipOrFailedAcc = maps:get(SkipOrFailed, State0),
Entry = {Suite, Group, Case, Reason},
case Mode of
live_details ->
print_entry(D, SkipOrFailed, Entry),
print(D, "~n");
live ->
print(D, result_short(SkipOrFailed));
_ ->
ok
end,
maps:put(SkipOrFailed,
[Entry | SkipOrFailedAcc],
State0).

print_entry(Device, Result, Entry) when is_atom(Result) ->
print_entry(Device, result_long(Result), Entry);
print_entry(Device, RS, {Suite, undefined, Case, Reason}) ->
print(Device, "~n~s ~p:~p ~s",
[RS, Suite, Case, format_reason(Reason)]);
print_entry(Device, RS, {Suite, Group, Case, Reason}) ->
print(Device, "~n~s ~p@~p:~p ~s",
[RS, Suite, Group, Case,format_reason(Reason)]).

result_short(failed) -> "F";
result_short(R) when R == skipped; R == auto_skipped -> "S";
result_short(_) -> "?".

result_long(failed) -> "[FAILED]";
result_long(R) when R == skipped; R == auto_skipped -> "[SKIPPED]";
result_long(_) -> "[?]".

format_reason(Reason) when is_list(Reason) ->
lists:flatten(Reason);
format_reason({Reason, SubReason}) ->
io_lib:format("~p (~p)", [Reason, SubReason]);
format_reason({Reason, A, B, C}) ->
io_lib:format("~p (~p ~p ~p)", [Reason, A, B, C]);
format_reason(Reason) ->
io_lib:format("~n > Not recognized FIXME! ~p", [Reason]).

get_nice_time(Seconds) when is_integer(Seconds) ->
case Seconds < 60 of
true ->
io_lib:format("~ws", [Seconds]);
_ ->
io_lib:format("~wm", [round(Seconds/60)])
end.

get_seconds() ->
erlang:system_time(second).
3 changes: 2 additions & 1 deletion lib/inets/test/inets.spec
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{suites,"../inets_test", all}.
{skip_suites, "../inets_test", [httpd_bench_SUITE],
{skip_suites, "../inets_test", [httpd_bench_SUITE],
"Benchmarks run separately"}.
{event_handler, {cte_track, [{mode, live_details}]}}.
10 changes: 3 additions & 7 deletions lib/ssh/test/ssh.spec
Original file line number Diff line number Diff line change
@@ -1,8 +1,4 @@
{suites,"../ssh_test",all}.

{skip_suites, "../ssh_test", [ssh_bench_SUITE,
ssh_upgrade_SUITE
],
"Benchmarks run separately"}.


{skip_suites, "../ssh_test",
[ssh_bench_SUITE, ssh_upgrade_SUITE], "Benchmarks run separately"}.
{event_handler, {cte_track, [{mode, live_details}]}}.
1 change: 1 addition & 0 deletions lib/ssl/test/ssl_gh.spec
Original file line number Diff line number Diff line change
@@ -13,3 +13,4 @@
{skip_groups,dir,ssl_dist_bench_SUITE,throughput,"Benchmarks run separately"}.
{skip_groups,dir,ssl_dist_bench_SUITE,sched_utilization,"Benchmarks run separately"}.

{event_handler, {cte_track, [{mode, live_details}]}}.

0 comments on commit 52e1081

Please sign in to comment.