Skip to content

Commit aa1be07

Browse files
committed
Replace 'or'/'and' with 'orelse'/'andalso' respectively
1 parent e45f20e commit aa1be07

File tree

97 files changed

+286
-285
lines changed

Some content is hidden

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

97 files changed

+286
-285
lines changed

erts/preloaded/src/prim_zip.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -605,7 +605,7 @@ splitter(Left, Right, 0) ->
605605
{Left, Right};
606606
splitter(<<>>, Right, RelPos) ->
607607
split_iolist(Right, RelPos);
608-
splitter(Left, [A | Right], RelPos) when is_list(A) or is_binary(A) ->
608+
splitter(Left, [A | Right], RelPos) when is_list(A) orelse is_binary(A) ->
609609
Sz = erlang:iolist_size(A),
610610
case Sz > RelPos of
611611
true ->
@@ -629,7 +629,7 @@ skip_iolist(L, Pos) when is_list(L) ->
629629

630630
skipper(Right, 0) ->
631631
Right;
632-
skipper([A | Right], RelPos) when is_list(A) or is_binary(A) ->
632+
skipper([A | Right], RelPos) when is_list(A) orelse is_binary(A) ->
633633
Sz = erlang:iolist_size(A),
634634
case Sz > RelPos of
635635
true ->

lib/common_test/src/ct_framework.erl

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -410,7 +410,7 @@ add_defaults1(Mod,Func, GroupPath, SuiteInfo) ->
410410
SuiteReqs =
411411
[SDDef || SDDef <- SuiteInfo,
412412
((require == element(1,SDDef))
413-
or (default_config == element(1,SDDef)))],
413+
orelse (default_config == element(1,SDDef)))],
414414
case check_for_clashes(TestCaseInfo, GroupPathInfo,
415415
SuiteReqs) of
416416
[] ->
@@ -461,11 +461,11 @@ remove_info_in_prev(Terms, [[] | Rest]) ->
461461
[[] | remove_info_in_prev(Terms, Rest)];
462462
remove_info_in_prev(Terms, [Info | Rest]) ->
463463
UniqueInInfo = [U || U <- Info,
464-
((timetrap == element(1,U)) and
465-
(not lists:keymember(timetrap,1,Terms))) or
466-
((require == element(1,U)) and
467-
(not lists:member(U,Terms))) or
468-
((default_config == element(1,U)) and
464+
((timetrap == element(1,U)) andalso
465+
(not lists:keymember(timetrap,1,Terms))) orelse
466+
((require == element(1,U)) andalso
467+
(not lists:member(U,Terms))) orelse
468+
((default_config == element(1,U)) andalso
469469
(not keysmember([default_config,1,
470470
element(2,U),2], Terms)))],
471471
OtherTermsInInfo = [T || T <- Info,

lib/common_test/src/ct_groups.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,7 @@ find_groups1(Mod, GrNames, TCs, GroupDefs) ->
5858
Path ->
5959
{Path,true}
6060
end,
61-
TCs1 = if (is_atom(TCs) and (TCs /= all)) or is_tuple(TCs) ->
61+
TCs1 = if (is_atom(TCs) andalso (TCs /= all)) orelse is_tuple(TCs) ->
6262
[TCs];
6363
true ->
6464
TCs

lib/common_test/src/ct_logs.erl

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -822,7 +822,7 @@ logger_loop(State) ->
822822
end,
823823
if Importance >= (100-VLvl) ->
824824
CtLogFd = State#logger_state.ct_log_fd,
825-
DoEscChars = State#logger_state.tc_esc_chars and EscChars,
825+
DoEscChars = State#logger_state.tc_esc_chars andalso EscChars,
826826
case get_groupleader(Pid, GL, State) of
827827
{tc_log,TCGL,TCGLs} ->
828828
case erlang:is_process_alive(TCGL) of
@@ -1494,7 +1494,7 @@ make_one_index_entry1(SuiteName, Link, Label, Success, Fail, UserSkip, AutoSkip,
14941494
integer_to_list(NotBuilt),"</a></td>\n"]
14951495
end,
14961496
FailStr =
1497-
if (Fail > 0) or (NotBuilt > 0) or
1497+
if (Fail > 0) orelse (NotBuilt > 0) orelse
14981498
((Success+Fail+UserSkip+AutoSkip) == 0) ->
14991499
["<font color=\"red\">",
15001500
integer_to_list(Fail),"</font>"];
@@ -2273,7 +2273,7 @@ runentry(Dir, undefined, _) ->
22732273
runentry(Dir, Totals={Node,Label,Logs,
22742274
{TotSucc,TotFail,UserSkip,AutoSkip,NotBuilt}}, Index) ->
22752275
TotFailStr =
2276-
if (TotFail > 0) or (NotBuilt > 0) or
2276+
if (TotFail > 0) orelse (NotBuilt > 0) orelse
22772277
((TotSucc+TotFail+UserSkip+AutoSkip) == 0) ->
22782278
["<font color=\"red\">",
22792279
integer_to_list(TotFail),"</font>"];

lib/common_test/src/ct_run.erl

Lines changed: 19 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1272,23 +1272,23 @@ run_dir(Opts = #opts{logdir = LogDir,
12721272
true -> D end || D <- Dirs],
12731273
reformat_result(catch do_run(tests(Dirs1), [], Opts1, StartOpts));
12741274

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

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

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

1286-
{undefined,Suite,[]} when is_atom(Suite) and
1286+
{undefined,Suite,[]} when is_atom(Suite) andalso
12871287
(Suite /= undefined) ->
12881288
{Dir,Mod} = suite_to_test(Suite),
12891289
reformat_result(catch do_run(tests(Dir, Mod), [], Opts1, StartOpts));
12901290

1291-
{undefined,Suite,GsAndCs} when is_atom(Suite) and
1291+
{undefined,Suite,GsAndCs} when is_atom(Suite) andalso
12921292
(Suite /= undefined) ->
12931293
{Dir,Mod} = suite_to_test(Suite),
12941294
reformat_result(catch do_run(tests(Dir, Mod, GsAndCs),
@@ -1298,8 +1298,8 @@ run_dir(Opts = #opts{logdir = LogDir,
12981298
exit({error,multiple_suites_and_cases});
12991299

13001300
{undefined,Suite=[Hd|Tl],GsAndCs} when is_integer(Hd) ;
1301-
(is_list(Hd) and (Tl == [])) ;
1302-
(is_atom(Hd) and (Tl == [])) ->
1301+
(is_list(Hd) andalso (Tl == [])) ;
1302+
(is_atom(Hd) andalso (Tl == [])) ->
13031303
{Dir,Mod} = suite_to_test(Suite),
13041304
reformat_result(catch do_run(tests(Dir, Mod, GsAndCs),
13051305
[], Opts1, StartOpts));
@@ -1311,18 +1311,18 @@ run_dir(Opts = #opts{logdir = LogDir,
13111311
exit({error,incorrect_start_options});
13121312

13131313
{Dir,Suite,GsAndCs} when is_integer(hd(Dir)) ;
1314-
(is_atom(Dir) and (Dir /= undefined)) ;
1315-
((length(Dir) == 1) and is_atom(hd(Dir))) ;
1316-
((length(Dir) == 1) and is_list(hd(Dir))) ->
1314+
(is_atom(Dir) andalso (Dir /= undefined)) ;
1315+
((length(Dir) == 1) andalso is_atom(hd(Dir))) ;
1316+
((length(Dir) == 1) andalso is_list(hd(Dir))) ->
13171317
Dir1 = if is_atom(Dir) -> atom_to_list(Dir);
13181318
true -> Dir end,
13191319
if Suite == undefined ->
13201320
exit({error,incorrect_start_options});
13211321

13221322
is_integer(hd(Suite)) ;
1323-
(is_atom(Suite) and (Suite /= undefined)) ;
1324-
((length(Suite) == 1) and is_atom(hd(Suite))) ;
1325-
((length(Suite) == 1) and is_list(hd(Suite))) ->
1323+
(is_atom(Suite) andalso (Suite /= undefined)) ;
1324+
((length(Suite) == 1) andalso is_atom(hd(Suite))) ;
1325+
((length(Suite) == 1) andalso is_list(hd(Suite))) ->
13261326
{Dir2,Mod} = suite_to_test(Dir1, Suite),
13271327
case GsAndCs of
13281328
[] ->
@@ -1608,20 +1608,20 @@ suite_to_test(Dir, Suite) when is_list(Suite) ->
16081608
{DirName,list_to_atom(filename:rootname(File))}
16091609
end.
16101610

1611-
groups_and_cases(Gs, Cs) when ((Gs == undefined) or (Gs == [])) and
1612-
((Cs == undefined) or (Cs == [])) ->
1611+
groups_and_cases(Gs, Cs) when ((Gs == undefined) orelse (Gs == [])) andalso
1612+
((Cs == undefined) orelse (Cs == [])) ->
16131613
[];
16141614
groups_and_cases(Gs, Cs) when Gs == undefined ; Gs == [] ->
1615-
if (Cs == all) or (Cs == [all]) or (Cs == ["all"]) -> all;
1615+
if (Cs == all) orelse (Cs == [all]) orelse (Cs == ["all"]) -> all;
16161616
true -> [ensure_atom(C) || C <- listify(Cs)]
16171617
end;
16181618
groups_and_cases(GOrGs, Cs) when (is_atom(GOrGs) orelse
16191619
(is_list(GOrGs) andalso
16201620
(is_atom(hd(GOrGs)) orelse
16211621
(is_list(hd(GOrGs)) andalso
16221622
is_atom(hd(hd(GOrGs))))))) ->
1623-
if (Cs == undefined) or (Cs == []) or
1624-
(Cs == all) or (Cs == [all]) or (Cs == ["all"]) ->
1623+
if (Cs == undefined) orelse (Cs == []) orelse
1624+
(Cs == all) orelse (Cs == [all]) orelse (Cs == ["all"]) ->
16251625
[{GOrGs,all}];
16261626
true ->
16271627
[{GOrGs,[ensure_atom(C) || C <- listify(Cs)]}]
@@ -1630,7 +1630,7 @@ groups_and_cases(Gs, Cs) when is_integer(hd(hd(Gs))) ->
16301630
%% if list of strings, this comes from 'ct_run -group G1 G2 ...' and
16311631
%% we need to parse the strings
16321632
Gs1 =
1633-
if (Gs == [all]) or (Gs == ["all"]) ->
1633+
if (Gs == [all]) orelse (Gs == ["all"]) ->
16341634
all;
16351635
true ->
16361636
lists:map(fun(G) ->
@@ -2358,7 +2358,7 @@ start_cover(Opts=#opts{coverspec=CovData,cover_stop=CovStop},LogDir) ->
23582358
[TsCoverInfo]),
23592359

23602360
%% start cover on specified nodes
2361-
if (CovNodes /= []) and (CovNodes /= undefined) ->
2361+
if (CovNodes /= []) andalso (CovNodes /= undefined) ->
23622362
ct_logs:log("COVER INFO",
23632363
"Nodes included in cover "
23642364
"session: ~tw",

lib/common_test/src/ct_slave.erl

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

lib/common_test/src/ct_telnet.erl

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

11841184
convert_pattern(Pattern0,Seq)
1185-
when Pattern0==[] orelse (is_list(Pattern0) and not is_integer(hd(Pattern0))) ->
1185+
when Pattern0==[] orelse (is_list(Pattern0) andalso not is_integer(hd(Pattern0))) ->
11861186
Pattern =
11871187
case Seq of
11881188
true -> Pattern0;

lib/common_test/src/ct_testspec.erl

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -472,10 +472,10 @@ replace_names(Terms) ->
472472
throw({illegal_name_in_testspec,Name});
473473
true ->
474474
[First|_] = atom_to_list(Name),
475-
if ((First == $?) or (First == $$)
476-
or (First == $_)
477-
or ((First >= $A)
478-
and (First =< $Z))) ->
475+
if ((First == $?) orelse (First == $$)
476+
orelse (First == $_)
477+
orelse ((First >= $A)
478+
andalso (First =< $Z))) ->
479479
[Def];
480480
true ->
481481
throw({illegal_name_in_testspec,
@@ -1297,14 +1297,14 @@ insert_groups(Node,Dir,Suite,Group,Cases,Tests,MergeTests)
12971297
when is_atom(Group); is_tuple(Group) ->
12981298
insert_groups(Node,Dir,Suite,[Group],Cases,Tests,MergeTests);
12991299
insert_groups(Node,Dir,Suite,Groups,Cases,Tests,false) when
1300-
((Cases == all) or is_list(Cases)) and is_list(Groups) ->
1300+
((Cases == all) orelse is_list(Cases)) andalso is_list(Groups) ->
13011301
Groups1 = [if is_list(Gr) -> % preserve group path
13021302
{[Gr],Cases};
13031303
true ->
13041304
{Gr,Cases} end || Gr <- Groups],
13051305
append({{Node,Dir},[{Suite,Groups1}]},Tests);
13061306
insert_groups(Node,Dir,Suite,Groups,Cases,Tests,true) when
1307-
((Cases == all) or is_list(Cases)) and is_list(Groups) ->
1307+
((Cases == all) orelse is_list(Cases)) andalso is_list(Groups) ->
13081308
Groups1 = [if is_list(Gr) -> % preserve group path
13091309
{[Gr],Cases};
13101310
true ->
@@ -1416,11 +1416,11 @@ skip_groups(Node,Dir,Suite,Groups,Case,Cmt,Tests,MergeTests)
14161416
when is_atom(Case),Case =/= all ->
14171417
skip_groups(Node,Dir,Suite,Groups,[Case],Cmt,Tests,MergeTests);
14181418
skip_groups(Node,Dir,Suite,Groups,Cases,Cmt,Tests,false) when
1419-
((Cases == all) or is_list(Cases)) and is_list(Groups) ->
1419+
((Cases == all) orelse is_list(Cases)) andalso is_list(Groups) ->
14201420
Suites1 = skip_groups1(Suite,[{Gr,Cases} || Gr <- Groups],Cmt,[]),
14211421
append({{Node,Dir},Suites1},Tests);
14221422
skip_groups(Node,Dir,Suite,Groups,Cases,Cmt,Tests,true) when
1423-
((Cases == all) or is_list(Cases)) and is_list(Groups) ->
1423+
((Cases == all) orelse is_list(Cases)) andalso is_list(Groups) ->
14241424
{Tests1,Done} =
14251425
lists:foldr(fun({{N,D},Suites0},{Merged,_}) when N == Node,
14261426
D == Dir ->
@@ -1577,7 +1577,7 @@ is_node([master|_],_Nodes) ->
15771577
is_node(What={N,H},Nodes) when is_atom(N), is_atom(H) ->
15781578
is_node([What],Nodes);
15791579
is_node([What|_],Nodes) ->
1580-
case lists:keymember(What,1,Nodes) or
1580+
case lists:keymember(What,1,Nodes) orelse
15811581
lists:keymember(What,2,Nodes) of
15821582
true ->
15831583
true;

lib/common_test/src/test_server_ctrl.erl

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

23302330
run_test_cases_loop([{SkipTag,CaseData={Type,_Ref,_Case,_Comment}}|Cases],
23312331
Config, TimetrapData, Mode, Status) when
2332-
((SkipTag==auto_skip_case) or (SkipTag==skip_case)) and
2333-
((Type==conf) or (Type==make)) ->
2332+
((SkipTag==auto_skip_case) orelse (SkipTag==skip_case)) andalso
2333+
((Type==conf) orelse (Type==make)) ->
23342334
run_test_cases_loop([{SkipTag,CaseData,Mode}|Cases],
23352335
Config, TimetrapData, Mode, Status);
23362336

23372337
run_test_cases_loop([{SkipTag,{Type,Ref,Case,Comment},SkipMode}|Cases],
23382338
Config, TimetrapData, Mode, Status) when
2339-
((SkipTag==auto_skip_case) or (SkipTag==skip_case)) and
2340-
((Type==conf) or (Type==make)) ->
2339+
((SkipTag==auto_skip_case) orelse (SkipTag==skip_case)) andalso
2340+
((Type==conf) orelse (Type==make)) ->
23412341
ok = file:set_cwd(filename:dirname(get(test_server_dir))),
23422342
CurrIOHandler = get(test_server_common_io_handler),
23432343
ParentMode = tl(Mode),
@@ -2802,7 +2802,7 @@ run_test_cases_loop([{conf,Ref,Props,{Mod,Func}}|_Cases]=Cs0,
28022802
stop_minor_log_file(),
28032803
run_test_cases_loop(Cases2, Config1, TimetrapData, Mode, Status3);
28042804

2805-
{_,{Skip,Reason},_} when StartConf and ((Skip==skip) or (Skip==skipped)) ->
2805+
{_,{Skip,Reason},_} when StartConf andalso ((Skip==skip) orelse (Skip==skipped)) ->
28062806
ReportAbortRepeat(skipped),
28072807
print(minor, "~n*** ~tw skipped.~n"
28082808
" Skipping all cases.", [Func]),

lib/compiler/src/beam_dict.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -215,7 +215,7 @@ line([{location,Name,Line}|_], #asm{lines=Lines,num_lines=N,
215215
when is_atom(Instr) ->
216216
{FnameIndex,Dict1} = fname(Name, Dict0),
217217
Key = {FnameIndex,Line},
218-
ExecLine = ExecLine0 or (Instr =:= executable_line),
218+
ExecLine = ExecLine0 orelse (Instr =:= executable_line),
219219
case Lines of
220220
#{Key := Index} ->
221221
{Index,Dict1#asm{num_lines=N+1,exec_line=ExecLine}};

0 commit comments

Comments
 (0)