Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
19 changes: 8 additions & 11 deletions lib/common_test/src/ct_framework.erl
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,6 @@
-export([error_in_suite/1, init_per_suite/1, end_per_suite/1,
init_per_group/2, end_per_group/2]).

-compile(nowarn_obsolete_bool_op).

-include("ct.hrl").
-include("ct_event.hrl").
-include("ct_util.hrl").
Expand Down Expand Up @@ -413,8 +411,8 @@ add_defaults1(Mod,Func, GroupPath, SuiteInfo) ->
%% find and save require terms found in suite info
SuiteReqs =
[SDDef || SDDef <- SuiteInfo,
((require == element(1,SDDef))
or (default_config == element(1,SDDef)))],
require == element(1,SDDef)
orelse default_config == element(1,SDDef)],
case check_for_clashes(TestCaseInfo, GroupPathInfo,
SuiteReqs) of
[] ->
Expand Down Expand Up @@ -465,13 +463,12 @@ remove_info_in_prev(Terms, [[] | Rest]) ->
[[] | remove_info_in_prev(Terms, Rest)];
remove_info_in_prev(Terms, [Info | Rest]) ->
UniqueInInfo = [U || U <- Info,
((timetrap == element(1,U)) and
(not lists:keymember(timetrap,1,Terms))) or
((require == element(1,U)) and
(not lists:member(U,Terms))) or
((default_config == element(1,U)) and
(not keysmember([default_config,1,
element(2,U),2], Terms)))],
timetrap == element(1, U) andalso
not lists:keymember(timetrap, 1, Terms) orelse
require == element(1, U) andalso
not lists:member(U,Terms) orelse
default_config == element(1,U) andalso
not keysmember([default_config, 1, element(2, U), 2], Terms)],
OtherTermsInInfo = [T || T <- Info,
timetrap /= element(1,T),
require /= element(1,T),
Expand Down
4 changes: 1 addition & 3 deletions lib/common_test/src/ct_groups.erl
Original file line number Diff line number Diff line change
Expand Up @@ -32,8 +32,6 @@
-export([delete_subs/2]).
-export([expand_groups/3, search_and_override/3]).

-compile(nowarn_obsolete_bool_op).

-define(val(Key, List), proplists:get_value(Key, List)).
-define(val(Key, List, Def), proplists:get_value(Key, List, Def)).
-define(rev(L), lists:reverse(L)).
Expand Down Expand Up @@ -62,7 +60,7 @@ find_groups1(Mod, GrNames, TCs, GroupDefs) ->
Path ->
{Path,true}
end,
TCs1 = if (is_atom(TCs) and (TCs /= all)) or is_tuple(TCs) ->
TCs1 = if is_atom(TCs), TCs /= all; is_tuple(TCs) ->
[TCs];
true ->
TCs
Expand Down
12 changes: 5 additions & 7 deletions lib/common_test/src/ct_logs.erl
Original file line number Diff line number Diff line change
Expand Up @@ -54,8 +54,6 @@
%% Simulate logger process for use without ct environment running
-export([simulate/0]).

-compile(nowarn_obsolete_bool_op).

-include("ct.hrl").
-include("ct_event.hrl").
-include("ct_util.hrl").
Expand Down Expand Up @@ -833,7 +831,7 @@ logger_loop(State) ->
end,
if Importance >= (100-VLvl) ->
CtLogFd = State#logger_state.ct_log_fd,
DoEscChars = State#logger_state.tc_esc_chars and EscChars,
DoEscChars = State#logger_state.tc_esc_chars andalso EscChars,
case get_groupleader(Pid, GL, State) of
{tc_log,TCGL,TCGLs} ->
case erlang:is_process_alive(TCGL) of
Expand Down Expand Up @@ -1505,8 +1503,8 @@ make_one_index_entry1(SuiteName, Link, Label, Success, Fail, UserSkip, AutoSkip,
integer_to_list(NotBuilt),"</a></td>\n"]
end,
FailStr =
if (Fail > 0) or (NotBuilt > 0) or
((Success+Fail+UserSkip+AutoSkip) == 0) ->
if Fail > 0; NotBuilt > 0;
Success+Fail+UserSkip+AutoSkip == 0 ->
["<font color=\"red\">",
integer_to_list(Fail),"</font>"];
true ->
Expand Down Expand Up @@ -2290,8 +2288,8 @@ runentry(Dir, undefined, _) ->
runentry(Dir, Totals={Node,Label,Logs,
{TotSucc,TotFail,UserSkip,AutoSkip,NotBuilt}}, Index) ->
TotFailStr =
if (TotFail > 0) or (NotBuilt > 0) or
((TotSucc+TotFail+UserSkip+AutoSkip) == 0) ->
if TotFail > 0; NotBuilt > 0;
TotSucc+TotFail+UserSkip+AutoSkip == 0 ->
["<font color=\"red\">",
integer_to_list(TotFail),"</font>"];
true ->
Expand Down
50 changes: 24 additions & 26 deletions lib/common_test/src/ct_run.erl
Original file line number Diff line number Diff line change
Expand Up @@ -33,8 +33,6 @@
%% Misc internal API functions
-export([variables_file_name/1,script_start1/2,run_test2/1, run_make/3]).

-compile(nowarn_obsolete_bool_op).

-include("ct.hrl").
-include("ct_event.hrl").
-include("ct_util.hrl").
Expand Down Expand Up @@ -1276,34 +1274,34 @@ run_dir(Opts = #opts{logdir = LogDir,
true -> D end || D <- Dirs],
reformat_result(catch do_run(tests(Dirs1), [], Opts1, StartOpts));

{Dir=[Hd|_],undefined,[]} when is_list(Dir) and is_integer(Hd) ->
{Dir=[Hd|_],undefined,[]} when is_list(Dir), is_integer(Hd) ->
reformat_result(catch do_run(tests(Dir), [], Opts1, StartOpts));

{Dir,undefined,[]} when is_atom(Dir) and (Dir /= undefined) ->
{Dir,undefined,[]} when is_atom(Dir), Dir /= undefined ->
reformat_result(catch do_run(tests(atom_to_list(Dir)),
[], Opts1, StartOpts));

{undefined,Suites=[Hd|_],[]} when not is_integer(Hd) ->
Suites1 = [suite_to_test(S) || S <- Suites],
reformat_result(catch do_run(tests(Suites1), [], Opts1, StartOpts));

{undefined,Suite,[]} when is_atom(Suite) and
(Suite /= undefined) ->
{undefined,Suite,[]} when is_atom(Suite),
Suite /= undefined ->
{Dir,Mod} = suite_to_test(Suite),
reformat_result(catch do_run(tests(Dir, Mod), [], Opts1, StartOpts));

{undefined,Suite,GsAndCs} when is_atom(Suite) and
(Suite /= undefined) ->
{undefined,Suite,GsAndCs} when is_atom(Suite),
Suite /= undefined ->
{Dir,Mod} = suite_to_test(Suite),
reformat_result(catch do_run(tests(Dir, Mod, GsAndCs),
[], Opts1, StartOpts));

{undefined,[Hd,_|_],_GsAndCs} when not is_integer(Hd) ->
exit({error,multiple_suites_and_cases});

{undefined,Suite=[Hd|Tl],GsAndCs} when is_integer(Hd) ;
(is_list(Hd) and (Tl == [])) ;
(is_atom(Hd) and (Tl == [])) ->
{undefined,Suite=[Hd|Tl],GsAndCs} when is_integer(Hd);
is_list(Hd), Tl == [];
is_atom(Hd), Tl == [] ->
{Dir,Mod} = suite_to_test(Suite),
reformat_result(catch do_run(tests(Dir, Mod, GsAndCs),
[], Opts1, StartOpts));
Expand All @@ -1314,19 +1312,19 @@ run_dir(Opts = #opts{logdir = LogDir,
{undefined,undefined,GsAndCs} when GsAndCs /= [] ->
exit({error,incorrect_start_options});

{Dir,Suite,GsAndCs} when is_integer(hd(Dir)) ;
(is_atom(Dir) and (Dir /= undefined)) ;
((length(Dir) == 1) and is_atom(hd(Dir))) ;
((length(Dir) == 1) and is_list(hd(Dir))) ->
{Dir,Suite,GsAndCs} when is_integer(hd(Dir));
is_atom(Dir), Dir /= undefined;
is_atom(hd(Dir)), length(Dir) == 1;
is_list(hd(Dir)), length(Dir) == 1 ->
Dir1 = if is_atom(Dir) -> atom_to_list(Dir);
true -> Dir end,
if Suite == undefined ->
exit({error,incorrect_start_options});

is_integer(hd(Suite)) ;
(is_atom(Suite) and (Suite /= undefined)) ;
((length(Suite) == 1) and is_atom(hd(Suite))) ;
((length(Suite) == 1) and is_list(hd(Suite))) ->
is_integer(hd(Suite));
is_atom(Suite), Suite /= undefined;
is_atom(hd(Suite)), length(Suite) == 1;
is_list(hd(Suite)), length(Suite) == 1 ->
{Dir2,Mod} = suite_to_test(Dir1, Suite),
case GsAndCs of
[] ->
Expand Down Expand Up @@ -1612,20 +1610,20 @@ suite_to_test(Dir, Suite) when is_list(Suite) ->
{DirName,list_to_atom(filename:rootname(File))}
end.

groups_and_cases(Gs, Cs) when ((Gs == undefined) or (Gs == [])) and
((Cs == undefined) or (Cs == [])) ->
groups_and_cases(Gs, Cs) when Gs == undefined orelse Gs == [],
Cs == undefined orelse Cs == [] ->
[];
groups_and_cases(Gs, Cs) when Gs == undefined ; Gs == [] ->
if (Cs == all) or (Cs == [all]) or (Cs == ["all"]) -> all;
if Cs == all; Cs == [all]; Cs == ["all"] -> all;
true -> [ensure_atom(C) || C <- listify(Cs)]
end;
groups_and_cases(GOrGs, Cs) when (is_atom(GOrGs) orelse
(is_list(GOrGs) andalso
(is_atom(hd(GOrGs)) orelse
(is_list(hd(GOrGs)) andalso
is_atom(hd(hd(GOrGs))))))) ->
if (Cs == undefined) or (Cs == []) or
(Cs == all) or (Cs == [all]) or (Cs == ["all"]) ->
if Cs == undefined; Cs == [];
Cs == all; Cs == [all]; Cs == ["all"] ->
[{GOrGs,all}];
true ->
[{GOrGs,[ensure_atom(C) || C <- listify(Cs)]}]
Expand All @@ -1634,7 +1632,7 @@ groups_and_cases(Gs, Cs) when is_integer(hd(hd(Gs))) ->
%% if list of strings, this comes from 'ct_run -group G1 G2 ...' and
%% we need to parse the strings
Gs1 =
if (Gs == [all]) or (Gs == ["all"]) ->
if Gs == [all]; Gs == ["all"] ->
all;
true ->
lists:map(fun(G) ->
Expand Down Expand Up @@ -2362,7 +2360,7 @@ start_cover(Opts=#opts{coverspec=CovData,cover_stop=CovStop},LogDir) ->
[TsCoverInfo]),

%% start cover on specified nodes
if (CovNodes /= []) and (CovNodes /= undefined) ->
if CovNodes /= [], CovNodes /= undefined ->
ct_logs:log("COVER INFO",
"Nodes included in cover "
"session: ~tw",
Expand Down
4 changes: 1 addition & 3 deletions lib/common_test/src/ct_slave.erl
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,6 @@ term in the Test Specification.
""".
-moduledoc(#{since => "OTP R14B"}).

-compile(nowarn_obsolete_bool_op).

-export([start/1, start/2, start/3, stop/1, stop/2]).

-export([slave_started/2, slave_ready/2, monitor_master/1]).
Expand Down Expand Up @@ -352,7 +350,7 @@ do_start(Host, Node, Options) ->
{ok, ENode}->
ok;
{error, Timeout, ENode}
when ((Timeout==init_timeout) or (Timeout==startup_timeout)) and
when Timeout==init_timeout orelse Timeout==startup_timeout,
Options#options.kill_if_fail->
do_stop(ENode);
_-> ok
Expand Down
4 changes: 1 addition & 3 deletions lib/common_test/src/ct_telnet.erl
Original file line number Diff line number Diff line change
Expand Up @@ -173,8 +173,6 @@ suite() ->
format_data/2]).
-export([start_gen_log/1, end_gen_log/0, log/3, log/4]).

-compile(nowarn_obsolete_bool_op).

-define(RECONNS,3).
-define(RECONN_TIMEOUT,5000).
-define(DEFAULT_TIMEOUT,10000).
Expand Down Expand Up @@ -1192,7 +1190,7 @@ teln_expect(Name,Pid,Data,Pattern0,Prx,Opts) ->
end.

convert_pattern(Pattern0,Seq)
when Pattern0==[] orelse (is_list(Pattern0) and not is_integer(hd(Pattern0))) ->
when Pattern0==[]; is_list(Pattern0), not is_integer(hd(Pattern0)) ->
Pattern =
case Seq of
true -> Pattern0;
Expand Down
20 changes: 9 additions & 11 deletions lib/common_test/src/ct_testspec.erl
Original file line number Diff line number Diff line change
Expand Up @@ -35,8 +35,6 @@ This module exports help functions for parsing of test specifications.

-export([testspec_rec2list/1, testspec_rec2list/2]).

-compile(nowarn_obsolete_bool_op).

-include("ct_util.hrl").
-define(testspec_fields, record_info(fields, testspec)).

Expand Down Expand Up @@ -476,10 +474,10 @@ replace_names(Terms) ->
throw({illegal_name_in_testspec,Name});
true ->
[First|_] = atom_to_list(Name),
if ((First == $?) or (First == $$)
or (First == $_)
or ((First >= $A)
and (First =< $Z))) ->
if First == $?;
First == $$;
First == $_;
First >= $A andalso First =< $Z ->
[Def];
true ->
throw({illegal_name_in_testspec,
Expand Down Expand Up @@ -1301,14 +1299,14 @@ insert_groups(Node,Dir,Suite,Group,Cases,Tests,MergeTests)
when is_atom(Group); is_tuple(Group) ->
insert_groups(Node,Dir,Suite,[Group],Cases,Tests,MergeTests);
insert_groups(Node,Dir,Suite,Groups,Cases,Tests,false) when
((Cases == all) or is_list(Cases)) and is_list(Groups) ->
Cases == all orelse is_list(Cases), is_list(Groups) ->
Groups1 = [if is_list(Gr) -> % preserve group path
{[Gr],Cases};
true ->
{Gr,Cases} end || Gr <- Groups],
append({{Node,Dir},[{Suite,Groups1}]},Tests);
insert_groups(Node,Dir,Suite,Groups,Cases,Tests,true) when
((Cases == all) or is_list(Cases)) and is_list(Groups) ->
Cases == all orelse is_list(Cases), is_list(Groups) ->
Groups1 = [if is_list(Gr) -> % preserve group path
{[Gr],Cases};
true ->
Expand Down Expand Up @@ -1420,11 +1418,11 @@ skip_groups(Node,Dir,Suite,Groups,Case,Cmt,Tests,MergeTests)
when is_atom(Case),Case =/= all ->
skip_groups(Node,Dir,Suite,Groups,[Case],Cmt,Tests,MergeTests);
skip_groups(Node,Dir,Suite,Groups,Cases,Cmt,Tests,false) when
((Cases == all) or is_list(Cases)) and is_list(Groups) ->
Cases == all orelse is_list(Cases), is_list(Groups) ->
Suites1 = skip_groups1(Suite,[{Gr,Cases} || Gr <- Groups],Cmt,[]),
append({{Node,Dir},Suites1},Tests);
skip_groups(Node,Dir,Suite,Groups,Cases,Cmt,Tests,true) when
((Cases == all) or is_list(Cases)) and is_list(Groups) ->
Cases == all orelse is_list(Cases), is_list(Groups) ->
{Tests1,Done} =
lists:foldr(fun({{N,D},Suites0},{Merged,_}) when N == Node,
D == Dir ->
Expand Down Expand Up @@ -1581,7 +1579,7 @@ is_node([master|_],_Nodes) ->
is_node(What={N,H},Nodes) when is_atom(N), is_atom(H) ->
is_node([What],Nodes);
is_node([What|_],Nodes) ->
case lists:keymember(What,1,Nodes) or
case lists:keymember(What,1,Nodes) orelse
lists:keymember(What,2,Nodes) of
true ->
true;
Expand Down
12 changes: 5 additions & 7 deletions lib/common_test/src/test_server_ctrl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -83,8 +83,6 @@

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

-compile(nowarn_obsolete_bool_op).

-include("test_server_internal.hrl").
-include_lib("kernel/include/file.hrl").
-define(suite_ext, "_SUITE").
Expand Down Expand Up @@ -2352,15 +2350,15 @@ run_test_cases(TestSpec, Config, TimetrapData) ->

run_test_cases_loop([{SkipTag,CaseData={Type,_Ref,_Case,_Comment}}|Cases],
Config, TimetrapData, Mode, Status) when
((SkipTag==auto_skip_case) or (SkipTag==skip_case)) and
((Type==conf) or (Type==make)) ->
SkipTag==auto_skip_case orelse SkipTag==skip_case,
Type==conf orelse Type==make ->
run_test_cases_loop([{SkipTag,CaseData,Mode}|Cases],
Config, TimetrapData, Mode, Status);

run_test_cases_loop([{SkipTag,{Type,Ref,Case,Comment},SkipMode}|Cases],
Config, TimetrapData, Mode, Status) when
((SkipTag==auto_skip_case) or (SkipTag==skip_case)) and
((Type==conf) or (Type==make)) ->
SkipTag==auto_skip_case orelse SkipTag==skip_case,
Type==conf orelse Type==make ->
ok = file:set_cwd(filename:dirname(get(test_server_dir))),
CurrIOHandler = get(test_server_common_io_handler),
ParentMode = tl(Mode),
Expand Down Expand Up @@ -2825,7 +2823,7 @@ run_test_cases_loop([{conf,Ref,Props,{Mod,Func}}|_Cases]=Cs0,
stop_minor_log_file(),
run_test_cases_loop(Cases2, Config1, TimetrapData, Mode, Status3);

{_,{Skip,Reason},_} when StartConf and ((Skip==skip) or (Skip==skipped)) ->
{_,{Skip,Reason},_} when StartConf, Skip==skip orelse Skip==skipped ->
ReportAbortRepeat(skipped),
print(minor, "~n*** ~tw skipped.~n"
" Skipping all cases.", [Func]),
Expand Down
Loading