Skip to content

Commit f2b12d5

Browse files
committed
Replace 'or'/'and' with 'orelse'/'andalso' respectively
1 parent 6e58f14 commit f2b12d5

File tree

96 files changed

+321
-321
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

96 files changed

+321
-321
lines changed

erts/preloaded/src/prim_zip.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -614,7 +614,7 @@ splitter(Left, Right, 0) ->
614614
{Left, Right};
615615
splitter(<<>>, Right, RelPos) ->
616616
split_iolist(Right, RelPos);
617-
splitter(Left, [A | Right], RelPos) when is_list(A) or is_binary(A) ->
617+
splitter(Left, [A | Right], RelPos) when is_list(A) ; is_binary(A) ->
618618
Sz = erlang:iolist_size(A),
619619
case Sz > RelPos of
620620
true ->
@@ -638,7 +638,7 @@ skip_iolist(L, Pos) when is_list(L) ->
638638

639639
skipper(Right, 0) ->
640640
Right;
641-
skipper([A | Right], RelPos) when is_list(A) or is_binary(A) ->
641+
skipper([A | Right], RelPos) when is_list(A) ; is_binary(A) ->
642642
Sz = erlang:iolist_size(A),
643643
case Sz > RelPos of
644644
true ->

lib/common_test/src/ct_framework.erl

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -411,8 +411,8 @@ add_defaults1(Mod,Func, GroupPath, SuiteInfo) ->
411411
%% find and save require terms found in suite info
412412
SuiteReqs =
413413
[SDDef || SDDef <- SuiteInfo,
414-
((require == element(1,SDDef))
415-
or (default_config == element(1,SDDef)))],
414+
require == element(1,SDDef)
415+
orelse default_config == element(1,SDDef)],
416416
case check_for_clashes(TestCaseInfo, GroupPathInfo,
417417
SuiteReqs) of
418418
[] ->
@@ -463,13 +463,13 @@ remove_info_in_prev(Terms, [[] | Rest]) ->
463463
[[] | remove_info_in_prev(Terms, Rest)];
464464
remove_info_in_prev(Terms, [Info | Rest]) ->
465465
UniqueInInfo = [U || U <- Info,
466-
((timetrap == element(1,U)) and
467-
(not lists:keymember(timetrap,1,Terms))) or
468-
((require == element(1,U)) and
469-
(not lists:member(U,Terms))) or
470-
((default_config == element(1,U)) and
471-
(not keysmember([default_config,1,
472-
element(2,U),2], Terms)))],
466+
(timetrap == element(1,U) andalso
467+
not lists:keymember(timetrap,1,Terms)) orelse
468+
(require == element(1,U) andalso
469+
not lists:member(U,Terms)) orelse
470+
(default_config == element(1,U) andalso
471+
not keysmember([default_config,1,
472+
element(2,U),2], Terms))],
473473
OtherTermsInInfo = [T || T <- Info,
474474
timetrap /= element(1,T),
475475
require /= element(1,T),

lib/common_test/src/ct_groups.erl

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,8 @@ find_groups1(Mod, GrNames, TCs, GroupDefs) ->
6060
Path ->
6161
{Path,true}
6262
end,
63-
TCs1 = if (is_atom(TCs) and (TCs /= all)) or is_tuple(TCs) ->
63+
TCs1 = if is_atom(TCs), TCs /= all ;
64+
is_tuple(TCs) ->
6465
[TCs];
6566
true ->
6667
TCs

lib/common_test/src/ct_logs.erl

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -831,7 +831,7 @@ logger_loop(State) ->
831831
end,
832832
if Importance >= (100-VLvl) ->
833833
CtLogFd = State#logger_state.ct_log_fd,
834-
DoEscChars = State#logger_state.tc_esc_chars and EscChars,
834+
DoEscChars = State#logger_state.tc_esc_chars andalso EscChars,
835835
case get_groupleader(Pid, GL, State) of
836836
{tc_log,TCGL,TCGLs} ->
837837
case erlang:is_process_alive(TCGL) of
@@ -1503,8 +1503,8 @@ make_one_index_entry1(SuiteName, Link, Label, Success, Fail, UserSkip, AutoSkip,
15031503
integer_to_list(NotBuilt),"</a></td>\n"]
15041504
end,
15051505
FailStr =
1506-
if (Fail > 0) or (NotBuilt > 0) or
1507-
((Success+Fail+UserSkip+AutoSkip) == 0) ->
1506+
if Fail > 0 ; NotBuilt > 0 ;
1507+
(Success+Fail+UserSkip+AutoSkip) == 0 ->
15081508
["<font color=\"red\">",
15091509
integer_to_list(Fail),"</font>"];
15101510
true ->
@@ -2288,8 +2288,8 @@ runentry(Dir, undefined, _) ->
22882288
runentry(Dir, Totals={Node,Label,Logs,
22892289
{TotSucc,TotFail,UserSkip,AutoSkip,NotBuilt}}, Index) ->
22902290
TotFailStr =
2291-
if (TotFail > 0) or (NotBuilt > 0) or
2292-
((TotSucc+TotFail+UserSkip+AutoSkip) == 0) ->
2291+
if TotFail > 0 ; NotBuilt > 0 ;
2292+
(TotSucc+TotFail+UserSkip+AutoSkip) == 0 ->
22932293
["<font color=\"red\">",
22942294
integer_to_list(TotFail),"</font>"];
22952295
true ->

lib/common_test/src/ct_run.erl

Lines changed: 18 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -1274,24 +1274,22 @@ run_dir(Opts = #opts{logdir = LogDir,
12741274
true -> D end || D <- Dirs],
12751275
reformat_result(catch do_run(tests(Dirs1), [], Opts1, StartOpts));
12761276

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

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

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

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

1293-
{undefined,Suite,GsAndCs} when is_atom(Suite) and
1294-
(Suite /= undefined) ->
1292+
{undefined,Suite,GsAndCs} when is_atom(Suite), Suite /= undefined ->
12951293
{Dir,Mod} = suite_to_test(Suite),
12961294
reformat_result(catch do_run(tests(Dir, Mod, GsAndCs),
12971295
[], Opts1, StartOpts));
@@ -1300,8 +1298,8 @@ run_dir(Opts = #opts{logdir = LogDir,
13001298
exit({error,multiple_suites_and_cases});
13011299

13021300
{undefined,Suite=[Hd|Tl],GsAndCs} when is_integer(Hd) ;
1303-
(is_list(Hd) and (Tl == [])) ;
1304-
(is_atom(Hd) and (Tl == [])) ->
1301+
is_list(Hd), Tl == [] ;
1302+
is_atom(Hd), Tl == [] ->
13051303
{Dir,Mod} = suite_to_test(Suite),
13061304
reformat_result(catch do_run(tests(Dir, Mod, GsAndCs),
13071305
[], Opts1, StartOpts));
@@ -1313,18 +1311,18 @@ run_dir(Opts = #opts{logdir = LogDir,
13131311
exit({error,incorrect_start_options});
13141312

13151313
{Dir,Suite,GsAndCs} when is_integer(hd(Dir)) ;
1316-
(is_atom(Dir) and (Dir /= undefined)) ;
1317-
((length(Dir) == 1) and is_atom(hd(Dir))) ;
1318-
((length(Dir) == 1) and is_list(hd(Dir))) ->
1314+
is_atom(Dir), (Dir /= undefined) ;
1315+
length(Dir) == 1, is_atom(hd(Dir)) ;
1316+
length(Dir) == 1, is_list(hd(Dir)) ->
13191317
Dir1 = if is_atom(Dir) -> atom_to_list(Dir);
13201318
true -> Dir end,
13211319
if Suite == undefined ->
13221320
exit({error,incorrect_start_options});
13231321

13241322
is_integer(hd(Suite)) ;
1325-
(is_atom(Suite) and (Suite /= undefined)) ;
1326-
((length(Suite) == 1) and is_atom(hd(Suite))) ;
1327-
((length(Suite) == 1) and is_list(hd(Suite))) ->
1323+
is_atom(Suite), (Suite /= undefined) ;
1324+
length(Suite) == 1, is_atom(hd(Suite)) ;
1325+
length(Suite) == 1, is_list(hd(Suite)) ->
13281326
{Dir2,Mod} = suite_to_test(Dir1, Suite),
13291327
case GsAndCs of
13301328
[] ->
@@ -1610,20 +1608,19 @@ suite_to_test(Dir, Suite) when is_list(Suite) ->
16101608
{DirName,list_to_atom(filename:rootname(File))}
16111609
end.
16121610

1613-
groups_and_cases(Gs, Cs) when ((Gs == undefined) or (Gs == [])) and
1614-
((Cs == undefined) or (Cs == [])) ->
1611+
groups_and_cases(Gs, Cs) when (Gs == undefined orelse Gs == []),
1612+
(Cs == undefined orelse Cs == []) ->
16151613
[];
16161614
groups_and_cases(Gs, Cs) when Gs == undefined ; Gs == [] ->
1617-
if (Cs == all) or (Cs == [all]) or (Cs == ["all"]) -> all;
1615+
if Cs == all ; Cs == [all] ; Cs == ["all"] -> all;
16181616
true -> [ensure_atom(C) || C <- listify(Cs)]
16191617
end;
16201618
groups_and_cases(GOrGs, Cs) when (is_atom(GOrGs) orelse
16211619
(is_list(GOrGs) andalso
16221620
(is_atom(hd(GOrGs)) orelse
16231621
(is_list(hd(GOrGs)) andalso
16241622
is_atom(hd(hd(GOrGs))))))) ->
1625-
if (Cs == undefined) or (Cs == []) or
1626-
(Cs == all) or (Cs == [all]) or (Cs == ["all"]) ->
1623+
if Cs == undefined ; Cs == [] ; Cs == all ; Cs == [all] ; Cs == ["all"] ->
16271624
[{GOrGs,all}];
16281625
true ->
16291626
[{GOrGs,[ensure_atom(C) || C <- listify(Cs)]}]
@@ -1632,7 +1629,7 @@ groups_and_cases(Gs, Cs) when is_integer(hd(hd(Gs))) ->
16321629
%% if list of strings, this comes from 'ct_run -group G1 G2 ...' and
16331630
%% we need to parse the strings
16341631
Gs1 =
1635-
if (Gs == [all]) or (Gs == ["all"]) ->
1632+
if Gs == [all] ; Gs == ["all"] ->
16361633
all;
16371634
true ->
16381635
lists:map(fun(G) ->
@@ -2360,7 +2357,7 @@ start_cover(Opts=#opts{coverspec=CovData,cover_stop=CovStop},LogDir) ->
23602357
[TsCoverInfo]),
23612358

23622359
%% start cover on specified nodes
2363-
if (CovNodes /= []) and (CovNodes /= undefined) ->
2360+
if CovNodes /= [], CovNodes /= undefined ->
23642361
ct_logs:log("COVER INFO",
23652362
"Nodes included in cover "
23662363
"session: ~tw",

lib/common_test/src/ct_slave.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -350,7 +350,7 @@ do_start(Host, Node, Options) ->
350350
{ok, ENode}->
351351
ok;
352352
{error, Timeout, ENode}
353-
when ((Timeout==init_timeout) or (Timeout==startup_timeout)) and
353+
when (Timeout == init_timeout orelse Timeout == startup_timeout),
354354
Options#options.kill_if_fail->
355355
do_stop(ENode);
356356
_-> ok

lib/common_test/src/ct_telnet.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1190,7 +1190,7 @@ teln_expect(Name,Pid,Data,Pattern0,Prx,Opts) ->
11901190
end.
11911191

11921192
convert_pattern(Pattern0,Seq)
1193-
when Pattern0==[] orelse (is_list(Pattern0) and not is_integer(hd(Pattern0))) ->
1193+
when Pattern0 == [] ; is_list(Pattern0), not is_integer(hd(Pattern0)) ->
11941194
Pattern =
11951195
case Seq of
11961196
true -> Pattern0;

lib/common_test/src/ct_testspec.erl

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -474,10 +474,10 @@ replace_names(Terms) ->
474474
throw({illegal_name_in_testspec,Name});
475475
true ->
476476
[First|_] = atom_to_list(Name),
477-
if ((First == $?) or (First == $$)
478-
or (First == $_)
479-
or ((First >= $A)
480-
and (First =< $Z))) ->
477+
if (First == $?) ;
478+
(First == $$) ;
479+
(First == $_) ;
480+
(First >= $A), (First =< $Z) ->
481481
[Def];
482482
true ->
483483
throw({illegal_name_in_testspec,
@@ -1299,14 +1299,14 @@ insert_groups(Node,Dir,Suite,Group,Cases,Tests,MergeTests)
12991299
when is_atom(Group); is_tuple(Group) ->
13001300
insert_groups(Node,Dir,Suite,[Group],Cases,Tests,MergeTests);
13011301
insert_groups(Node,Dir,Suite,Groups,Cases,Tests,false) when
1302-
((Cases == all) or is_list(Cases)) and is_list(Groups) ->
1302+
Cases == all orelse is_list(Cases), is_list(Groups) ->
13031303
Groups1 = [if is_list(Gr) -> % preserve group path
13041304
{[Gr],Cases};
13051305
true ->
13061306
{Gr,Cases} end || Gr <- Groups],
13071307
append({{Node,Dir},[{Suite,Groups1}]},Tests);
13081308
insert_groups(Node,Dir,Suite,Groups,Cases,Tests,true) when
1309-
((Cases == all) or is_list(Cases)) and is_list(Groups) ->
1309+
Cases == all orelse is_list(Cases), is_list(Groups) ->
13101310
Groups1 = [if is_list(Gr) -> % preserve group path
13111311
{[Gr],Cases};
13121312
true ->
@@ -1418,11 +1418,11 @@ skip_groups(Node,Dir,Suite,Groups,Case,Cmt,Tests,MergeTests)
14181418
when is_atom(Case),Case =/= all ->
14191419
skip_groups(Node,Dir,Suite,Groups,[Case],Cmt,Tests,MergeTests);
14201420
skip_groups(Node,Dir,Suite,Groups,Cases,Cmt,Tests,false) when
1421-
((Cases == all) or is_list(Cases)) and is_list(Groups) ->
1421+
(Cases == all orelse is_list(Cases)), is_list(Groups) ->
14221422
Suites1 = skip_groups1(Suite,[{Gr,Cases} || Gr <- Groups],Cmt,[]),
14231423
append({{Node,Dir},Suites1},Tests);
14241424
skip_groups(Node,Dir,Suite,Groups,Cases,Cmt,Tests,true) when
1425-
((Cases == all) or is_list(Cases)) and is_list(Groups) ->
1425+
(Cases == all orelse is_list(Cases)), is_list(Groups) ->
14261426
{Tests1,Done} =
14271427
lists:foldr(fun({{N,D},Suites0},{Merged,_}) when N == Node,
14281428
D == Dir ->
@@ -1579,7 +1579,7 @@ is_node([master|_],_Nodes) ->
15791579
is_node(What={N,H},Nodes) when is_atom(N), is_atom(H) ->
15801580
is_node([What],Nodes);
15811581
is_node([What|_],Nodes) ->
1582-
case lists:keymember(What,1,Nodes) or
1582+
case lists:keymember(What,1,Nodes) orelse
15831583
lists:keymember(What,2,Nodes) of
15841584
true ->
15851585
true;

lib/common_test/src/test_server_ctrl.erl

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -2350,15 +2350,15 @@ run_test_cases(TestSpec, Config, TimetrapData) ->
23502350

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

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

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

lib/compiler/src/beam_dict.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -222,7 +222,7 @@ line([{location,Name,Line}|_], #asm{lines=Lines,num_lines=N,
222222
when is_atom(Instr) ->
223223
{FnameIndex,Dict1} = fname(Name, Dict0),
224224
Key = {FnameIndex,Line},
225-
ExecLine = ExecLine0 or (Instr =:= executable_line),
225+
ExecLine = ExecLine0 orelse Instr =:= executable_line,
226226
case Lines of
227227
#{Key := Index} ->
228228
{Index,Dict1#asm{num_lines=N+1,exec_line=ExecLine}};

0 commit comments

Comments
 (0)