From a7f60e4383313fdc802105725ca51ec8067a4c28 Mon Sep 17 00:00:00 2001 From: Richard Carlsson Date: Tue, 26 Nov 2024 17:32:07 +0100 Subject: [PATCH] Replace 'or'/'and' with 'orelse'/'andalso' respectively --- erts/preloaded/src/prim_zip.erl | 4 +- lib/common_test/src/ct_framework.erl | 12 +++--- lib/common_test/src/ct_groups.erl | 2 +- lib/common_test/src/ct_logs.erl | 6 +-- lib/common_test/src/ct_run.erl | 38 +++++++++--------- lib/common_test/src/ct_slave.erl | 2 +- lib/common_test/src/ct_telnet.erl | 2 +- lib/common_test/src/ct_testspec.erl | 18 ++++----- lib/common_test/src/test_server_ctrl.erl | 10 ++--- lib/compiler/src/beam_dict.erl | 2 +- lib/compiler/src/beam_ssa_opt.erl | 2 +- lib/compiler/src/beam_types.erl | 8 ++-- lib/compiler/src/cerl_inline.erl | 8 ++-- lib/compiler/src/sys_pre_attributes.erl | 2 +- lib/compiler/src/v3_core.erl | 4 +- lib/dialyzer/src/dialyzer_dataflow.erl | 2 +- lib/dialyzer/src/dialyzer_utils.erl | 11 ++--- lib/dialyzer/src/erl_types.erl | 2 +- lib/diameter/src/info/diameter_info.erl | 2 +- lib/et/examples/et_demo.erl | 6 +-- lib/eunit/src/eunit_data.erl | 14 +++---- lib/inets/src/http_client/httpc_response.erl | 2 +- lib/inets/src/http_lib/http_chunk.erl | 2 +- .../src/http_server/httpd_request_handler.erl | 2 +- lib/inets/src/http_server/mod_cgi.erl | 2 +- lib/inets/src/http_server/mod_esi.erl | 2 +- lib/kernel/src/application.erl | 4 +- lib/kernel/src/disk_log_server.erl | 2 +- lib/kernel/src/file_io_server.erl | 4 +- lib/kernel/src/inet_dns.erl | 4 +- lib/kernel/src/os.erl | 2 +- lib/megaco/src/app/megaco.erl | 2 +- lib/megaco/src/engine/megaco_config.erl | 10 ++--- lib/megaco/src/engine/megaco_digit_map.erl | 6 +-- .../src/engine/megaco_erl_dist_encoder.erl | 2 +- lib/megaco/src/engine/megaco_messenger.erl | 6 +-- .../src/engine/megaco_messenger_misc.erl | 10 ++--- lib/megaco/src/engine/megaco_sdp.erl | 14 +++---- lib/megaco/src/engine/megaco_timer.erl | 10 ++--- lib/megaco/src/flex/megaco_flex_scanner.erl | 2 +- lib/megaco/src/text/megaco_text_gen_v2.hrl | 2 +- lib/megaco/src/text/megaco_text_gen_v3.hrl | 40 +++++++++---------- lib/megaco/src/text/megaco_text_scanner.erl | 2 +- lib/mnesia/src/mnesia_controller.erl | 2 +- lib/mnesia/src/mnesia_dumper.erl | 2 +- lib/mnesia/src/mnesia_loader.erl | 2 +- lib/mnesia/src/mnesia_monitor.erl | 4 +- lib/mnesia/src/mnesia_recover.erl | 8 ++-- lib/mnesia/src/mnesia_schema.erl | 6 +-- lib/mnesia/src/mnesia_tm.erl | 2 +- lib/parsetools/src/leex.erl | 6 +-- lib/parsetools/src/yecc.erl | 2 +- lib/public_key/src/pubkey_cert.erl | 2 +- lib/public_key/src/pubkey_crl.erl | 8 ++-- lib/public_key/src/pubkey_pbe.erl | 6 +-- lib/public_key/src/public_key.erl | 6 +-- lib/snmp/src/agent/snmpa_conf.erl | 36 ++++++++--------- lib/snmp/src/agent/snmpa_get.erl | 2 +- lib/snmp/src/agent/snmpa_supervisor.erl | 4 +- lib/snmp/src/misc/snmp_config.erl | 6 +-- lib/snmp/src/misc/snmp_log.erl | 2 +- lib/ssh/src/ssh_connection.erl | 2 +- lib/ssh/src/ssh_connection_handler.erl | 2 +- lib/ssh/src/ssh_lib.erl | 8 ++-- lib/ssl/src/ssl_cipher.erl | 8 ++-- lib/ssl/src/ssl_gen_statem.erl | 4 +- lib/ssl/src/ssl_handshake.erl | 4 +- lib/stdlib/examples/erl_id_trans.erl | 12 +++--- lib/stdlib/src/dets.erl | 4 +- lib/stdlib/src/dets_v9.erl | 14 +++---- lib/stdlib/src/erl_error.erl | 2 +- lib/stdlib/src/erl_eval.erl | 2 +- lib/stdlib/src/erl_lint.erl | 8 ++-- lib/stdlib/src/erl_pp.erl | 2 +- lib/stdlib/src/erl_stdlib_errors.erl | 2 +- lib/stdlib/src/erl_tar.erl | 2 +- lib/stdlib/src/escript.erl | 2 +- lib/stdlib/src/filename.erl | 2 +- lib/stdlib/src/io_lib_fread.erl | 4 +- lib/stdlib/src/io_lib_pretty.erl | 6 +-- lib/stdlib/src/ms_transform.erl | 12 +++--- lib/stdlib/src/proc_lib.erl | 2 +- lib/stdlib/src/qlc.erl | 18 ++++----- lib/stdlib/src/qlc_pt.erl | 2 +- lib/stdlib/src/shell.erl | 2 +- lib/stdlib/src/shell_docs.erl | 2 +- lib/stdlib/src/sofs.erl | 10 ++--- lib/stdlib/src/unicode.erl | 4 +- lib/syntax_tools/src/erl_prettypr.erl | 2 +- lib/syntax_tools/src/erl_syntax.erl | 2 +- lib/syntax_tools/src/erl_syntax_lib.erl | 4 +- lib/syntax_tools/src/prettypr.erl | 6 +-- lib/tftp/src/tftp_lib.erl | 4 +- lib/wx/examples/simple/menu.erl | 2 +- lib/wx/examples/sudoku/sudoku_game.erl | 4 +- lib/xmerl/src/xmerl_scan.erl | 4 +- lib/xmerl/src/xmerl_xpath_pred.erl | 4 +- 97 files changed, 285 insertions(+), 284 deletions(-) diff --git a/erts/preloaded/src/prim_zip.erl b/erts/preloaded/src/prim_zip.erl index f1cfb4dafce9..604c7acfaf68 100644 --- a/erts/preloaded/src/prim_zip.erl +++ b/erts/preloaded/src/prim_zip.erl @@ -605,7 +605,7 @@ splitter(Left, Right, 0) -> {Left, Right}; splitter(<<>>, Right, RelPos) -> split_iolist(Right, RelPos); -splitter(Left, [A | Right], RelPos) when is_list(A) or is_binary(A) -> +splitter(Left, [A | Right], RelPos) when is_list(A) orelse is_binary(A) -> Sz = erlang:iolist_size(A), case Sz > RelPos of true -> @@ -629,7 +629,7 @@ skip_iolist(L, Pos) when is_list(L) -> skipper(Right, 0) -> Right; -skipper([A | Right], RelPos) when is_list(A) or is_binary(A) -> +skipper([A | Right], RelPos) when is_list(A) orelse is_binary(A) -> Sz = erlang:iolist_size(A), case Sz > RelPos of true -> diff --git a/lib/common_test/src/ct_framework.erl b/lib/common_test/src/ct_framework.erl index 423e01c8e0f7..a2496dd162b7 100644 --- a/lib/common_test/src/ct_framework.erl +++ b/lib/common_test/src/ct_framework.erl @@ -410,7 +410,7 @@ add_defaults1(Mod,Func, GroupPath, SuiteInfo) -> SuiteReqs = [SDDef || SDDef <- SuiteInfo, ((require == element(1,SDDef)) - or (default_config == element(1,SDDef)))], + orelse (default_config == element(1,SDDef)))], case check_for_clashes(TestCaseInfo, GroupPathInfo, SuiteReqs) of [] -> @@ -461,11 +461,11 @@ 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 + ((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, diff --git a/lib/common_test/src/ct_groups.erl b/lib/common_test/src/ct_groups.erl index 08257706b2fa..791a46bea730 100644 --- a/lib/common_test/src/ct_groups.erl +++ b/lib/common_test/src/ct_groups.erl @@ -58,7 +58,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) andalso (TCs /= all)) orelse is_tuple(TCs) -> [TCs]; true -> TCs diff --git a/lib/common_test/src/ct_logs.erl b/lib/common_test/src/ct_logs.erl index 71d821681ba2..b9135b931c9d 100644 --- a/lib/common_test/src/ct_logs.erl +++ b/lib/common_test/src/ct_logs.erl @@ -822,7 +822,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 @@ -1494,7 +1494,7 @@ make_one_index_entry1(SuiteName, Link, Label, Success, Fail, UserSkip, AutoSkip, integer_to_list(NotBuilt),"\n"] end, FailStr = - if (Fail > 0) or (NotBuilt > 0) or + if (Fail > 0) orelse (NotBuilt > 0) orelse ((Success+Fail+UserSkip+AutoSkip) == 0) -> ["", integer_to_list(Fail),""]; @@ -2273,7 +2273,7 @@ runentry(Dir, undefined, _) -> runentry(Dir, Totals={Node,Label,Logs, {TotSucc,TotFail,UserSkip,AutoSkip,NotBuilt}}, Index) -> TotFailStr = - if (TotFail > 0) or (NotBuilt > 0) or + if (TotFail > 0) orelse (NotBuilt > 0) orelse ((TotSucc+TotFail+UserSkip+AutoSkip) == 0) -> ["", integer_to_list(TotFail),""]; diff --git a/lib/common_test/src/ct_run.erl b/lib/common_test/src/ct_run.erl index d6d35a8ad29a..b82f41be95c0 100644 --- a/lib/common_test/src/ct_run.erl +++ b/lib/common_test/src/ct_run.erl @@ -1272,10 +1272,10 @@ 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) andalso 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) andalso (Dir /= undefined) -> reformat_result(catch do_run(tests(atom_to_list(Dir)), [], Opts1, StartOpts)); @@ -1283,12 +1283,12 @@ run_dir(Opts = #opts{logdir = LogDir, Suites1 = [suite_to_test(S) || S <- Suites], reformat_result(catch do_run(tests(Suites1), [], Opts1, StartOpts)); - {undefined,Suite,[]} when is_atom(Suite) and + {undefined,Suite,[]} when is_atom(Suite) andalso (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 + {undefined,Suite,GsAndCs} when is_atom(Suite) andalso (Suite /= undefined) -> {Dir,Mod} = suite_to_test(Suite), reformat_result(catch do_run(tests(Dir, Mod, GsAndCs), @@ -1298,8 +1298,8 @@ run_dir(Opts = #opts{logdir = LogDir, 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 == [])) -> + (is_list(Hd) andalso (Tl == [])) ; + (is_atom(Hd) andalso (Tl == [])) -> {Dir,Mod} = suite_to_test(Suite), reformat_result(catch do_run(tests(Dir, Mod, GsAndCs), [], Opts1, StartOpts)); @@ -1311,18 +1311,18 @@ run_dir(Opts = #opts{logdir = LogDir, 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))) -> + (is_atom(Dir) andalso (Dir /= undefined)) ; + ((length(Dir) == 1) andalso is_atom(hd(Dir))) ; + ((length(Dir) == 1) andalso is_list(hd(Dir))) -> 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_atom(Suite) andalso (Suite /= undefined)) ; + ((length(Suite) == 1) andalso is_atom(hd(Suite))) ; + ((length(Suite) == 1) andalso is_list(hd(Suite))) -> {Dir2,Mod} = suite_to_test(Dir1, Suite), case GsAndCs of [] -> @@ -1608,11 +1608,11 @@ 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 == [])) andalso + ((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) orelse (Cs == [all]) orelse (Cs == ["all"]) -> all; true -> [ensure_atom(C) || C <- listify(Cs)] end; groups_and_cases(GOrGs, Cs) when (is_atom(GOrGs) orelse @@ -1620,8 +1620,8 @@ groups_and_cases(GOrGs, Cs) when (is_atom(GOrGs) orelse (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) orelse (Cs == []) orelse + (Cs == all) orelse (Cs == [all]) orelse (Cs == ["all"]) -> [{GOrGs,all}]; true -> [{GOrGs,[ensure_atom(C) || C <- listify(Cs)]}] @@ -1630,7 +1630,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]) orelse (Gs == ["all"]) -> all; true -> lists:map(fun(G) -> @@ -2358,7 +2358,7 @@ start_cover(Opts=#opts{coverspec=CovData,cover_stop=CovStop},LogDir) -> [TsCoverInfo]), %% start cover on specified nodes - if (CovNodes /= []) and (CovNodes /= undefined) -> + if (CovNodes /= []) andalso (CovNodes /= undefined) -> ct_logs:log("COVER INFO", "Nodes included in cover " "session: ~tw", diff --git a/lib/common_test/src/ct_slave.erl b/lib/common_test/src/ct_slave.erl index c361bb90a233..2dc2d84eff11 100644 --- a/lib/common_test/src/ct_slave.erl +++ b/lib/common_test/src/ct_slave.erl @@ -348,7 +348,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)) andalso Options#options.kill_if_fail-> do_stop(ENode); _-> ok diff --git a/lib/common_test/src/ct_telnet.erl b/lib/common_test/src/ct_telnet.erl index c227799b692b..9607170d0638 100644 --- a/lib/common_test/src/ct_telnet.erl +++ b/lib/common_test/src/ct_telnet.erl @@ -1188,7 +1188,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==[] orelse (is_list(Pattern0) andalso not is_integer(hd(Pattern0))) -> Pattern = case Seq of true -> Pattern0; diff --git a/lib/common_test/src/ct_testspec.erl b/lib/common_test/src/ct_testspec.erl index 0af4fc844813..9c3ca6acc4be 100644 --- a/lib/common_test/src/ct_testspec.erl +++ b/lib/common_test/src/ct_testspec.erl @@ -472,10 +472,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 == $?) orelse (First == $$) + orelse (First == $_) + orelse ((First >= $A) + andalso (First =< $Z))) -> [Def]; true -> throw({illegal_name_in_testspec, @@ -1297,14 +1297,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)) andalso 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)) andalso is_list(Groups) -> Groups1 = [if is_list(Gr) -> % preserve group path {[Gr],Cases}; true -> @@ -1416,11 +1416,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)) andalso 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)) andalso is_list(Groups) -> {Tests1,Done} = lists:foldr(fun({{N,D},Suites0},{Merged,_}) when N == Node, D == Dir -> @@ -1577,7 +1577,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; diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl index 193b0e80767f..2470e8db8b30 100644 --- a/lib/common_test/src/test_server_ctrl.erl +++ b/lib/common_test/src/test_server_ctrl.erl @@ -2348,15 +2348,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)) andalso + ((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)) andalso + ((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), @@ -2821,7 +2821,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 andalso ((Skip==skip) orelse (Skip==skipped)) -> ReportAbortRepeat(skipped), print(minor, "~n*** ~tw skipped.~n" " Skipping all cases.", [Func]), diff --git a/lib/compiler/src/beam_dict.erl b/lib/compiler/src/beam_dict.erl index 51f144e40802..8da636303eeb 100644 --- a/lib/compiler/src/beam_dict.erl +++ b/lib/compiler/src/beam_dict.erl @@ -215,7 +215,7 @@ line([{location,Name,Line}|_], #asm{lines=Lines,num_lines=N, when is_atom(Instr) -> {FnameIndex,Dict1} = fname(Name, Dict0), Key = {FnameIndex,Line}, - ExecLine = ExecLine0 or (Instr =:= executable_line), + ExecLine = ExecLine0 orelse (Instr =:= executable_line), case Lines of #{Key := Index} -> {Index,Dict1#asm{num_lines=N+1,exec_line=ExecLine}}; diff --git a/lib/compiler/src/beam_ssa_opt.erl b/lib/compiler/src/beam_ssa_opt.erl index 82bde660df3b..2c46bdd3cb7b 100644 --- a/lib/compiler/src/beam_ssa_opt.erl +++ b/lib/compiler/src/beam_ssa_opt.erl @@ -3284,7 +3284,7 @@ unfold_literals([], _, _, Blocks) -> Blocks. unfold_update_succ([S|Ss], Safe, SafeMap0) -> - F = fun(Prev) -> Prev and Safe end, + F = fun(Prev) -> Prev andalso Safe end, SafeMap = maps:update_with(S, F, Safe, SafeMap0), unfold_update_succ(Ss, Safe, SafeMap); unfold_update_succ([], _, SafeMap) -> diff --git a/lib/compiler/src/beam_types.erl b/lib/compiler/src/beam_types.erl index 500b0d7220d2..2659109c517a 100644 --- a/lib/compiler/src/beam_types.erl +++ b/lib/compiler/src/beam_types.erl @@ -840,7 +840,7 @@ glb(#t_atom{elements=any}, #t_atom{elements=[_|_]}=T) -> T; glb(#t_bitstring{size_unit=U1,appendable=A1}, #t_bitstring{size_unit=U2,appendable=A2}) -> - #t_bitstring{size_unit=U1 * U2 div gcd(U1, U2),appendable=A1 or A2}; + #t_bitstring{size_unit=U1 * U2 div gcd(U1, U2),appendable=A1 orelse A2}; glb(#t_bitstring{size_unit=UnitA,appendable=Appendable}=T, #t_bs_matchable{tail_unit=UnitB}) -> Unit = UnitA * UnitB div gcd(UnitA, UnitB), @@ -971,7 +971,7 @@ glb_tuples(#t_tuple{size=Sz1,exact=Ex1}, #t_tuple{size=Sz2,exact=Ex2}) glb_tuples(#t_tuple{size=Sz1,exact=Ex1,elements=Es1}, #t_tuple{size=Sz2,exact=Ex2,elements=Es2}) -> Size = max(Sz1, Sz2), - Exact = Ex1 or Ex2, + Exact = Ex1 orelse Ex2, case glb_elements(Es1, Es2) of none -> none; @@ -1036,7 +1036,7 @@ lub(#t_atom{elements=any}=T, #t_atom{elements=[_|_]}) -> T; lub(#t_atom{elements=[_|_]}, #t_atom{elements=any}=T) -> T; lub(#t_bitstring{size_unit=U1,appendable=A1}, #t_bitstring{size_unit=U2,appendable=A2}) -> - #t_bitstring{size_unit=gcd(U1, U2),appendable=A1 and A2}; + #t_bitstring{size_unit=gcd(U1, U2),appendable=A1 andalso A2}; lub(#t_bitstring{size_unit=U1}, #t_bs_context{tail_unit=U2}) -> #t_bs_matchable{tail_unit=gcd(U1, U2)}; lub(#t_bitstring{size_unit=UnitA}, #t_bs_matchable{tail_unit=UnitB}) -> @@ -1106,7 +1106,7 @@ lub(#t_map{super_key=SKeyA,super_value=SValueA}, #t_map{super_key=SKey,super_value=SValue}; lub(#t_tuple{size=Sz,exact=ExactA,elements=EsA}, #t_tuple{size=Sz,exact=ExactB,elements=EsB}) -> - Exact = ExactA and ExactB, + Exact = ExactA andalso ExactB, Es = lub_tuple_elements(Sz, EsA, EsB), #t_tuple{size=Sz,exact=Exact,elements=Es}; lub(#t_tuple{size=SzA,elements=EsA}, #t_tuple{size=SzB,elements=EsB}) -> diff --git a/lib/compiler/src/cerl_inline.erl b/lib/compiler/src/cerl_inline.erl index e1ce4d522e49..e53cd9ab51e3 100644 --- a/lib/compiler/src/cerl_inline.erl +++ b/lib/compiler/src/cerl_inline.erl @@ -1066,7 +1066,7 @@ i_call(E, Ctxt, Ren, Env, S) -> %% Check if the name of the called function is static. If so, %% discard the size counts performed above, since the values will %% not cause any runtime cost. - Static = is_c_atom(M) and is_c_atom(F), + Static = is_c_atom(M) andalso is_c_atom(F), S3 = case Static of true -> revert_size(S, S2); @@ -2274,7 +2274,7 @@ equivalent(E1, E2, Env) -> end. equivalent_lists([E1 | Es1], [E2 | Es2], Env) -> - equivalent(E1, E2, Env) and equivalent_lists(Es1, Es2, Env); + equivalent(E1, E2, Env) andalso equivalent_lists(Es1, Es2, Env); equivalent_lists([], [], _) -> true; equivalent_lists(_, _, _) -> @@ -2287,7 +2287,7 @@ reduce_bif_call(M, F, As, Env) -> reduce_bif_call_1(M, F, length(As), As, Env). reduce_bif_call_1(erlang, element, 2, [X, Y], _Env) -> - case is_c_int(X) and is_c_tuple(Y) of + case is_c_int(X) andalso is_c_tuple(Y) of true -> %% We are free to change the relative evaluation order of %% the elements, so lifting out a particular element is OK. @@ -2330,7 +2330,7 @@ reduce_bif_call_1(erlang, list_to_tuple, 1, [X], _Env) -> false end; reduce_bif_call_1(erlang, setelement, 3, [X, Y, Z], Env) -> - case is_c_int(X) and is_c_tuple(Y) of + case is_c_int(X) andalso is_c_tuple(Y) of true -> %% Here, unless `Z' is a simple expression, we must bind it %% to a new variable, because in that case, `Z' must be diff --git a/lib/compiler/src/sys_pre_attributes.erl b/lib/compiler/src/sys_pre_attributes.erl index 6daa1710e7f6..16739b5e6e25 100644 --- a/lib/compiler/src/sys_pre_attributes.erl +++ b/lib/compiler/src/sys_pre_attributes.erl @@ -201,7 +201,7 @@ report_verbose(Format, Args, S) -> end. is_warning(S) -> - lists:member(report_warnings, S#state.options) or is_verbose(S). + lists:member(report_warnings, S#state.options) orelse is_verbose(S). is_verbose(S) -> lists:member(verbose, S#state.options). diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl index 950e82d1a1d4..77ff31820581 100644 --- a/lib/compiler/src/v3_core.erl +++ b/lib/compiler/src/v3_core.erl @@ -210,7 +210,7 @@ module(Forms0, Opts) -> end, Cexp = [#c_var{name=FA} || {_,_}=FA <:- Exp], Kfs1 = reverse(Kfs0), - Kfs = if LoadNif and (Nifs =:= none) -> + Kfs = if LoadNif andalso (Nifs =:= none) -> insert_nif_start(Kfs1); true -> Kfs1 @@ -223,7 +223,7 @@ form({function,_,_,_,_}=F0, #imodule{defs=Defs,load_nif=LoadNif0}=Module, Opts) -> {F,Ws,LoadNif} = function(F0, Module, Opts), - Module#imodule{defs=[F|Defs],ws=Ws,load_nif=LoadNif or LoadNif0}; + Module#imodule{defs=[F|Defs],ws=Ws,load_nif=LoadNif orelse LoadNif0}; form({attribute,_,module,Mod}, Module, _Opts) -> true = is_atom(Mod), Module#imodule{name=Mod}; diff --git a/lib/dialyzer/src/dialyzer_dataflow.erl b/lib/dialyzer/src/dialyzer_dataflow.erl index 59494fa052b4..080a24b2ef5b 100644 --- a/lib/dialyzer/src/dialyzer_dataflow.erl +++ b/lib/dialyzer/src/dialyzer_dataflow.erl @@ -3548,7 +3548,7 @@ find_terminals_list(List) -> find_terminals_list([Tree|Left], Explicit1, Normal1) -> {Explicit2, Normal2} = find_terminals(Tree), - case {Explicit1 or Explicit2, Normal1 or Normal2} of + case {Explicit1 orelse Explicit2, Normal1 orelse Normal2} of {true, true} = Ans -> Ans; {NewExplicit, NewNormal} -> find_terminals_list(Left, NewExplicit, NewNormal) diff --git a/lib/dialyzer/src/dialyzer_utils.erl b/lib/dialyzer/src/dialyzer_utils.erl index ed6edeafdb37..ca6170fbc9d6 100644 --- a/lib/dialyzer/src/dialyzer_utils.erl +++ b/lib/dialyzer/src/dialyzer_utils.erl @@ -505,7 +505,7 @@ get_optional_callbacks(Tuples, ModName) -> get_spec_info([{Contract, Ln, [{Id, TypeSpec}]}|Left], SpecMap, CallbackMap, RecordsMap, ModName, OptCb, File) - when ((Contract =:= 'spec') or (Contract =:= 'callback')), + when ((Contract =:= 'spec') orelse (Contract =:= 'callback')), is_list(TypeSpec) -> MFA = case Id of {_, _, _} = T -> T; @@ -971,11 +971,11 @@ pp_flags([Flag|Flags]) -> pp_flags(Flags))). keep_endian(Flags) -> - [cerl:c_atom(X) || X <- Flags, (X =:= little) or (X =:= native)]. + [cerl:c_atom(X) || X <- Flags, (X =:= little) orelse (X =:= native)]. keep_all(Flags) -> [cerl:c_atom(X) || X <- Flags, - (X =:= little) or (X =:= native) or (X =:= signed)]. + (X =:= little) orelse (X =:= native) orelse (X =:= signed)]. pp_unit(Unit, Ctxt, Cont) -> case cerl:concrete(Unit) of @@ -1107,8 +1107,9 @@ refold_concrete_pat(Val) -> false -> label(cerl:c_tuple_skel(Els)) end; [H|T] -> - case cerl:is_literal(HP=refold_concrete_pat(H)) - and cerl:is_literal(TP=refold_concrete_pat(T)) + HP=refold_concrete_pat(H), + TP=refold_concrete_pat(T), + case cerl:is_literal(HP) andalso cerl:is_literal(TP) of true -> cerl:abstract(Val); false -> label(cerl:c_cons_skel(HP, TP)) diff --git a/lib/dialyzer/src/erl_types.erl b/lib/dialyzer/src/erl_types.erl index 2588e7aa240d..eac87796fe7f 100644 --- a/lib/dialyzer/src/erl_types.erl +++ b/lib/dialyzer/src/erl_types.erl @@ -3231,7 +3231,7 @@ t_subtract_aux(?int_range(From, To) = T1, ?int_set(Set)) -> true -> To - 1; false -> To end, - if (NewFrom =:= From) and (NewTo =:= To) -> T1; + if (NewFrom =:= From) andalso (NewTo =:= To) -> T1; true -> t_from_range(NewFrom, NewTo) end; t_subtract_aux(?int_set(Set), ?int_range(From, To)) -> diff --git a/lib/diameter/src/info/diameter_info.erl b/lib/diameter/src/info/diameter_info.erl index c65a3aa2743f..9eff530becaa 100644 --- a/lib/diameter/src/info/diameter_info.erl +++ b/lib/diameter/src/info/diameter_info.erl @@ -209,7 +209,7 @@ format(Local, Remote, SFun, CFun) %%% ---------------------------------------------------------- format(Tables, SFun) - when is_list(Tables), (is_function(SFun, 2) or is_function(SFun, 3)) -> + when is_list(Tables), (is_function(SFun, 2) orelse is_function(SFun, 3)) -> format(Tables, SFun, fun tab2list/1); format(Tables, CFun) diff --git a/lib/et/examples/et_demo.erl b/lib/et/examples/et_demo.erl index f06bcaf4b825..f57b39b0641f 100644 --- a/lib/et/examples/et_demo.erl +++ b/lib/et/examples/et_demo.erl @@ -195,9 +195,9 @@ plain_process_info(E) when is_record(E, event) -> %plain_process_info_nolink plain_process_info_nolink(E) when is_record(E, event) -> - (E#event.label /= link) and - (E#event.label /= unlink) and - (E#event.label /= getting_linked) and + (E#event.label /= link) andalso + (E#event.label /= unlink) andalso + (E#event.label /= getting_linked) andalso plain_process_info(E). %plain_process_info_nolink diff --git a/lib/eunit/src/eunit_data.erl b/lib/eunit/src/eunit_data.erl index 637de05e5c0c..53c1e3c4b262 100644 --- a/lib/eunit/src/eunit_data.erl +++ b/lib/eunit/src/eunit_data.erl @@ -488,8 +488,8 @@ group(#group{tests = T0, desc = Desc, options = Options, order = Order, case T1 of #test{desc = Desc1, timeout = Timeout1} when T2 =:= none, Spawn =:= undefined, Context =:= undefined, - ((Desc =:= undefined) or (Desc1 =:= undefined)), - ((Timeout =:= undefined) or (Timeout1 =:= undefined)) -> + ((Desc =:= undefined) orelse (Desc1 =:= undefined)), + ((Timeout =:= undefined) orelse (Timeout1 =:= undefined)) -> %% a single test within a non-spawn/setup group: put the %% information directly on the test; drop the order T1#test{desc = join_properties(Desc, Desc1), @@ -506,11 +506,11 @@ group(#group{tests = T0, desc = Desc, options = Options, order = Order, #group{desc = Desc1, order = Order1, context = Context1, spawn = Spawn1, timeout = Timeout1} when T2 =:= none, - ((Desc =:= undefined) or (Desc1 =:= undefined)), - ((Order =:= undefined) or (Order1 =:= undefined)), - ((Context =:= undefined) or (Context1 =:= undefined)), - ((Spawn =:= undefined) or (Spawn1 =:= undefined)), - ((Timeout =:= undefined) or (Timeout1 =:= undefined)) -> + ((Desc =:= undefined) orelse (Desc1 =:= undefined)), + ((Order =:= undefined) orelse (Order1 =:= undefined)), + ((Context =:= undefined) orelse (Context1 =:= undefined)), + ((Spawn =:= undefined) orelse (Spawn1 =:= undefined)), + ((Timeout =:= undefined) orelse (Timeout1 =:= undefined)) -> %% two nested groups with non-conflicting properties group(T1#group{desc = join_properties(Desc, Desc1), order = join_properties(Order, Order1), diff --git a/lib/inets/src/http_client/httpc_response.erl b/lib/inets/src/http_client/httpc_response.erl index 9ebea9bdbc68..7bf569a466ff 100644 --- a/lib/inets/src/http_client/httpc_response.erl +++ b/lib/inets/src/http_client/httpc_response.erl @@ -281,7 +281,7 @@ parse_headers(<>, Header, Headers, HTTPHeaders = [lists:reverse(Header) | Headers], Length = lists:foldl(fun(H, Acc) -> length(H) + Acc end, 0, HTTPHeaders), - case ((Length =< MaxHeaderSize) or (MaxHeaderSize == nolimit)) of + case ((Length =< MaxHeaderSize) orelse (MaxHeaderSize == nolimit)) of true -> ResponseHeaderRcord = http_response:headers(HTTPHeaders, #http_response_h{}), diff --git a/lib/inets/src/http_lib/http_chunk.erl b/lib/inets/src/http_lib/http_chunk.erl index 7ae74dcb7781..e6ff11403e37 100644 --- a/lib/inets/src/http_lib/http_chunk.erl +++ b/lib/inets/src/http_lib/http_chunk.erl @@ -235,7 +235,7 @@ decode_data(ChunkSize, TotalChunk, NewBody = <>, {?MODULE, decode_size, [<<>>, [], 0, {MaxBodySize, NewBody, AccLength, MaxHeaderSize}]}; <> - when (AccLength < MaxBodySize) or (MaxBodySize == nolimit) -> + when (AccLength < MaxBodySize) orelse (MaxBodySize == nolimit) -> decode_size(Rest, [], 0, {MaxBodySize, <>, AccLength, MaxHeaderSize}); diff --git a/lib/inets/src/http_server/httpd_request_handler.erl b/lib/inets/src/http_server/httpd_request_handler.erl index f96bf8a53137..085841175c2b 100644 --- a/lib/inets/src/http_server/httpd_request_handler.erl +++ b/lib/inets/src/http_server/httpd_request_handler.erl @@ -518,7 +518,7 @@ handle_body(#state{headers = Headers, body = Body, _ -> Length = list_to_integer(Headers#http_request_h.'content-length'), MaxChunk = max_client_body_chunk(ConfigDB), - case ((Length =< MaxBodySize) or (MaxBodySize == nolimit)) of + case ((Length =< MaxBodySize) orelse (MaxBodySize == nolimit)) of true -> case httpd_request:body_chunk_first(Body, Length, MaxChunk) of %% This is the case that the we need more data to complete diff --git a/lib/inets/src/http_server/mod_cgi.erl b/lib/inets/src/http_server/mod_cgi.erl index abcd69dd5b65..79aac7b0e5f6 100644 --- a/lib/inets/src/http_server/mod_cgi.erl +++ b/lib/inets/src/http_server/mod_cgi.erl @@ -212,7 +212,7 @@ deliver_webpage(#mod{config_db = Db} = ModData, Port) -> {ok, HTTPHeaders, Status} when is_binary(Body)-> IsDisableChunkedSend = httpd_response:is_disable_chunked_send(Db), - case (ModData#mod.http_version =/= "HTTP/1.1") or + case (ModData#mod.http_version =/= "HTTP/1.1") orelse (IsDisableChunkedSend) of true -> send_headers(ModData, Status, diff --git a/lib/inets/src/http_server/mod_esi.erl b/lib/inets/src/http_server/mod_esi.erl index 76f9420bbc71..e9774cd043f1 100644 --- a/lib/inets/src/http_server/mod_esi.erl +++ b/lib/inets/src/http_server/mod_esi.erl @@ -459,7 +459,7 @@ deliver_webpage_chunk(#mod{config_db = Db} = ModData, Pid, Timeout) -> StatusCode =:= 204 orelse %% No Content StatusCode =:= 304 orelse %% Not Modified (100 =< StatusCode andalso StatusCode =< 199), %% Informational - case (ModData#mod.http_version =/= "HTTP/1.1") or + case (ModData#mod.http_version =/= "HTTP/1.1") orelse (IsDisableChunkedSend) of true -> send_headers(ModData, StatusCode, diff --git a/lib/kernel/src/application.erl b/lib/kernel/src/application.erl index 350312c09d1b..5f80d18a1d6b 100644 --- a/lib/kernel/src/application.erl +++ b/lib/kernel/src/application.erl @@ -414,8 +414,8 @@ enqueue_or_start_app(Name, App, DAG, Pending, Started, Opts) -> %% we start it immediately. At the end of serial mode, the DAG %% is always empty. case enqueue_or_start(ChildApps, OptionalApps, DAG, [], Started, Opts) of - {ok, NewDAG, NewPending, NewStarted} - when NewPending =:= [], (Mode =:= serial) or (Mod =:= []) -> + {ok, NewDAG, []=_NewPending, NewStarted} + when (Mode =:= serial) orelse (Mod =:= []) -> case application_controller:start_application(App, Type) of ok -> {ok, NewDAG, Pending, [App | NewStarted]}; diff --git a/lib/kernel/src/disk_log_server.erl b/lib/kernel/src/disk_log_server.erl index cb5398ab678c..2d799e019278 100644 --- a/lib/kernel/src/disk_log_server.erl +++ b/lib/kernel/src/disk_log_server.erl @@ -89,7 +89,7 @@ handle_info({pending_reply, Pid, Result0}, State) -> NP = lists:keydelete(Pid, #pending.pid, State#state.pending), State1 = State#state{pending = NP}, if - Attach and (Result0 =:= {error, no_such_log}) -> + Attach andalso (Result0 =:= {error, no_such_log}) -> %% The disk_log process has terminated. Try again. open([{Request,From} | Clients], State1); true -> diff --git a/lib/kernel/src/file_io_server.erl b/lib/kernel/src/file_io_server.erl index aa07c09ef59b..8d3c75bcdab1 100644 --- a/lib/kernel/src/file_io_server.erl +++ b/lib/kernel/src/file_io_server.erl @@ -928,7 +928,7 @@ cbv({utf32,big}, <<0:8>>) -> cbv({utf32,big}, <<0:8,X:8>>) when X =< 16 -> 2; cbv({utf32,big}, <<0:8,X:8,Y:8>>) - when X =< 16, ((X > 0) or ((Y =< 215) or (Y >= 224))) -> + when X =< 16, ((X > 0) orelse ((Y =< 215) orelse (Y >= 224))) -> 1; cbv({utf32,big},_) -> false; @@ -939,7 +939,7 @@ cbv({utf32,little},<<_:8,_:8>>) -> cbv({utf32,little},<>) when X =:= 254; X =:= 255 -> false; cbv({utf32,little},<<_:8,Y:8,X:8>>) - when X =< 16, ((X > 0) or ((Y =< 215) or (Y >= 224))) -> + when X =< 16, ((X > 0) orelse ((Y =< 215) orelse (Y >= 224))) -> 1; cbv({utf32,little},_) -> false. diff --git a/lib/kernel/src/inet_dns.erl b/lib/kernel/src/inet_dns.erl index 05a8682de6d1..c8321d5346a1 100644 --- a/lib/kernel/src/inet_dns.erl +++ b/lib/kernel/src/inet_dns.erl @@ -193,7 +193,7 @@ do_decode(< T = encode_type(Type), - C = encode_class(Class, Mdns and CacheFlush), + C = encode_class(Class, Mdns andalso CacheFlush), {Bin,Comp1} = encode_name(Bin0, Comp0, byte_size(Bin0), DName), Pos = byte_size(Bin)+2+2+byte_size(TTL)+2, {DataBin,Comp} = encode_data(Comp1, Pos, Type, Class, Data, Opcode), diff --git a/lib/kernel/src/os.erl b/lib/kernel/src/os.erl index bba2b847365d..1a96f05da127 100644 --- a/lib/kernel/src/os.erl +++ b/lib/kernel/src/os.erl @@ -673,7 +673,7 @@ validate2([0|Rest]) -> validate2([C|Rest]) when is_integer(C), C > 0 -> validate2(Rest); validate2([List|Rest]) when is_list(List) -> - validate2(List) or validate2(Rest); + validate2(List) orelse validate2(Rest); validate2([]) -> false. diff --git a/lib/megaco/src/app/megaco.erl b/lib/megaco/src/app/megaco.erl index 18212139e40f..54843f741134 100644 --- a/lib/megaco/src/app/megaco.erl +++ b/lib/megaco/src/app/megaco.erl @@ -2201,7 +2201,7 @@ token_tag2string(Tag, pretty) -> token_tag2string(Tag, megaco_pretty_text_encoder); token_tag2string(Tag, compact) -> token_tag2string(Tag, megaco_compact_text_encoder); -token_tag2string(Tag, Mod) when is_atom(Tag) and is_atom(Mod) -> +token_tag2string(Tag, Mod) when is_atom(Tag) andalso is_atom(Mod) -> Mod:token_tag2string(Tag). -doc """ diff --git a/lib/megaco/src/engine/megaco_config.erl b/lib/megaco/src/engine/megaco_config.erl index c99c86fcb4ee..1ca8b4718742 100644 --- a/lib/megaco/src/engine/megaco_config.erl +++ b/lib/megaco/src/engine/megaco_config.erl @@ -1526,7 +1526,7 @@ verify_val(Item, Val) -> megaco_config_misc:verify_uint(Val); trans_timer -> - verify_timer(Val) and (Val >= 0); + verify_timer(Val) andalso (Val >= 0); trans_sender when Val =:= undefined -> true; pending_timer -> verify_timer(Val); @@ -1827,7 +1827,7 @@ update_trans_timer(#conn_data{trans_sender = Pid} = CD, 0) when is_pid(Pid) -> CD#conn_data{trans_timer = 0, trans_sender = undefined}; update_trans_timer(#conn_data{trans_sender = Pid} = CD, To) - when is_pid(Pid) and (To > 0) -> + when is_pid(Pid) andalso (To > 0) -> megaco_trans_sender:timeout(Pid, To), CD#conn_data{trans_timer = To}; @@ -1836,7 +1836,7 @@ update_trans_timer(CD, To) when To > 0 -> %% update trans_ack_maxcount update_trans_ack_maxcount(#conn_data{trans_sender = Pid} = CD, Max) - when is_pid(Pid) and (Max > 0) -> + when is_pid(Pid) andalso (Max > 0) -> megaco_trans_sender:ack_maxcount(Pid, Max), CD#conn_data{trans_ack_maxcount = Max}; @@ -1847,7 +1847,7 @@ update_trans_ack_maxcount(CD, Max) %% update trans_req_maxcount update_trans_req_maxcount(#conn_data{trans_sender = Pid} = CD, Max) - when is_pid(Pid) and (Max > 0) -> + when is_pid(Pid) andalso (Max > 0) -> megaco_trans_sender:req_maxcount(Pid, Max), CD#conn_data{trans_req_maxcount = Max}; @@ -1858,7 +1858,7 @@ update_trans_req_maxcount(CD, Max) %% update trans_req_maxsize update_trans_req_maxsize(#conn_data{trans_sender = Pid} = CD, Max) - when is_pid(Pid) and (Max > 0) -> + when is_pid(Pid) andalso (Max > 0) -> megaco_trans_sender:req_maxsize(Pid, Max), CD#conn_data{trans_req_maxsize = Max}; diff --git a/lib/megaco/src/engine/megaco_digit_map.erl b/lib/megaco/src/engine/megaco_digit_map.erl index b03cc99b6aa4..2e171e1e00e4 100644 --- a/lib/megaco/src/engine/megaco_digit_map.erl +++ b/lib/megaco/src/engine/megaco_digit_map.erl @@ -852,9 +852,9 @@ report(Pid, Event) when is_pid(Pid) -> $s -> sleep(1); % 1 sec (1000 ms) $L -> sleep(10); % 10 sec (10000 ms) $l -> sleep(10); % 10 sec (10000 ms) - {long, I} when (I >= $0) and (I =< $9) -> cast(Pid, {long, I}); - {long, A} when (A >= $a) and (A =< $k) -> cast(Pid, {long, A}); - {long, A} when (A >= $A) and (A =< $K) -> cast(Pid, {long, A}); + {long, I} when (I >= $0) andalso (I =< $9) -> cast(Pid, {long, I}); + {long, A} when (A >= $a) andalso (A =< $k) -> cast(Pid, {long, A}); + {long, A} when (A >= $A) andalso (A =< $K) -> cast(Pid, {long, A}); %% {long, I} when (I >= $0) and (I =< $9) -> long(Pid, I); %% {long, A} when (A >= $a) and (A =< $k) -> long(Pid, A); %% {long, A} when (A >= $A) and (A =< $K) -> long(Pid, A); diff --git a/lib/megaco/src/engine/megaco_erl_dist_encoder.erl b/lib/megaco/src/engine/megaco_erl_dist_encoder.erl index 69d8cf274f80..d1c4e196e5cc 100644 --- a/lib/megaco/src/engine/megaco_erl_dist_encoder.erl +++ b/lib/megaco/src/engine/megaco_erl_dist_encoder.erl @@ -66,7 +66,7 @@ encode_message([megaco_compressed|Config], Vsn, MegaMsg) when is_record(MegaMsg, 'MegacoMessage') -> {ok, erlang:term_to_binary(?MC_MOD:encode(MegaMsg, Vsn), Config)}; encode_message([{megaco_compressed, Mod}|Config], Vsn, MegaMsg) - when is_atom(Mod) and is_record(MegaMsg, 'MegacoMessage') -> + when is_atom(Mod) andalso is_record(MegaMsg, 'MegacoMessage') -> {ok, erlang:term_to_binary(Mod:encode(MegaMsg, Vsn), Config)}; encode_message(Config, _Vsn, MegaMsg) when is_record(MegaMsg, 'MegacoMessage') -> diff --git a/lib/megaco/src/engine/megaco_messenger.erl b/lib/megaco/src/engine/megaco_messenger.erl index 27f95787129f..76178e4cd861 100644 --- a/lib/megaco/src/engine/megaco_messenger.erl +++ b/lib/megaco/src/engine/megaco_messenger.erl @@ -3145,7 +3145,7 @@ handle_disconnect_callback(ConnData, UserReason) %% test_request(ConnHandle, Actions, Version, EncodingMod, EncodingConfig) - when is_record(ConnHandle, megaco_conn_handle) and + when is_record(ConnHandle, megaco_conn_handle) andalso is_integer(Version) andalso is_atom(EncodingMod) -> %% Create a fake conn_data structure ConnData = #conn_data{serial = 1, @@ -4119,8 +4119,8 @@ format_encode_error_reason(Reason) -> case Reason of {Mod, Func, [EC, Msg], {AE, CS}} when is_atom(Mod) andalso is_atom(Func) andalso - is_list(EC) and - is_tuple(Msg) and + is_list(EC) andalso + is_tuple(Msg) andalso is_list(CS) -> io_lib:format("~n Encode module: ~w" "~n Func: ~w" diff --git a/lib/megaco/src/engine/megaco_messenger_misc.erl b/lib/megaco/src/engine/megaco_messenger_misc.erl index d976d6139c38..14316cd243d2 100644 --- a/lib/megaco/src/engine/megaco_messenger_misc.erl +++ b/lib/megaco/src/engine/megaco_messenger_misc.erl @@ -89,15 +89,15 @@ encode_trans_request(CD, TR) when is_record(TR, 'TransactionRequest') -> encode_trans_reply(#conn_data{segment_send = SegSend, max_pdu_size = Max, protocol_version = V} = CD, Reply) - when (SegSend == infinity) or (is_integer(SegSend) and (SegSend > 0)) and - is_integer(V) and (V >= 3) and - is_integer(Max) and (Max >= ?MSG_HDR_SZ) -> + when (SegSend == infinity) orelse (is_integer(SegSend) andalso (SegSend > 0)) andalso + is_integer(V) andalso (V >= 3) andalso + is_integer(Max) andalso (Max >= ?MSG_HDR_SZ) -> (catch encode_segmented_trans_reply(CD, Reply)); encode_trans_reply(CD, TR) when is_record(TR, megaco_transaction_reply) -> ?report_debug(CD, "encode trans reply", [TR]), Trans = {transactionReply, transform_transaction_reply(CD, TR)}, encode_transaction(CD, Trans); -encode_trans_reply(CD, TR) when is_tuple(TR) and +encode_trans_reply(CD, TR) when is_tuple(TR) andalso (element(1, TR) == 'TransactionReply') -> ?report_debug(CD, "encode trans reply", [TR]), Trans = {transactionReply, TR}, @@ -353,7 +353,7 @@ do_send_message(ConnData, SendFunc, Bin, Extra) -> %%%----------------------------------------------------------------- transform_transaction_reply(#conn_data{protocol_version = V}, TR) - when is_integer(V) and (V >= 3) -> + when is_integer(V) andalso (V >= 3) -> #megaco_transaction_reply{transactionId = TransId, immAckRequired = IAR, transactionResult = TransRes, diff --git a/lib/megaco/src/engine/megaco_sdp.erl b/lib/megaco/src/engine/megaco_sdp.erl index ada6d0ad5be8..8d24c84c4adf 100644 --- a/lib/megaco/src/engine/megaco_sdp.erl +++ b/lib/megaco/src/engine/megaco_sdp.erl @@ -547,7 +547,7 @@ encode_PropertyParm(SDP) -> -doc false. get_sdp_record_from_PropertyGroup(Type, PG) - when is_atom(Type) and is_list(PG) -> + when is_atom(Type) andalso is_list(PG) -> F = fun(R) -> not is_pg_record(Type, R) end, lists:filter(F, PG). @@ -883,7 +883,7 @@ encode_conn_data_conn_addr(ip4, CA) when is_record(CA, megaco_sdp_c_conn_addr) -> encode_conn_data_conn_addr(CA); encode_conn_data_conn_addr(AT, CA) - when is_list(AT) and is_record(CA, megaco_sdp_c_conn_addr) -> + when is_list(AT) andalso is_record(CA, megaco_sdp_c_conn_addr) -> case tolower(AT) of "ip4" -> encode_conn_data_conn_addr(CA); @@ -1085,7 +1085,7 @@ encode_rtimes_list_of_offsets(BadLoo) -> %% ===== Time Zones ===== %% -decode_pp_tzones(Value) when is_list(Value) and (length(Value) > 0) -> +decode_pp_tzones(Value) when is_list(Value) andalso (length(Value) > 0) -> ?d("decode_pp_ztimes -> entry with" "~n Value: ~p", [Value]), LOA = decode_tzones_list_of_adjustments(string:tokens(Value, " \t"), []), @@ -1182,7 +1182,7 @@ encode_pp_encryption_keys(uri = _Method, EncryptionKey) #'PropertyParm'{name = "k", value = ["uri:" ++ EncryptionKey]}; encode_pp_encryption_keys(Method, EncryptionKey) - when is_list(Method) and is_list(EncryptionKey) -> + when is_list(Method) andalso is_list(EncryptionKey) -> ?d("encode_pp_encryption_keys -> entry with" "~n Method: ~p" "~n EncryptionKey: ~p", [Method, EncryptionKey]), @@ -1199,7 +1199,7 @@ decode_pp_attribute(Value) -> "~n Value: ~p", [Value]), First = string:chr(Value, $:), if - (First > 0) and (First < length(Value)) -> + (First > 0) andalso (First < length(Value)) -> ?d("decode_pp_attribute -> value attribute", []), Attr = string:substr(Value, 1, First -1), AttrValue = string:substr(Value, First + 1), @@ -1326,7 +1326,7 @@ decode_pp_attribute_value("fmtp", AttrValue) -> FMTP = AttrValue, First = string:chr(FMTP, $ ), if - (First > 0) and (First < length(FMTP)) -> + (First > 0) andalso (First < length(FMTP)) -> ?d("decode_pp_attribute_value -> valid fmtp with params", []), Format = string:substr(FMTP, 1, First - 1), Params = string:substr(FMTP, First + 1), @@ -1547,7 +1547,7 @@ encode_pp_attribute(Attr, undefined) when is_list(Attr) -> "~n Attr: ~p", [Attr]), #'PropertyParm'{name = "a", value = [Attr]}; -encode_pp_attribute(Attr, Value) when is_list(Attr) and is_list(Value) -> +encode_pp_attribute(Attr, Value) when is_list(Attr) andalso is_list(Value) -> ?d("encode_pp_attribute_rtpmap -> entry with" "~n Attr: ~p" "~n Value: ~p", [Attr, Value]), diff --git a/lib/megaco/src/engine/megaco_timer.erl b/lib/megaco/src/engine/megaco_timer.erl index 093f323ebb5d..fdcd88713fad 100644 --- a/lib/megaco/src/engine/megaco_timer.erl +++ b/lib/megaco/src/engine/megaco_timer.erl @@ -46,7 +46,7 @@ %% init(SingleWaitFor) when SingleWaitFor =:= infinity -> {SingleWaitFor, timeout}; -init(SingleWaitFor) when is_integer(SingleWaitFor) and (SingleWaitFor >= 0) -> +init(SingleWaitFor) when is_integer(SingleWaitFor) andalso (SingleWaitFor >= 0) -> {SingleWaitFor, timeout}; init(Timer) when is_record(Timer, megaco_incr_timer) -> return_incr(Timer). @@ -78,9 +78,9 @@ verify(#megaco_incr_timer{wait_for = WaitFor, factor = Factor, incr = Incr, max_retries = MaxRetries}) -> - (megaco_config_misc:verify_strict_uint(WaitFor) and - megaco_config_misc:verify_strict_uint(Factor) and - megaco_config_misc:verify_strict_int(Incr) and + (megaco_config_misc:verify_strict_uint(WaitFor) andalso + megaco_config_misc:verify_strict_uint(Factor) andalso + megaco_config_misc:verify_strict_int(Incr) andalso verify_max_retries(MaxRetries)); verify(Timer) -> megaco_config_misc:verify_uint(Timer). @@ -104,7 +104,7 @@ return_incr(#megaco_incr_timer{wait_for = WaitFor, return_incr(#megaco_incr_timer{wait_for = WaitFor, max_retries = Int} = Timer) - when is_integer(Int) and (Int > 0) -> + when is_integer(Int) andalso (Int > 0) -> {WaitFor, Timer}; return_incr(#megaco_incr_timer{wait_for = WaitFor, diff --git a/lib/megaco/src/flex/megaco_flex_scanner.erl b/lib/megaco/src/flex/megaco_flex_scanner.erl index ffb1d0551f6e..07e1e21d39e9 100644 --- a/lib/megaco/src/flex/megaco_flex_scanner.erl +++ b/lib/megaco/src/flex/megaco_flex_scanner.erl @@ -299,7 +299,7 @@ version([_|T]) -> version(T). -guess_version([C]) when (48 =< C) and (C =< 57) -> +guess_version([C]) when (48 =< C) andalso (C =< 57) -> C-48; guess_version(Str) when is_list(Str) -> case (catch list_to_integer(Str)) of diff --git a/lib/megaco/src/text/megaco_text_gen_v2.hrl b/lib/megaco/src/text/megaco_text_gen_v2.hrl index 23afa85800b6..daa9d84613f9 100644 --- a/lib/megaco/src/text/megaco_text_gen_v2.hrl +++ b/lib/megaco/src/text/megaco_text_gen_v2.hrl @@ -2090,7 +2090,7 @@ enc_EventBufferDescriptor([], _State) -> ?EventBufferToken ]; enc_EventBufferDescriptor(EventSpecs, State) - when is_list(EventSpecs) and (length(EventSpecs) >= 1) -> + when is_list(EventSpecs) andalso (length(EventSpecs) >= 1) -> [ ?EventBufferToken, ?LBRKT_INDENT(State), diff --git a/lib/megaco/src/text/megaco_text_gen_v3.hrl b/lib/megaco/src/text/megaco_text_gen_v3.hrl index 35500b521e12..5bd4899796b8 100644 --- a/lib/megaco/src/text/megaco_text_gen_v3.hrl +++ b/lib/megaco/src/text/megaco_text_gen_v3.hrl @@ -124,7 +124,7 @@ enc_Message(Val, State) enc_Message_messageBody(Val#'Message'.messageBody, State) ]. -enc_version(Val, State) when is_integer(Val) and (Val >= 0) -> +enc_version(Val, State) when is_integer(Val) andalso (Val >= 0) -> enc_DIGIT(Val, State, 0, 99). enc_Message_messageBody({'Message_messageBody',Val}, State) -> @@ -143,7 +143,7 @@ enc_Message_messageBody_transactions({'Message_messageBody_transactions',Val}, State) -> enc_Message_messageBody_transactions(Val, State); enc_Message_messageBody_transactions(Val, State) - when is_list(Val) and (Val /= []) -> + when is_list(Val) andalso (Val /= []) -> [enc_Transaction(T, State) || T <- Val]. enc_MId({'MId',Val}, State) -> @@ -674,7 +674,7 @@ do_enc_ActionReply(asn1_NOVALUE, CtxRep, [], State) enc_ContextRequest(CtxRep, ?INC_INDENT(State)) ]; do_enc_ActionReply(asn1_NOVALUE, CtxRep, CmdRep, State) - when (CtxRep =/= asn1_NOVALUE) and (CmdRep =/= []) -> + when (CtxRep =/= asn1_NOVALUE) andalso (CmdRep =/= []) -> [ enc_ContextRequest(CtxRep, ?INC_INDENT(State)), ?COMMA_INDENT(?INC_INDENT(State)), @@ -688,7 +688,7 @@ do_enc_ActionReply(asn1_NOVALUE, asn1_NOVALUE, CmdRep, State) ?INC_INDENT(State)) ]; do_enc_ActionReply(ED, CtxRep, [], State) - when (ED =/= asn1_NOVALUE) and (CtxRep =/= asn1_NOVALUE) -> + when (ED =/= asn1_NOVALUE) andalso (CtxRep =/= asn1_NOVALUE) -> [ enc_ContextRequest(CtxRep, ?INC_INDENT(State)), ?COMMA_INDENT(?INC_INDENT(State)), @@ -696,15 +696,15 @@ do_enc_ActionReply(ED, CtxRep, [], State) ?INC_INDENT(State)) ]; do_enc_ActionReply(ED, asn1_NOVALUE, CmdRep, State) - when (ED =/= asn1_NOVALUE) and (CmdRep =/= []) -> + when (ED =/= asn1_NOVALUE) andalso (CmdRep =/= []) -> [ enc_list([{CmdRep, fun enc_CommandReply/2}, {[ED], fun enc_ErrorDescriptor/2}], % Indention cosmetics ?INC_INDENT(State)) ]; do_enc_ActionReply(ED, CtxRep, CmdRep, State) - when (ED =/= asn1_NOVALUE) and - (CtxRep =/= asn1_NOVALUE) and + when (ED =/= asn1_NOVALUE) andalso + (CtxRep =/= asn1_NOVALUE) andalso (CmdRep =/= []) -> [ enc_ContextRequest(CtxRep, ?INC_INDENT(State)), @@ -1091,7 +1091,7 @@ enc_TopologyRequest1( topologyDirection = TD, streamID = SID, % OPTIONAL topologyDirectionExtension = TDE}, % OPTIONAL - State) when (SID =/= asn1_NOVALUE) and (TDE =/= asn1_NOVALUE) -> + State) when (SID =/= asn1_NOVALUE) andalso (TDE =/= asn1_NOVALUE) -> [ enc_TerminationID(From, State), ?COMMA_INDENT(State), @@ -2055,7 +2055,7 @@ enc_termIDList({'TerminationIDList',Val}, State) -> enc_termIDList([Singleton], State) -> enc_TerminationID(Singleton, State); enc_termIDList(TidList, State) - when is_list(TidList) and (length(TidList) > 1) -> + when is_list(TidList) andalso (length(TidList) > 1) -> %% d("enc_termIDList -> entry with" %% "~n TidList: ~p", [TidList]), State2 = ?INC_INDENT(State), @@ -2293,7 +2293,7 @@ enc_LocalRemoteDescriptor(Val, State) enc_PropertyGroup({'PropertyGroup',Val}, RequiresV, State) -> enc_PropertyGroup(Val, RequiresV, State); enc_PropertyGroup([H | _T] = List, mand_v, State) - when is_record(H, 'PropertyParm') and (H#'PropertyParm'.name == "v") -> + when is_record(H, 'PropertyParm') andalso (H#'PropertyParm'.name == "v") -> enc_PropertyGroup(List, opt_v, State); enc_PropertyGroup(PG, opt_v, State) -> [ @@ -2435,7 +2435,7 @@ enc_EventsDescriptor(#'EventsDescriptor'{requestID = asn1_NOVALUE, ]; enc_EventsDescriptor(#'EventsDescriptor'{requestID = RID, eventList = Evs}, State) - when (RID =/= asn1_NOVALUE) and (Evs =/= []) -> + when (RID =/= asn1_NOVALUE) andalso (Evs =/= []) -> [ ?EventsToken, ?EQUAL, @@ -2501,7 +2501,7 @@ decompose_requestedActions(#'RequestedActions'{keepActive = KA, signalsDescriptor = SD, notifyBehaviour = NB, resetEventsDescriptor = RED}) - when (KA =/= true) and ((SD =/= asn1_NOVALUE) and (SD =/= [])) -> + when (KA =/= true) andalso ((SD =/= asn1_NOVALUE) andalso (SD =/= [])) -> [ {[EDM], fun enc_EventDM/2}, {[{SE, SD}], fun enc_embedWithSig/2}, @@ -2516,7 +2516,7 @@ decompose_requestedActions(#'RequestedActions'{keepActive = KA, signalsDescriptor = SD, notifyBehaviour = NB, resetEventsDescriptor = RED}) - when (SD == asn1_NOVALUE) or (SD == []) -> + when (SD == asn1_NOVALUE) orelse (SD == []) -> [ {[KA], fun enc_keepActive/2}, {[EDM], fun enc_EventDM/2}, @@ -2597,7 +2597,7 @@ enc_EventDM({Tag, Val}, State) -> enc_embedFirst(RID, Evs, State) - when (RID =/= asn1_NOVALUE) and (is_list(Evs) and (Evs =/= [])) -> + when (RID =/= asn1_NOVALUE) andalso (is_list(Evs) andalso (Evs =/= [])) -> %% d("enc_embedFirst -> entry with" %% "~n RID: ~p" %% "~n Evs: ~p", [RID, Evs]), @@ -2700,7 +2700,7 @@ decompose_secondRequestedActions( signalsDescriptor = SD, notifyBehaviour = NB, resetEventsDescriptor = RED}) - when (KA =/= true) and ((SD =/= asn1_NOVALUE) and (SD =/= [])) -> + when (KA =/= true) andalso ((SD =/= asn1_NOVALUE) andalso (SD =/= [])) -> [ {[EDM], fun enc_EventDM/2}, {[SD], fun enc_embedSig/2}, @@ -2713,7 +2713,7 @@ decompose_secondRequestedActions( signalsDescriptor = SD, notifyBehaviour = NB, resetEventsDescriptor = RED}) - when (SD == asn1_NOVALUE) or (SD == []) -> + when (SD == asn1_NOVALUE) orelse (SD == []) -> [ {[KA], fun enc_keepActive/2}, {[EDM], fun enc_EventDM/2}, @@ -3172,7 +3172,7 @@ enc_serviceChangeMgcId(Val, State) -> enc_MId(Val, State) ]. -enc_portNumber(Val, State) when is_integer(Val) and (Val >= 0) -> +enc_portNumber(Val, State) when is_integer(Val) andalso (Val >= 0) -> enc_UINT16(Val, State). enc_ServiceChangeResParm(Val, State) @@ -3320,7 +3320,7 @@ enc_HEXDIG(Octets, State, Min, Max) when is_list(Octets) -> do_enc_HEXDIG(Octets, State, Min, Max, 0, []). do_enc_HEXDIG([Octet | Rest], State, Min, Max, Count, Acc) - when (Octet >= 0) and (Octet =< 255) -> + when (Octet >= 0) andalso (Octet =< 255) -> Hex = hex(Octet), % OTP-4921 if Octet =< 15 -> @@ -3331,7 +3331,7 @@ do_enc_HEXDIG([Octet | Rest], State, Min, Max, Count, Acc) do_enc_HEXDIG(Rest, State, Min, Max, Count + 2, Acc2) end; do_enc_HEXDIG([], State, Min, Max, Count, Acc) - when is_integer(Min) and (Count < Min) -> + when is_integer(Min) andalso (Count < Min) -> do_enc_HEXDIG([0], State, Min, Max, Count, Acc); do_enc_HEXDIG([], _State, Min, Max, Count, Acc) -> %% OTP-4710 verify_count(Count, Min, Max), @@ -3382,7 +3382,7 @@ do_enc_list([], _State, _ElemEncoder, _SepEncoder, _NeedsSep) -> do_enc_list([asn1_NOVALUE | T], State, ElemEncoder, SepEncoder, NeedsSep) -> do_enc_list(T, State, ElemEncoder, SepEncoder, NeedsSep); do_enc_list([H | T], State, ElemEncoder, SepEncoder, NeedsSep) - when is_function(ElemEncoder) and is_function(SepEncoder) -> + when is_function(ElemEncoder) andalso is_function(SepEncoder) -> case ElemEncoder(H, State) of [] -> do_enc_list(T, State, ElemEncoder, SepEncoder, NeedsSep); diff --git a/lib/megaco/src/text/megaco_text_scanner.erl b/lib/megaco/src/text/megaco_text_scanner.erl index 83af2afe735f..5202a6140d8a 100644 --- a/lib/megaco/src/text/megaco_text_scanner.erl +++ b/lib/megaco/src/text/megaco_text_scanner.erl @@ -132,7 +132,7 @@ tokens3(Chars, Line, Acc, Version) -> end. -guess_version([C]) when (48 =< C) and (C =< 57) -> +guess_version([C]) when (48 =< C) andalso (C =< 57) -> {ok, C-48}; guess_version(Str) when is_list(Str) -> case (catch list_to_integer(Str)) of diff --git a/lib/mnesia/src/mnesia_controller.erl b/lib/mnesia/src/mnesia_controller.erl index d7ae12520662..8766be5d8f33 100644 --- a/lib/mnesia/src/mnesia_controller.erl +++ b/lib/mnesia/src/mnesia_controller.erl @@ -728,7 +728,7 @@ handle_call(disc_load_intents,From,State = #state{loader_queue=LQ,late_loader_qu handle_call({update_where_to_write, [add, Tab, AddNode], _From}, _Dummy, State) -> Current = val({current, db_nodes}), Res = - case lists:member(AddNode, Current) and + case lists:member(AddNode, Current) andalso (State#state.schema_is_merged == true) of true -> mnesia_lib:add_lsort({Tab, where_to_write}, AddNode), diff --git a/lib/mnesia/src/mnesia_dumper.erl b/lib/mnesia/src/mnesia_dumper.erl index 2d56bbd6fc4c..83a90ef08392 100644 --- a/lib/mnesia/src/mnesia_dumper.erl +++ b/lib/mnesia/src/mnesia_dumper.erl @@ -728,7 +728,7 @@ insert_op(Tid, _, {op, restore_recreate, TabDef}, InPlace, InitBy) -> %% And create new ones.. if - (InitBy == startup) or (Semantics == unknown) -> + (InitBy == startup) orelse (Semantics == unknown) -> ignore; Semantics == ram_copies -> EtsProps = proplists:get_value(ets, StorageProps, []), diff --git a/lib/mnesia/src/mnesia_loader.erl b/lib/mnesia/src/mnesia_loader.erl index b578ddac2309..cd3f677f8471 100644 --- a/lib/mnesia/src/mnesia_loader.erl +++ b/lib/mnesia/src/mnesia_loader.erl @@ -432,7 +432,7 @@ create_table(Tab, TabSize, Storage, Cs) -> mnesia_lib:unlock_table(Tab), {error, {mktab, Reason}} end; - (Storage == ram_copies) or (Storage == disc_copies) -> + (Storage == ram_copies) orelse (Storage == disc_copies) -> EtsOpts = proplists:get_value(ets, StorageProps, []), Args = [{keypos, 2}, public, named_table, Cs#cstruct.type | EtsOpts], case mnesia_monitor:unsafe_mktab(Tab, Args) of diff --git a/lib/mnesia/src/mnesia_monitor.erl b/lib/mnesia/src/mnesia_monitor.erl index c4b48518f0ba..dd0be4cda15f 100644 --- a/lib/mnesia/src/mnesia_monitor.erl +++ b/lib/mnesia/src/mnesia_monitor.erl @@ -314,8 +314,8 @@ use_dir() -> %% Returns true if the Mnesia directory contains %% important files non_empty_dir() -> - mnesia_lib:exists(mnesia_bup:fallback_bup()) or - mnesia_lib:exists(mnesia_lib:tab2dmp(schema)) or + mnesia_lib:exists(mnesia_bup:fallback_bup()) orelse + mnesia_lib:exists(mnesia_lib:tab2dmp(schema)) orelse mnesia_lib:exists(mnesia_lib:tab2dat(schema)). %%---------------------------------------------------------------------- diff --git a/lib/mnesia/src/mnesia_recover.erl b/lib/mnesia/src/mnesia_recover.erl index 06bd5211627a..ec6c722bda45 100644 --- a/lib/mnesia/src/mnesia_recover.erl +++ b/lib/mnesia/src/mnesia_recover.erl @@ -493,7 +493,7 @@ load_decision_tab(Cont, InitBy) -> %% From now on all decisions are logged in the transaction log file convert_old() -> HasOldStuff = - mnesia_lib:exists(mnesia_log:previous_decision_log_file()) or + mnesia_lib:exists(mnesia_log:previous_decision_log_file()) orelse mnesia_lib:exists(mnesia_log:decision_log_file()), case HasOldStuff of true -> @@ -1162,7 +1162,7 @@ add_remote_decision(Node, NewD, State) -> Outcome == unclear -> ignore; true -> - case lists:member(node(), NewD#decision.disc_nodes) or + case lists:member(node(), NewD#decision.disc_nodes) orelse lists:member(node(), NewD#decision.ram_nodes) of true -> tell_im_certain([Node], D); @@ -1224,8 +1224,8 @@ send_decisions([]) -> ok. arrange([To | ToNodes], D, Acc, ForceSend) when is_record(D, decision) -> - NeedsAdd = (ForceSend or - lists:member(To, D#decision.disc_nodes) or + NeedsAdd = (ForceSend orelse + lists:member(To, D#decision.disc_nodes) orelse lists:member(To, D#decision.ram_nodes)), case NeedsAdd of true -> diff --git a/lib/mnesia/src/mnesia_schema.erl b/lib/mnesia/src/mnesia_schema.erl index 13ee81991a2c..bf7553bd076a 100644 --- a/lib/mnesia/src/mnesia_schema.erl +++ b/lib/mnesia/src/mnesia_schema.erl @@ -3478,7 +3478,7 @@ do_make_merge_schema(Node, NeedsConv, RemoteCs = #cstruct{name = schema}) -> Masters = mnesia_recover:get_master_nodes(schema), HasRemoteMaster = lists:member(Node, Masters), HasLocalMaster = lists:member(node(), Masters), - Force = HasLocalMaster or HasRemoteMaster, + Force = HasLocalMaster orelse HasRemoteMaster, %% What is the storage types opinions? StCsLocal = mnesia_lib:cs_to_storage_type(node(), Cs), StRcsLocal = mnesia_lib:cs_to_storage_type(node(), RemoteCs), @@ -3558,7 +3558,7 @@ do_make_merge_schema(Node, NeedsConv, RemoteCs = #cstruct{}) -> Masters = mnesia_recover:get_master_nodes(schema), HasRemoteMaster = lists:member(Node, Masters), HasLocalMaster = lists:member(node(), Masters), - Force = HasLocalMaster or HasRemoteMaster, + Force = HasLocalMaster orelse HasRemoteMaster, case ?catch_val({Tab, cstruct}) of {'EXIT', _} -> %% A completely new table, created while Node was down @@ -3757,7 +3757,7 @@ verify_merge(RemoteCs) -> announce_im_running([N | Ns], SchemaCs) -> {L1, L2} = mnesia_recover:connect_nodes([N]), - case lists:member(N, L1) or lists:member(N, L2) of + case lists:member(N, L1) orelse lists:member(N, L2) of true -> mnesia_lib:add({current, db_nodes}, N), mnesia_controller:add_active_replica(schema, N, SchemaCs); diff --git a/lib/mnesia/src/mnesia_tm.erl b/lib/mnesia/src/mnesia_tm.erl index 8e5e517bceb8..dcdbbd6fc28e 100644 --- a/lib/mnesia/src/mnesia_tm.erl +++ b/lib/mnesia/src/mnesia_tm.erl @@ -2345,7 +2345,7 @@ send_to_pids([], _Msg) -> ok. reconfigure_participants(N, [P | Tail]) -> - case lists:member(N, P#participant.disc_nodes) or + case lists:member(N, P#participant.disc_nodes) orelse lists:member(N, P#participant.ram_nodes) of false -> %% Ignore, since we are not a participant diff --git a/lib/parsetools/src/leex.erl b/lib/parsetools/src/leex.erl index 27b401f4a01c..1f75966ede10 100644 --- a/lib/parsetools/src/leex.erl +++ b/lib/parsetools/src/leex.erl @@ -2130,10 +2130,10 @@ prep_out_actions(As) -> ({A,Code,TokenChars,TokenLen,TokenLine,TokenCol,TokenLoc}) -> Vs = [{TokenChars,"TokenChars"}, {TokenLen,"TokenLen"}, - {TokenLine or TokenLoc,"TokenLine"}, - {TokenCol or TokenLoc,"TokenCol"}, + {TokenLine orelse TokenLoc,"TokenLine"}, + {TokenCol orelse TokenLoc,"TokenCol"}, {TokenChars,"YYtcs"}, - {TokenLen or TokenChars,"TokenLen"}], + {TokenLen orelse TokenChars,"TokenLen"}], Vars = [if F -> S; true -> "_" end || {F,S} <- Vs], Name = list_to_atom(lists:concat([yyaction_,A])), [Chars,Len,Line,Col,_,_] = Vars, diff --git a/lib/parsetools/src/yecc.erl b/lib/parsetools/src/yecc.erl index 2c08a5954a75..1943cb082a30 100644 --- a/lib/parsetools/src/yecc.erl +++ b/lib/parsetools/src/yecc.erl @@ -1485,7 +1485,7 @@ check_expected(St0) -> end, NStates = NStates0 + 1, if - (not Done) or (ExpStates =:= []) or (NStates =:= ExpStates) -> + (not Done) orelse (ExpStates =:= []) orelse (NStates =:= ExpStates) -> St1; true -> add_warning(none, {n_states, ExpStates, NStates}, St1) diff --git a/lib/public_key/src/pubkey_cert.erl b/lib/public_key/src/pubkey_cert.erl index 75b658f3fad1..ec2616d8a81d 100644 --- a/lib/public_key/src/pubkey_cert.erl +++ b/lib/public_key/src/pubkey_cert.erl @@ -183,7 +183,7 @@ parse_and_check_validity_dates(OtpCert) -> % Expiration check if - ((NotBefore =< Now) and (Now =< NotAfter)) -> ok; + ((NotBefore =< Now) andalso (Now =< NotAfter)) -> ok; true -> expired end diff --git a/lib/public_key/src/pubkey_crl.erl b/lib/public_key/src/pubkey_crl.erl index 10186292aae7..f76ad3a03432 100644 --- a/lib/public_key/src/pubkey_crl.erl +++ b/lib/public_key/src/pubkey_crl.erl @@ -135,7 +135,7 @@ verify_crl(OtpCert, DP, CRL, DerCRL, DeltaCRL, DerDeltaCRL, OtherDPCRLs, DeltaRevoked = delta_revoked(DeltaCRL), - ValidExt = verify_extensions(Extensions) and + ValidExt = verify_extensions(Extensions) andalso verify_extensions(Revoked), IntMask = compute_interim_reasons_mask(DP, IDP), @@ -316,7 +316,7 @@ verify_issuer_and_scope(#'OTPCertificate'{tbsCertificate = TBSCert} = Cert, when DPIssuer =/= asn1_NOVALUE -> CRLIssuer = pubkey_cert_records:transform(TBSCRL#'TBSCertList'.issuer, decode), Issuer = dp_crlissuer_to_issuer(DPIssuer), - case pubkey_cert:is_issuer(Issuer, CRLIssuer) and is_indirect_crl(IDP) of + case pubkey_cert:is_issuer(Issuer, CRLIssuer) andalso is_indirect_crl(IDP) of true -> verify_scope(Cert, DP, IDP), issuer_id(Cert, CRL); @@ -598,7 +598,7 @@ check_revoked(#'DistributionPoint'{cRLIssuer = DPIssuer} = DP, IDP, DefaultIssue Extensions}| Rest], State) -> Reason = revoked_reason(Extensions), - case (DPIssuer =/= asn1_NOVALUE) and is_indirect_crl(IDP) of + case (DPIssuer =/= asn1_NOVALUE) andalso is_indirect_crl(IDP) of true -> handle_indirect_crl_check(DP, IDP, DefaultIssuer0, Names, SerialNr, Extensions, Reason, Rest, State); false -> @@ -679,7 +679,7 @@ status(Reason) -> {revoked, Reason}. verify_extensions([#'TBSCertList_revokedCertificates_SEQOF'{crlEntryExtensions = Ext} | Rest]) -> - verify_extensions(pubkey_cert:extensions_list(Ext)) and verify_extensions(Rest); + verify_extensions(pubkey_cert:extensions_list(Ext)) andalso verify_extensions(Rest); verify_extensions([]) -> true; verify_extensions(asn1_NOVALUE) -> diff --git a/lib/public_key/src/pubkey_pbe.erl b/lib/public_key/src/pubkey_pbe.erl index a2821c938cf1..2186699f72e0 100644 --- a/lib/public_key/src/pubkey_pbe.erl +++ b/lib/public_key/src/pubkey_pbe.erl @@ -275,13 +275,13 @@ pseudo_output_length(?'id-hmacWithSHA512') -> derived_key_length(_, Len) when is_integer(Len) -> Len; -derived_key_length(Cipher,_) when (Cipher == ?'desCBC') or +derived_key_length(Cipher,_) when (Cipher == ?'desCBC') orelse (Cipher == "DES-CBC") -> 8; -derived_key_length(Cipher,_) when (Cipher == ?'rc2CBC') or +derived_key_length(Cipher,_) when (Cipher == ?'rc2CBC') orelse (Cipher == "RC2-CBC") -> 16; -derived_key_length(Cipher,_) when (Cipher == ?'des-EDE3-CBC') or +derived_key_length(Cipher,_) when (Cipher == ?'des-EDE3-CBC') orelse (Cipher == "DES-EDE3-CBC") -> 24; diff --git a/lib/public_key/src/public_key.erl b/lib/public_key/src/public_key.erl index 243e5548d3b3..07fe20f698d1 100644 --- a/lib/public_key/src/public_key.erl +++ b/lib/public_key/src/public_key.erl @@ -462,7 +462,7 @@ pem_entry_decode({Asn1Type, CryptDer, {Cipher, Salt}} = PemEntry, is_binary(CryptDer) andalso is_list(Cipher) andalso is_binary(Salt) andalso - ((erlang:byte_size(Salt) == 8) or (erlang:byte_size(Salt) == 16)) andalso + ((erlang:byte_size(Salt) == 8) orelse (erlang:byte_size(Salt) == 16)) andalso is_list(Password) -> do_pem_entry_decode(PemEntry, Password). @@ -538,7 +538,7 @@ pem_entry_encode(Asn1Type, Entity, {{Cipher, Salt} = CipherInfo, is_list(Password) andalso is_list(Cipher) andalso is_binary(Salt) andalso - ((erlang:byte_size(Salt) == 8) or + ((erlang:byte_size(Salt) == 8) orelse (erlang:byte_size(Salt) == 16)) -> do_pem_entry_encode(Asn1Type, Entity, CipherInfo, Password). @@ -1487,7 +1487,7 @@ pkix_is_fixed_dh_cert(Cert) when is_binary(Cert) -> Reason :: term() . %%-------------------------------------------------------------------- -pkix_issuer_id(#'OTPCertificate'{} = OtpCert, Signed) when (Signed == self) or +pkix_issuer_id(#'OTPCertificate'{} = OtpCert, Signed) when (Signed == self) orelse (Signed == other) -> pubkey_cert:issuer_id(OtpCert, Signed); pkix_issuer_id(Cert, Signed) when is_binary(Cert) -> diff --git a/lib/snmp/src/agent/snmpa_conf.erl b/lib/snmp/src/agent/snmpa_conf.erl index 0b1a63d35d62..75f084bd79e7 100644 --- a/lib/snmp/src/agent/snmpa_conf.erl +++ b/lib/snmp/src/agent/snmpa_conf.erl @@ -439,7 +439,7 @@ info. Conf :: [agent_entry()]. write_agent_config(Dir, Hdr, Conf) - when is_list(Dir) and is_list(Hdr) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Hdr) andalso is_list(Conf) -> Order = fun snmp_framework_mib:order_agent/2, Check = fun snmp_framework_mib:check_agent/2, Write = fun (Fd, Entries) -> write_agent_conf(Fd, Hdr, Entries) end, @@ -459,7 +459,7 @@ info. Conf :: [agent_entry()]. append_agent_config(Dir, Conf) - when is_list(Dir) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Conf) -> Order = fun snmp_framework_mib:order_agent/2, Check = fun snmp_framework_mib:check_agent/2, Write = fun write_agent_conf/2, @@ -569,7 +569,7 @@ See [Contexts](snmp_agent_config_files.md#context) for more info. Conf :: [context_entry()]. write_context_config(Dir, Hdr, Conf) - when is_list(Dir) and is_list(Hdr) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Hdr) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_context/2, Write = fun (Fd, Entries) -> write_context_conf(Fd, Hdr, Entries) end, @@ -588,7 +588,7 @@ See [Contexts](snmp_agent_config_files.md#context) for more info. Conf :: [context_entry()]. append_context_config(Dir, Conf) - when is_list(Dir) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_context/2, Write = fun write_context_conf/2, @@ -727,7 +727,7 @@ See [Community](snmp_agent_config_files.md#community) for more info. Conf :: [community_entry()]. write_community_config(Dir, Hdr, Conf) - when is_list(Dir) and is_list(Hdr) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Hdr) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_community/2, Write = fun (Fd, Entries) -> write_community_conf(Fd, Hdr, Entries) end, @@ -746,7 +746,7 @@ See [Community](snmp_agent_config_files.md#community) for more info. Conf :: [community_entry()]. append_community_config(Dir, Conf) - when is_list(Dir) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_community/2, Write = fun write_community_conf/2, @@ -883,7 +883,7 @@ info. Conf :: [standard_entry()]. write_standard_config(Dir, Hdr, Conf) - when is_list(Dir) and is_list(Hdr) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Hdr) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_standard/2, Write = fun (Fd, Entries) -> write_standard_conf(Fd, Hdr, Entries) end, @@ -903,7 +903,7 @@ info. Conf :: [standard_entry()]. append_standard_config(Dir, Conf) - when is_list(Dir) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_standard/2, Write = fun write_standard_conf/2, @@ -1239,7 +1239,7 @@ more info. Conf :: [target_addr_entry()]. write_target_addr_config(Dir, Hdr, Conf) - when is_list(Dir) and is_list(Hdr) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Hdr) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_target_addr/2, Write = fun (Fd, Entries) -> write_target_addr_conf(Fd, Hdr, Entries) end, @@ -1259,7 +1259,7 @@ more info. Conf :: [target_addr_entry()]. append_target_addr_config(Dir, Conf) - when is_list(Dir) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_target_addr/2, Write = fun write_target_addr_conf/2, @@ -1471,7 +1471,7 @@ for more info. Conf :: [target_params_entry()]. write_target_params_config(Dir, Hdr, Conf) - when is_list(Dir) and is_list(Hdr) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Hdr) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_target_params/2, Write = fun (Fd, Entries) -> write_target_params_conf(Fd, Hdr, Entries) end, @@ -1491,7 +1491,7 @@ for more info. Conf :: [target_params_entry()]. append_target_params_config(Dir, Conf) - when is_list(Dir) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_target_params/2, Write = fun write_target_params_conf/2, @@ -1597,7 +1597,7 @@ See [Notify Definitions](snmp_agent_config_files.md#notify) for more info. Conf :: [notify_entry()]. write_notify_config(Dir, Hdr, Conf) - when is_list(Dir) and is_list(Hdr) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Hdr) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_notify/2, Write = fun (Fd, Entries) -> write_notify_conf(Fd, Hdr, Entries) end, @@ -1616,7 +1616,7 @@ See [Notify Definitions](snmp_agent_config_files.md#notify) for more info. Conf :: [notify_entry()]. append_notify_config(Dir, Conf) - when is_list(Dir) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_notify/2, Write = fun write_notify_conf/2, @@ -1776,7 +1776,7 @@ See [Security data for USM](snmp_agent_config_files.md#usm) for more info. Conf :: [usm_entry()]. write_usm_config(Dir, Hdr, Conf) - when is_list(Dir) and is_list(Hdr) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Hdr) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_usm/2, Write = fun (Fd, Entries) -> write_usm_conf(Fd, Hdr, Entries) end, @@ -1795,7 +1795,7 @@ See [Security data for USM](snmp_agent_config_files.md#usm) for more info. Conf :: [usm_entry()]. append_usm_config(Dir, Conf) - when is_list(Dir) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_usm/2, Write = fun write_usm_conf/2, @@ -1983,7 +1983,7 @@ See [MIB Views for VACM](snmp_agent_config_files.md#vacm) for more info. Conf :: [vacm_entry()]. write_vacm_config(Dir, Hdr, Conf) - when is_list(Dir) and is_list(Hdr) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Hdr) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_vacm/2, Write = fun (Fd, Entries) -> write_vacm_conf(Fd, Hdr, Entries) end, @@ -2002,7 +2002,7 @@ See [MIB Views for VACM](snmp_agent_config_files.md#vacm) for more info. Conf :: [vacm_entry()]. append_vacm_config(Dir, Conf) - when is_list(Dir) and is_list(Conf) -> + when is_list(Dir) andalso is_list(Conf) -> Order = fun snmp_conf:no_order/2, Check = fun check_vacm/2, Write = fun write_vacm_conf/2, diff --git a/lib/snmp/src/agent/snmpa_get.erl b/lib/snmp/src/agent/snmpa_get.erl index 2fb867201a9e..1fcb261fc9d3 100644 --- a/lib/snmp/src/agent/snmpa_get.erl +++ b/lib/snmp/src/agent/snmpa_get.erl @@ -1094,7 +1094,7 @@ do_get_bulk(MibView, NonRepeaters, MaxRepetitions, {error, Idx, Reason} -> ?LIB:user_err("failed encoding varbind ~w:~n~p", [Idx, Reason]), {genErr, Idx, []}; - {SizeLeft, Res} when is_integer(SizeLeft) and is_list(Res) -> + {SizeLeft, Res} when is_integer(SizeLeft) andalso is_list(Res) -> ?vtrace("do_get_bulk -> encoded: " "~n SizeLeft: ~p" "~n Res: ~w", [SizeLeft, Res]), diff --git a/lib/snmp/src/agent/snmpa_supervisor.erl b/lib/snmp/src/agent/snmpa_supervisor.erl index a921d2342d0d..109a727d0247 100644 --- a/lib/snmp/src/agent/snmpa_supervisor.erl +++ b/lib/snmp/src/agent/snmpa_supervisor.erl @@ -632,7 +632,7 @@ erase(Key) -> get_mibs(Mibs, Vsns) -> MibDir = filename:join(code:priv_dir(snmp), "mibs"), StdMib = - case (lists:member(v2, Vsns) or lists:member(v3, Vsns)) of + case (lists:member(v2, Vsns) orelse lists:member(v3, Vsns)) of true -> filename:join([MibDir, "SNMPv2-MIB"]); false -> filename:join([MibDir, "STANDARD-MIB"]) end, @@ -703,7 +703,7 @@ conf1(Dir, Vsns, Func) -> snmp_notification_mib:Func(Dir), ?vdebug("~w snmp_view_based_acm_mib",[Func]), snmp_view_based_acm_mib:Func(Dir), - case lists:member(v1, Vsns) or lists:member(v2, Vsns) of + case lists:member(v1, Vsns) orelse lists:member(v2, Vsns) of true -> ?vdebug("we need to handle v1 and/or v2 =>~n" " ~w snmp_community_mib",[Func]), diff --git a/lib/snmp/src/misc/snmp_config.erl b/lib/snmp/src/misc/snmp_config.erl index d55e13844359..3d0ce619d76e 100644 --- a/lib/snmp/src/misc/snmp_config.erl +++ b/lib/snmp/src/misc/snmp_config.erl @@ -582,7 +582,7 @@ config_agent_snmp(Dir, Vsns) -> "minimum", fun verify_sec_type/1), Passwd = - case lists:member(v3, Vsns) and (SecType /= none) of + case lists:member(v3, Vsns) andalso (SecType /= none) of true -> ensure_crypto_started(), ask("8b. Give a password of at least length 8. It is used to " @@ -636,7 +636,7 @@ config_agent_snmp(Dir, Vsns) -> "read/write~n" " access to the \"internet\" subtree."), i(" 3. Standard traps are sent to the manager."), - case lists:member(v1, Vsns) or lists:member(v2, Vsns) of + case lists:member(v1, Vsns) orelse lists:member(v2, Vsns) of true -> i(" 4. Community \"public\" is mapped to security name" " \"initial\"."), @@ -1012,7 +1012,7 @@ default_dir(Component, DefDir) -> IsManagerDir = is_members(ManagerConfs, Files), Warning = if - IsAgentDir and IsManagerDir -> + IsAgentDir andalso IsManagerDir -> "Note that the default directory contains both agent and manager config files"; IsAgentDir -> "Note that the default directory contains agent config files"; diff --git a/lib/snmp/src/misc/snmp_log.erl b/lib/snmp/src/misc/snmp_log.erl index 535876fef4f6..4499b62ad962 100644 --- a/lib/snmp/src/misc/snmp_log.erl +++ b/lib/snmp/src/misc/snmp_log.erl @@ -955,7 +955,7 @@ dat2str({{Y,M,D},{H,Min,S}}) -> timestamp_filter({Local,Universal},Start,Stop) -> - tsf_ge(Local,Universal,Start) and tsf_le(Local,Universal,Stop); + tsf_ge(Local,Universal,Start) andalso tsf_le(Local,Universal,Stop); timestamp_filter(_,_Start,_Stop) -> true. diff --git a/lib/ssh/src/ssh_connection.erl b/lib/ssh/src/ssh_connection.erl index cef81e56a57d..159ca767c4ff 100644 --- a/lib/ssh/src/ssh_connection.erl +++ b/lib/ssh/src/ssh_connection.erl @@ -1869,7 +1869,7 @@ request_reply_or_data(#channel{local_id = ChannelId, user = ChannelPid}, {[{channel_request_reply, From, Reply}], Connection#connection{requests = lists:keydelete(ChannelId, 1, Requests)}}; - false when (Reply == success) or (Reply == failure) -> + false when (Reply == success) orelse (Reply == failure) -> {[], Connection}; false -> {[{channel_data, ChannelPid, Reply}], Connection} diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl index 8746c2bbd4e8..8a9823376e32 100644 --- a/lib/ssh/src/ssh_connection_handler.erl +++ b/lib/ssh/src/ssh_connection_handler.erl @@ -761,7 +761,7 @@ handle_event(internal, {conn_msg,Msg}, StateName, #data{connection_state = Conne {Repls, D} = send_replies(RepliesConn, D0), case {Reason0,Role} of {{_, Reason}, client} when ((StateName =/= {connected,client}) - and (not Rengotation)) -> + andalso (not Rengotation)) -> handshake({not_connected,Reason}, D); _ -> ok diff --git a/lib/ssh/src/ssh_lib.erl b/lib/ssh/src/ssh_lib.erl index 762bc3eb56a0..292f627d00f7 100644 --- a/lib/ssh/src/ssh_lib.erl +++ b/lib/ssh/src/ssh_lib.erl @@ -74,16 +74,16 @@ comp(X1, X2) -> %%% yes - very far from best implementation comp(<>, <>, Truth) -> - comp(R1, R2, Truth and (B1 == B2)); + comp(R1, R2, Truth andalso (B1 == B2)); comp(<<_,R1/binary>>, <<>>, Truth) -> - comp(R1, <<>>, Truth and false); + comp(R1, <<>>, Truth andalso false); comp(<<>>, <<>>, Truth) -> Truth; comp([H1|T1], [H2|T2], Truth) -> - comp(T1, T2, Truth and (H1 == H2)); + comp(T1, T2, Truth andalso (H1 == H2)); comp([_|T1], [], Truth) -> - comp(T1, [], Truth and false); + comp(T1, [], Truth andalso false); comp([], [], Truth) -> Truth; diff --git a/lib/ssl/src/ssl_cipher.erl b/lib/ssl/src/ssl_cipher.erl index c8ceaba4fc6d..88aacf048700 100644 --- a/lib/ssl/src/ssl_cipher.erl +++ b/lib/ssl/src/ssl_cipher.erl @@ -830,8 +830,8 @@ hash_algorithm(?SHA224) -> sha224; hash_algorithm(?SHA256) -> sha256; hash_algorithm(?SHA384) -> sha384; hash_algorithm(?SHA512) -> sha512; -hash_algorithm(Other) when is_integer(Other) andalso ((Other >= 7) and (Other =< 223)) -> unassigned; -hash_algorithm(Other) when is_integer(Other) andalso ((Other >= 224) and (Other =< 255)) -> Other. +hash_algorithm(Other) when is_integer(Other) andalso ((Other >= 7) andalso (Other =< 223)) -> unassigned; +hash_algorithm(Other) when is_integer(Other) andalso ((Other >= 224) andalso (Other =< 255)) -> Other. sign_algorithm(anon) -> ?ANON; sign_algorithm(rsa) -> ?RSA; @@ -841,8 +841,8 @@ sign_algorithm(?ANON) -> anon; sign_algorithm(?RSA) -> rsa; sign_algorithm(?DSA) -> dsa; sign_algorithm(?ECDSA) -> ecdsa; -sign_algorithm(Other) when is_integer(Other) andalso ((Other >= 4) and (Other =< 223)) -> unassigned; -sign_algorithm(Other) when is_integer(Other) andalso ((Other >= 224) and (Other =< 255)) -> Other. +sign_algorithm(Other) when is_integer(Other) andalso ((Other >= 4) andalso (Other =< 223)) -> unassigned; +sign_algorithm(Other) when is_integer(Other) andalso ((Other >= 224) andalso (Other =< 255)) -> Other. signature_algorithm_to_scheme(#'SignatureAlgorithm'{algorithm = ?'id-RSASSA-PSS', diff --git a/lib/ssl/src/ssl_gen_statem.erl b/lib/ssl/src/ssl_gen_statem.erl index b46c7640654a..03d63e4ceafb 100644 --- a/lib/ssl/src/ssl_gen_statem.erl +++ b/lib/ssl/src/ssl_gen_statem.erl @@ -1723,8 +1723,8 @@ deliver_app_data(UserSocket, #socket_options{active=Active, packet=Type} = SOpts SO = case Data of {P, _, _, _} - when ((P =:= http_request) or (P =:= http_response)), - ((Type =:= http) or (Type =:= http_bin)) -> + when ((P =:= http_request) orelse (P =:= http_response)), + ((Type =:= http) orelse (Type =:= http_bin)) -> SOpts#socket_options{packet={Type, headers}}; http_eoh when tuple_size(Type) =:= 2 -> %% End of headers - expect another Request/Response line diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl index 1b7033be2d44..0324005f9974 100644 --- a/lib/ssl/src/ssl_handshake.erl +++ b/lib/ssl/src/ssl_handshake.erl @@ -2101,7 +2101,7 @@ validation_fun_and_state(undefined, VerifyState, CertPath, LogLevel) -> Extension, SslState, LogLevel); - (OtpCert, _DerCert, VerifyResult, SslState) when (VerifyResult == valid) or + (OtpCert, _DerCert, VerifyResult, SslState) when (VerifyResult == valid) orelse (VerifyResult == valid_peer) -> case cert_status_check(OtpCert, SslState, VerifyResult, CertPath, LogLevel) of valid -> @@ -2121,7 +2121,7 @@ path_validation_options(Opts, ValidationFunAndState) -> {verify_fun, ValidationFunAndState} | PolicyOpts]. apply_user_fun(Fun, OtpCert, DerCert, VerifyResult0, UserState0, SslState, CertPath, LogLevel) when - (VerifyResult0 == valid) or (VerifyResult0 == valid_peer) -> + (VerifyResult0 == valid) orelse (VerifyResult0 == valid_peer) -> VerifyResult = maybe_check_hostname(OtpCert, VerifyResult0, SslState, LogLevel), case apply_fun(Fun, OtpCert, DerCert, VerifyResult, UserState0) of {Valid, UserState} when (Valid == valid) orelse (Valid == valid_peer) -> diff --git a/lib/stdlib/examples/erl_id_trans.erl b/lib/stdlib/examples/erl_id_trans.erl index c336af17ca32..b2f551eb679d 100644 --- a/lib/stdlib/examples/erl_id_trans.erl +++ b/lib/stdlib/examples/erl_id_trans.erl @@ -380,9 +380,9 @@ gexpr({call,Anno,{atom,Aa,F},As0}) -> end; % Guard bif's can be remote, but only in the module erlang... gexpr({call,Anno,{remote,Aa,{atom,Ab,erlang},{atom,Ac,F}},As0}) -> - case erl_internal:guard_bif(F, length(As0)) or - erl_internal:arith_op(F, length(As0)) or - erl_internal:comp_op(F, length(As0)) or + case erl_internal:guard_bif(F, length(As0)) orelse + erl_internal:arith_op(F, length(As0)) orelse + erl_internal:comp_op(F, length(As0)) orelse erl_internal:bool_op(F, length(As0)) of true -> As1 = gexpr_list(As0), {call,Anno,{remote,Aa,{atom,Ab,erlang},{atom,Ac,F}},As1} @@ -391,7 +391,7 @@ gexpr({bin,Anno,Fs}) -> Fs2 = pattern_grp(Fs), {bin,Anno,Fs2}; gexpr({op,Anno,Op,A0}) -> - case erl_internal:arith_op(Op, 1) or + case erl_internal:arith_op(Op, 1) orelse erl_internal:bool_op(Op, 1) of true -> A1 = gexpr(A0), {op,Anno,Op,A1} @@ -402,8 +402,8 @@ gexpr({op,Anno,Op,L0,R0}) when Op =:= 'andalso'; Op =:= 'orelse' -> R1 = gexpr(R0), %They see the same variables {op,Anno,Op,L1,R1}; gexpr({op,Anno,Op,L0,R0}) -> - case erl_internal:arith_op(Op, 2) or - erl_internal:bool_op(Op, 2) or + case erl_internal:arith_op(Op, 2) orelse + erl_internal:bool_op(Op, 2) orelse erl_internal:comp_op(Op, 2) of true -> L1 = gexpr(L0), diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl index 7f2e382a83ae..fa023502d302 100644 --- a/lib/stdlib/src/dets.erl +++ b/lib/stdlib/src/dets.erl @@ -3225,8 +3225,8 @@ fopen_existing_file(Tab, OpenArgs) -> Auto, access = Acc, debug = Debug} = OpenArgs, {ok, Fd, FH} = read_file_header(Fname, Acc, Ram), - MinF = (MinSlots =:= default) or (MinSlots =:= FH#fileheader.min_no_slots), - MaxF = (MaxSlots =:= default) or (MaxSlots =:= FH#fileheader.max_no_slots), + MinF = (MinSlots =:= default) orelse (MinSlots =:= FH#fileheader.min_no_slots), + MaxF = (MaxSlots =:= default) orelse (MaxSlots =:= FH#fileheader.max_no_slots), Wh = case dets_v9:check_file_header(FH, Fd) of {ok, Head} when Rep =:= force, Acc =:= read_write, FH#fileheader.no_colls =/= undefined, diff --git a/lib/stdlib/src/dets_v9.erl b/lib/stdlib/src/dets_v9.erl index 1e8098534759..7b6e3a4c2def 100644 --- a/lib/stdlib/src/dets_v9.erl +++ b/lib/stdlib/src/dets_v9.erl @@ -1094,7 +1094,7 @@ fast_output2(Head, SizeT, Bases, SegAddr, SS, SegEnd) -> end. fast_output_end(Head, SizeT) -> - case ets:foldl(fun({_Sz,_Pos,Cnt,NoC}, Acc) -> (Cnt =:= NoC) and Acc end, + case ets:foldl(fun({_Sz,_Pos,Cnt,NoC}, Acc) -> (Cnt =:= NoC) andalso Acc end, true, SizeT) of true -> {ok, Head}; false -> {error, invalid_objects_list} @@ -1949,10 +1949,10 @@ hash_invars(H) -> -define(M8(X), (((X) band (?SEGSZP - 1)) =:= 0)). hash_invars(N, M, Next, Min, Max) -> - ?M8(N) and ?M8(M) and ?M8(Next) and ?M8(Min) and ?M8(Max) - and (0 =< N) and (N =< M) and (N =< 2*Next) and (M =< Next) - and (Next =< 2*M) and (0 =< Min) and (Min =< Next) and (Next =< Max) - and (Min =< M). + ?M8(N) andalso ?M8(M) andalso ?M8(Next) andalso ?M8(Min) andalso ?M8(Max) + andalso (0 =< N) andalso (N =< M) andalso (N =< 2*Next) andalso (M =< Next) + andalso (Next =< 2*M) andalso (0 =< Min) andalso (Min =< Next) andalso (Next =< Max) + andalso (Min =< M). seg_zero() -> <<0:(4*?SEGSZ)/unit:8>>. @@ -2152,8 +2152,8 @@ updated(Head, Pos, OldSize, BSize, SlotPos, Bins, Ch, DeltaNoOs, DeltaNoKs) -> %% (and collections) as were present %% when chunking started (the table %% must have been fixed). - (Overwrite0 =/= false) and - (DeltaNoOs =:= 0) and (DeltaNoKs =:= 0); + (Overwrite0 =/= false) andalso + (DeltaNoOs =:= 0) andalso (DeltaNoKs =:= 0); true -> Overwrite0 end, diff --git a/lib/stdlib/src/erl_error.erl b/lib/stdlib/src/erl_error.erl index c5ae309ce12d..ad0d272874b9 100644 --- a/lib/stdlib/src/erl_error.erl +++ b/lib/stdlib/src/erl_error.erl @@ -564,7 +564,7 @@ format_call(ErrStr, Pre1, ForMForFun, As, PF, Enc, CL) -> S2 = pp_arguments(PF, As, string:length([Pre1|MFs]), Enc, CL), S3 = pp_arguments(PF, [a2345,b2345], I1, Enc, CL), Long = count_nl(S3) > 0, - case Long or (count_nl(S2) < count_nl(S1)) of + case Long orelse (count_nl(S2) < count_nl(S1)) of true -> [$\n, Pre1, MFs, S2]; false -> diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl index 9e362190ef08..35042ce072d9 100644 --- a/lib/stdlib/src/erl_eval.erl +++ b/lib/stdlib/src/erl_eval.erl @@ -727,7 +727,7 @@ find_maxline(LC) -> true -> L = erl_anno:line(A), case - is_integer(L) and (L > get('$erl_eval_max_line')) + is_integer(L) andalso (L > get('$erl_eval_max_line')) of true -> put('$erl_eval_max_line', L); false -> ok diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index aeb235b8751a..7e273f9c9279 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -1834,12 +1834,12 @@ import(Anno, {Mod,Fs}, St00) -> AutoImpSup = is_autoimport_suppressed(St0#lint.no_auto,{F,A}), OldBif = erl_internal:old_bif(F,A), {Err,if - Warn and (not AutoImpSup) and OldBif -> + Warn andalso (not AutoImpSup) andalso OldBif -> add_error (Anno, {redefine_old_bif_import, {F,A}}, St0); - Warn and (not AutoImpSup) -> + Warn andalso (not AutoImpSup) -> add_warning (Anno, {redefine_bif_import, {F,A}}, @@ -2313,7 +2313,7 @@ bit_type(Anno, Size0, Type, St) -> bit_size_check(_Anno, unknown, _, St) -> {unknown,St}; bit_size_check(_Anno, undefined, #bittype{type=Type}, St) -> - true = (Type =:= utf8) or (Type =:= utf16) or (Type =:= utf32), %Assertion. + true = (Type =:= utf8) orelse (Type =:= utf16) orelse (Type =:= utf32), %Assertion. {undefined,St}; bit_size_check(Anno, all, #bittype{type=Type}, St) -> case Type of @@ -2617,7 +2617,7 @@ is_gexpr({record,A,Name,Inits}, Info0) -> is_gexpr_fields(Inits, A, Name, Info); is_gexpr({bin,_A,Fs}, Info) -> all(fun ({bin_element,_Anno,E,Sz,_Ts}) -> - is_gexpr(E, Info) and (Sz =:= default orelse is_gexpr(Sz, Info)) + is_gexpr(E, Info) andalso (Sz =:= default orelse is_gexpr(Sz, Info)) end, Fs); is_gexpr({call,_A,{atom,_Af,F},As}, {_,IsOverridden}=Info) -> A = length(As), diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl index 34eb7cc36f20..1f326a9ac858 100644 --- a/lib/stdlib/src/erl_pp.erl +++ b/lib/stdlib/src/erl_pp.erl @@ -1424,7 +1424,7 @@ write_a_string([], _N, _Len, _PP) -> write_a_string(S, N, Len, PP) -> SS = string:slice(S, 0, N), Sl = write_string(SS, PP), - case (string:length(Sl) > Len) and (N > ?MIN_SUBSTRING) of + case (string:length(Sl) > Len) andalso (N > ?MIN_SUBSTRING) of true -> write_a_string(S, N-1, Len, PP); false -> diff --git a/lib/stdlib/src/erl_stdlib_errors.erl b/lib/stdlib/src/erl_stdlib_errors.erl index d841a020d830..dbb26927768f 100644 --- a/lib/stdlib/src/erl_stdlib_errors.erl +++ b/lib/stdlib/src/erl_stdlib_errors.erl @@ -547,7 +547,7 @@ check_io_format([Fmt, Args], Cause) -> case is_io_format(Fmt) of false -> [invalid_format, must_be_list(Args)] ++ - case (is_pid(Fmt) or is_atom(Fmt)) and is_io_format(Args) of + case (is_pid(Fmt) orelse is_atom(Fmt)) andalso is_io_format(Args) of true -> %% The user seems to have called io:format(Dev,"string"). [{general,missing_argument_list}]; diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl index e05d1176f750..8ac9d73fffc4 100644 --- a/lib/stdlib/src/erl_tar.erl +++ b/lib/stdlib/src/erl_tar.erl @@ -718,7 +718,7 @@ The options in `OptionList` modify the defaults as follows: -spec create(file:filename_all(), filelist(), [create_opt()]) -> ok | {error, term()} | {error, {string(), term()}}. create(Name, FileList, Options) when is_list(Name); is_binary(Name) -> - Mode = lists:filter(fun(X) -> (X=:=compressed) or (X=:=cooked) + Mode = lists:filter(fun(X) -> (X=:=compressed) orelse (X=:=cooked) end, Options), case open(Name, [write|Mode]) of {ok, TarFile} -> diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl index 9efd96f56d5f..3fc47f6c950c 100644 --- a/lib/stdlib/src/escript.erl +++ b/lib/stdlib/src/escript.erl @@ -1032,7 +1032,7 @@ format_exception(Class, Reason, StackTrace) -> PF = fun(Term, I) -> io_lib:format("~." ++ integer_to_list(I) ++ P, [Term, 50]) end, - StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end, + StackFun = fun(M, _F, _A) -> (M =:= erl_eval) orelse (M =:= ?MODULE) end, erl_error:format_exception(1, Class, Reason, StackTrace, StackFun, PF, Enc). encoding() -> diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl index 90e63dc6f12b..48096157911c 100644 --- a/lib/stdlib/src/filename.erl +++ b/lib/stdlib/src/filename.erl @@ -781,7 +781,7 @@ Returns the path type, which is one of the following: Path :: file:name_all(). pathtype(Atom) when is_atom(Atom) -> pathtype(atom_to_list(Atom)); -pathtype(Name) when is_list(Name) or is_binary(Name) -> +pathtype(Name) when is_list(Name) orelse is_binary(Name) -> case os:type() of {win32, _} -> win32_pathtype(Name); diff --git a/lib/stdlib/src/io_lib_fread.erl b/lib/stdlib/src/io_lib_fread.erl index b67bb2a67b8a..ba1a48f8ae3f 100644 --- a/lib/stdlib/src/io_lib_fread.erl +++ b/lib/stdlib/src/io_lib_fread.erl @@ -204,7 +204,7 @@ fread1([$#|Format], none, Sup, false, Line0, N0, Res) -> begin {Line1,N1,B1} = fread_base(Line0, N0), B = abs(B1), - true = (B >= 2) and (B =< 1+$Z-$A+10), + true = (B >= 2) andalso (B =< 1+$Z-$A+10), {Line2,N2,Cs2} = fread_digits(Line1, N1, B, []), fread_based(reverse(Cs2), B1, Sup, Format, Line2, N2, Res) end of @@ -218,7 +218,7 @@ fread1([$#|Format], F, Sup, false, Line0, N, Res) -> begin {Line1,Cs1} = fread_chars(Line0, F, false), {Line2,_,B2} = fread_base(reverse(Cs1), N), - true = ((B2 >= 2) and (B2 =< 1+$Z-$A+10)), + true = ((B2 >= 2) andalso (B2 =< 1+$Z-$A+10)), fread_based(Line2, B2, Sup, Format, Line1, N+F, Res) end of {'EXIT',_} -> diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl index ced5ab1cb13b..2ee265cec0b2 100644 --- a/lib/stdlib/src/io_lib_pretty.erl +++ b/lib/stdlib/src/io_lib_pretty.erl @@ -291,7 +291,7 @@ pp_field({{field, Name, NameL, F},_,_, _}, Col0, Ll, M, TInd, Ind0, LD, W0) -> rec_indent(RInd, TInd, Col0, Ind0, W0) -> %% this uses TInd - Nl = (TInd > 0) and (RInd > TInd), + Nl = (TInd > 0) andalso (RInd > TInd), DCol = case Nl of true -> TInd; false -> RInd @@ -639,7 +639,7 @@ print_length_tuple(Tuple, 1, _T, RF, Enc, Str, Ord) -> {"{...}", 5, 3, More}; print_length_tuple(Tuple, D, T, RF, Enc, Str, Ord) -> L = print_length_tuple1(Tuple, 1, D, tsub(T, 2), RF, Enc, Str, Ord), - IsTagged = is_atom(element(1, Tuple)) and (tuple_size(Tuple) > 1), + IsTagged = is_atom(element(1, Tuple)) andalso (tuple_size(Tuple) > 1), {Len, Dots} = list_length(L, 2, 0), {{tuple,IsTagged,L}, Len, Dots, no_more}. @@ -1077,7 +1077,7 @@ cind_field({{field, _Name, NameL, F},_Len,_,_}, Col0, Ll, M, Ind, LD, W0) -> Ll. cind_rec(RInd, Col0, Ll, M, Ind, W0) -> - Nl = (Ind > 0) and (RInd > Ind), + Nl = (Ind > 0) andalso (RInd > Ind), DCol = case Nl of true -> Ind; false -> RInd diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl index 5eb834e0581e..b99240367f59 100644 --- a/lib/stdlib/src/ms_transform.erl +++ b/lib/stdlib/src/ms_transform.erl @@ -1023,7 +1023,7 @@ pseudo_guard_function(get_tcw,0) -> true; pseudo_guard_function(_,_) -> false. guard_function(X,A) -> - real_guard_function(X,A) or pseudo_guard_function(X,A). + real_guard_function(X,A) orelse pseudo_guard_function(X,A). action_function(set_seq_token,2) -> true; action_function(get_seq_token,0) -> true; @@ -1112,17 +1112,17 @@ cmp_operator(_,_) -> false. is_operator(X,A,_) -> - bool_operator(X,A) or arith_operator(X,A) or cmp_operator(X,A). + bool_operator(X,A) orelse arith_operator(X,A) orelse cmp_operator(X,A). is_imported_from_erlang(X,A,_) -> - real_guard_function(X,A) or bool_test(X,A) or bool_operator(X,A) or - arith_operator(X,A) or cmp_operator(X,A). + real_guard_function(X,A) orelse bool_test(X,A) orelse bool_operator(X,A) orelse + arith_operator(X,A) orelse cmp_operator(X,A). is_ms_function(X,A,body) -> - action_function(X,A) or guard_function(X,A) or bool_test(X,A); + action_function(X,A) orelse guard_function(X,A) orelse bool_test(X,A); is_ms_function(X,A,guard) -> - guard_function(X,A) or bool_test(X,A). + guard_function(X,A) orelse bool_test(X,A). fixup_environment(L,B) when is_list(L) -> lists:map(fun(X) -> diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index 1a5dbd2169c2..b10fd13052a0 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.erl @@ -1437,7 +1437,7 @@ format_rep(_, _, _Extra, _Limit) -> format_exception(Class, Reason, StackTrace, Extra, Limit) -> #{encoding:=Enc,depth:=Depth, single_line:=Single} = Extra, - StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end, + StackFun = fun(M, _F, _A) -> (M =:= erl_eval) orelse (M =:= ?MODULE) end, if Single -> {P,Tl} = p(Enc,Depth), Opts = chars_limit_opt(Limit), diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl index ec6c8d27f169..3d7ec14fa90b 100644 --- a/lib/stdlib/src/qlc.erl +++ b/lib/stdlib/src/qlc.erl @@ -2233,7 +2233,7 @@ prep_le(#qlc_lc{lc = LC_fun, opt = #qlc_opt{} = Opt0}=H, GOpt) -> #qlc_opt{unique = GUnique, cache = GCache, tmpdir = TmpDir, max_list = MaxList, tmpdir_usage = TmpUsage} = GOpt, - Unique = Opt0#qlc_opt.unique or GUnique, + Unique = Opt0#qlc_opt.unique orelse GUnique, Cache = if not GCache -> Opt0#qlc_opt.cache; true -> GCache @@ -2248,7 +2248,7 @@ prep_le(#qlc_table{info_fun = IF}=T, GOpt) -> Prep = #prepared{qh = T, sort_info = SortInfo, sorted = Sorted, is_unique_objects = IsUnique}, Opt = if - IsUnique or not GOpt#qlc_opt.unique, + IsUnique orelse not GOpt#qlc_opt.unique, T#qlc_table.ms =:= no_match_spec -> GOpt#qlc_opt{cache = false}; true -> @@ -2418,8 +2418,8 @@ may_create_simple(#qlc_opt{unique = Unique, cache = Cache} = Opt, #prepared{is_cached = IsCached, is_unique_objects = IsUnique} = Prep) -> if - Unique and not IsUnique; - (Cache =/= false) and not IsCached -> + Unique andalso not IsUnique; + (Cache =/= false) andalso not IsCached -> prep_simple_qlc(?SIMPLE_QVAR, anno(1), Prep, Opt); true -> Prep @@ -2436,14 +2436,14 @@ prep_simple_qlc(PVar, Anno, LE, Opt) -> not IsCached -> Cache; true -> false end, - Optz = #optz{unique = Unique and not IsUnique, + Optz = #optz{unique = Unique andalso not IsUnique, cache = Cachez, opt = Opt}, QLC = #simple_qlc{p = PVar, le = LE, anno = Anno, init_value = not_a_list, optz = Optz}, %% LE#prepared.join is not copied - #prepared{qh = QLC, is_unique_objects = IsUnique or Unique, + #prepared{qh = QLC, is_unique_objects = IsUnique orelse Unique, sort_info = SortInfo, sorted = Sorted, - is_cached = IsCached or (Cachez =/= false)}. + is_cached = IsCached orelse (Cachez =/= false)}. prep_sort(#qlc_sort{h = #prepared{sorted = yes}=Prep}, _GOpt) -> Prep; @@ -2455,7 +2455,7 @@ prep_sort(#qlc_sort{h = #prepared{is_unique_objects = IsUniqueObjs}}=Q, {SortInfo, Sorted} = sort_sort_info(S), #prepared{qh = S, is_cached = true, sort_info = SortInfo, sorted = Sorted, - is_unique_objects = S#qlc_sort.unique or IsUniqueObjs}. + is_unique_objects = S#qlc_sort.unique orelse IsUniqueObjs}. prep_qlc(QFun, CodeF, Qdata0, QOpt, Opt) -> #qlc_opt{unique = Unique, cache = Cache, join = Join} = Opt, @@ -2798,7 +2798,7 @@ opt_le(#prepared{qh = #simple_qlc{le = LE0, optz = Optz0}=QLC}=Prep0, Cache2 -> Cache2 end, Optz = Optz0#optz{cache = Cachez, - unique = Optz0#optz.unique or Optz2#optz.unique}, + unique = Optz0#optz.unique orelse Optz2#optz.unique}, PVar = if LE_Pvar =:= ?SIMPLE_QVAR -> QLC#simple_qlc.p; true -> LE_Pvar diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl index eae3655c4510..db0185cd11dc 100644 --- a/lib/stdlib/src/qlc_pt.erl +++ b/lib/stdlib/src/qlc_pt.erl @@ -849,7 +849,7 @@ opt_info(TemplateInfo, Sizes, JoinInfo, MSQs, Anno, opt_column_constants(ColumnConstants0) -> [CC || {{IdNo,_Col},Const,_FilNs}=CC <- ColumnConstants0, - (IdNo =/= ?TNO) or (length(Const) =:= 1)]. + (IdNo =/= ?TNO) orelse (length(Const) =:= 1)]. opt_constants(Anno, ColumnConstants) -> Ns = lists:usort([IdNo || {{IdNo,_Col},_Const,_FilNs} <- ColumnConstants]), diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index 85bce919bc2a..bb3898a42b21 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -830,7 +830,7 @@ report_exception(Class, Severity, {Reason,Stacktrace}, RT) -> Tag = severity_tag(Severity), I = iolist_size(Tag) + 1, PF = fun(Term, I1) -> pp(Term, I1, RT) end, - SF = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end, + SF = fun(M, _F, _A) -> (M =:= erl_eval) orelse (M =:= ?MODULE) end, Enc = encoding(), Str = erl_error:format_exception(I, Class, Reason, Stacktrace, SF, PF, Enc), io:requests([{put_chars, latin1, Tag}, diff --git a/lib/stdlib/src/shell_docs.erl b/lib/stdlib/src/shell_docs.erl index 3fd2c1f96af6..f4c6c1bf338e 100644 --- a/lib/stdlib/src/shell_docs.erl +++ b/lib/stdlib/src/shell_docs.erl @@ -218,7 +218,7 @@ validate_docs({Tag,Attr,Content},Path) -> ok end, %% Test that there are no block tags within a pre, h* - case lists:member(pre,Path) or + case lists:member(pre,Path) orelse lists:any(fun(H) -> lists:member(H,Path) end, [h1,h2,h3,h4,h5,h6]) of true when ?IS_BLOCK(Tag) -> throw({cannot_put_block_tag_within_pre,Tag,Path}); diff --git a/lib/stdlib/src/sofs.erl b/lib/stdlib/src/sofs.erl index 0141c6d08c3e..b5312fa965c0 100644 --- a/lib/stdlib/src/sofs.erl +++ b/lib/stdlib/src/sofs.erl @@ -1207,7 +1207,7 @@ sofs:to_external(X). extension(R, S, E) when ?IS_SET(R), ?IS_SET(S) -> case {?TYPE(R), ?TYPE(S), is_sofs_set(E)} of {T=?BINREL(DT, RT), ST, true} -> - case match_types(DT, ST) and match_types(RT, type(E)) of + case match_types(DT, ST) andalso match_types(RT, type(E)) of false -> erlang:error(type_mismatch); true -> @@ -1845,7 +1845,7 @@ sofs:to_external(J). J :: pos_integer()). join(R1, I1, R2, I2) when ?IS_SET(R1), ?IS_SET(R2), is_integer(I1), is_integer(I2) -> - case test_rel(R1, I1, lte) and test_rel(R2, I2, lte) of + case test_rel(R1, I1, lte) andalso test_rel(R2, I2, lte) of false -> erlang:error(badarg); true when ?TYPE(R1) =:= ?ANYTYPE -> R1; true when ?TYPE(R2) =:= ?ANYTYPE -> R2; @@ -1853,7 +1853,7 @@ join(R1, I1, R2, I2) L1 = ?LIST(raise_element(R1, I1)), L2 = ?LIST(raise_element(R2, I2)), T = relprod1(L1, L2), - F = case (I1 =:= 1) and (I2 =:= 1) of + F = case (I1 =:= 1) andalso (I2 =:= 1) of true -> fun({X,Y}) -> join_element(X, Y) end; false -> @@ -2437,7 +2437,7 @@ ordset_of_sets(_, _L, _T) -> %% Inlined. rel(Ts, [Type]) -> - case is_type(Type) and atoms_only(Type, 1) of + case is_type(Type) andalso atoms_only(Type, 1) of true -> rel(Ts, tuple_size(Type), Type); false -> @@ -2921,7 +2921,7 @@ relprod_n(RL, R, EmptyR, IsR) -> Error = {error, _Reason} -> Error; DType -> - Empty = any(fun is_empty_set/1, RL) or EmptyR, + Empty = any(fun is_empty_set/1, RL) orelse EmptyR, RType = range_type(RL, []), Type = ?BINREL(DType, RType), Prod = diff --git a/lib/stdlib/src/unicode.erl b/lib/stdlib/src/unicode.erl index 727fb27bb948..dc58c3473039 100644 --- a/lib/stdlib/src/unicode.erl +++ b/lib/stdlib/src/unicode.erl @@ -827,7 +827,7 @@ cbv({utf32,big}, <<0:8>>) -> cbv({utf32,big}, <<0:8,X:8>>) when X =< 16 -> 2; cbv({utf32,big}, <<0:8,X:8,Y:8>>) - when X =< 16, ((X > 0) or ((Y =< 215) or (Y >= 224))) -> + when X =< 16, ((X > 0) orelse ((Y =< 215) orelse (Y >= 224))) -> 1; cbv({utf32,big},_) -> false; @@ -838,7 +838,7 @@ cbv({utf32,little},<<_:8,_:8>>) -> cbv({utf32,little},<>) when X =:= 254; X =:= 255 -> false; cbv({utf32,little},<<_:8,Y:8,X:8>>) - when X =< 16, ((X > 0) or ((Y =< 215) or (Y >= 224))) -> + when X =< 16, ((X > 0) orelse ((Y =< 215) orelse (Y >= 224))) -> 1; cbv({utf32,little},_) -> false. diff --git a/lib/syntax_tools/src/erl_prettypr.erl b/lib/syntax_tools/src/erl_prettypr.erl index 1d7bd31883fa..9a473e123469 100644 --- a/lib/syntax_tools/src/erl_prettypr.erl +++ b/lib/syntax_tools/src/erl_prettypr.erl @@ -1556,7 +1556,7 @@ is_last_and_before_empty_line(H, [], #ctxt{empty_lines = EmptyLines}) -> catch error:badarith -> false end; is_last_and_before_empty_line(H, [H2 | _], #ctxt{empty_lines = EmptyLines}) -> - try ((get_line(H2) - get_line(H)) >= 2) and sets:is_element(get_line(H) + 1, EmptyLines) + try ((get_line(H2) - get_line(H)) >= 2) andalso sets:is_element(get_line(H) + 1, EmptyLines) catch error:badarith -> false end. diff --git a/lib/syntax_tools/src/erl_syntax.erl b/lib/syntax_tools/src/erl_syntax.erl index e1ec49ab82b2..6978fa34fd65 100644 --- a/lib/syntax_tools/src/erl_syntax.erl +++ b/lib/syntax_tools/src/erl_syntax.erl @@ -8419,7 +8419,7 @@ fold_function_names(Ns) -> fold_function_name(N) -> Name = arity_qualifier_body(N), Arity = arity_qualifier_argument(N), - true = ((type(Name) =:= atom) and (type(Arity) =:= integer)), + true = ((type(Name) =:= atom) andalso (type(Arity) =:= integer)), {concrete(Name), concrete(Arity)}. fold_variable_names(Vs) -> diff --git a/lib/syntax_tools/src/erl_syntax_lib.erl b/lib/syntax_tools/src/erl_syntax_lib.erl index ea0e67ec7aba..e7c2482a4d8c 100644 --- a/lib/syntax_tools/src/erl_syntax_lib.erl +++ b/lib/syntax_tools/src/erl_syntax_lib.erl @@ -1516,7 +1516,7 @@ analyze_type_name(Node) -> N = erl_syntax:arity_qualifier_body(Node), case ((erl_syntax:type(A) =:= integer) - and (erl_syntax:type(N) =:= atom)) + andalso (erl_syntax:type(N) =:= atom)) of true -> append_arity(erl_syntax:integer_value(A), @@ -1768,7 +1768,7 @@ analyze_file_attribute(Node) -> case erl_syntax:attribute_arguments(Node) of [F, N] -> case (erl_syntax:type(F) =:= string) - and (erl_syntax:type(N) =:= integer) of + andalso (erl_syntax:type(N) =:= integer) of true -> {erl_syntax:string_value(F), erl_syntax:integer_value(N)}; diff --git a/lib/syntax_tools/src/prettypr.erl b/lib/syntax_tools/src/prettypr.erl index 10a0437d86b4..f140885c912c 100644 --- a/lib/syntax_tools/src/prettypr.erl +++ b/lib/syntax_tools/src/prettypr.erl @@ -783,7 +783,7 @@ rewrite(#text{s = S}, C) -> end; #c_best_nest_or{w = W, r = R, i = N, d = D} -> L = width(S), - case ((L + N) > W) or (L > R) of + case ((L + N) > W) orelse (L > R) of true -> %% The first line of the LHS layout is %% not nice, so select the RHS. @@ -853,7 +853,7 @@ rewrite(#text{s = S}, C) -> end; #c_best_nest_or{w = W, r = R, i = N, d = D} -> L = width(S), - case ((L + N) > W) or (L > R) of + case ((L + N) > W) orelse (L > R) of true -> %% The first line of the LHS layout is %% not nice, so select the RHS. @@ -905,7 +905,7 @@ rewrite(#text{s = S}, C) -> end; #c_best_nest_or{w = W, r = R, i = N, d = D} -> L = width(S), - case ((L + N) > W) or (L > R) of + case ((L + N) > W) orelse (L > R) of true -> %% The first line of the LHS layout is not %% nice, so select the RHS (which contains diff --git a/lib/tftp/src/tftp_lib.erl b/lib/tftp/src/tftp_lib.erl index b3b784099357..fc1ed3fd55b7 100644 --- a/lib/tftp/src/tftp_lib.erl +++ b/lib/tftp/src/tftp_lib.erl @@ -224,14 +224,14 @@ do_parse_config([], #config{udp_host = Host, IsInet = lists:member(inet, UdpOptions), Host2 = if - (IsInet and not IsInet6); (not IsInet and not IsInet6) -> + (IsInet andalso not IsInet6); (not IsInet andalso not IsInet6) -> case inet:getaddr(Host, inet) of {ok, Addr} -> Addr; {error, Reason} -> exit({badarg, {host, Reason}}) end; - (IsInet6 and not IsInet) -> + (IsInet6 andalso not IsInet) -> case inet:getaddr(Host, inet6) of {ok, Addr} -> Addr; diff --git a/lib/wx/examples/simple/menu.erl b/lib/wx/examples/simple/menu.erl index ee4b92a00a24..0ed4137abc77 100644 --- a/lib/wx/examples/simple/menu.erl +++ b/lib/wx/examples/simple/menu.erl @@ -528,7 +528,7 @@ onMenuAction(#wx{id=?menuID_MENU_APPEND_SUB, obj=Frame}, #state{} = State) -> State; -onMenuAction(#wx{id=Id, obj=Frame}, #state{}=State) when ((Id >= ?menuID_DUMMY_FIRST) and (Id =< ?menuID_DUMMY_LAST)) -> +onMenuAction(#wx{id=Id, obj=Frame}, #state{}=State) when ((Id >= ?menuID_DUMMY_FIRST) andalso (Id =< ?menuID_DUMMY_LAST)) -> logMessage(Frame, "Dummy item #~p ~n", [Id - ?menuID_DUMMY_FIRST + 1]), State; diff --git a/lib/wx/examples/sudoku/sudoku_game.erl b/lib/wx/examples/sudoku/sudoku_game.erl index c4dcf6eef559..e006add46613 100644 --- a/lib/wx/examples/sudoku/sudoku_game.erl +++ b/lib/wx/examples/sudoku/sudoku_game.erl @@ -240,10 +240,10 @@ solve([Index|Rest],All, St, S, US, Orig) -> solve_1(RCM={R,C,_M}, Avail, St) -> All = all(RCM), - Poss = fun({RI,CI},Acc) when (RI == R) and (CI == C) -> Acc; + Poss = fun({RI,CI},Acc) when (RI == R) andalso (CI == C) -> Acc; ({RI,CI},Acc) -> gb_sets:union(poss(rcm({RI,CI}),St),Acc) end, - D = fun({RI,CI},Acc) when (RI == R) and (CI == C) -> + D = fun({RI,CI},Acc) when (RI == R) andalso (CI == C) -> io:format("~p:~p: ignore~n",[RI,CI]), Acc; ({RI,CI},Acc) -> diff --git a/lib/xmerl/src/xmerl_scan.erl b/lib/xmerl/src/xmerl_scan.erl index aec6767312c8..7d5a18966378 100644 --- a/lib/xmerl/src/xmerl_scan.erl +++ b/lib/xmerl/src/xmerl_scan.erl @@ -1200,8 +1200,8 @@ scan_pi(Str = [H1,H2,H3 | T],S0=#xmerl_scanner{line = L, col = C}, Pos, Ps) %% names beginning with [xX][mM][lL] are reserved for future use. ?bump_col(3), if - ((H2==$m) or (H2==$M)) and - ((H3==$l) or (H3==$L)) -> + ((H2==$m) orelse (H2==$M)) andalso + ((H3==$l) orelse (H3==$L)) -> scan_wellknown_pi(T,S,Pos,Ps); true -> {Target, _NamespaceInfo, T1, S1} = scan_name(Str, S), diff --git a/lib/xmerl/src/xmerl_xpath_pred.erl b/lib/xmerl/src/xmerl_xpath_pred.erl index 2423a22d436f..f2ebb6ec3538 100644 --- a/lib/xmerl/src/xmerl_xpath_pred.erl +++ b/lib/xmerl/src/xmerl_xpath_pred.erl @@ -177,9 +177,9 @@ comp_expr('!=', E1, E2, C) -> ?boolean(compare_eq_format(N1,N2,C) /= compare_eq_format(N2,N1,C)). bool_expr('or', E1, E2, C) -> - ?boolean(mk_boolean(C, E1) or mk_boolean(C, E2)); + ?boolean(mk_boolean(C, E1) orelse mk_boolean(C, E2)); bool_expr('and', E1, E2, C) -> - ?boolean(mk_boolean(C, E1) and mk_boolean(C, E2)). + ?boolean(mk_boolean(C, E1) andalso mk_boolean(C, E2)). %% According to chapter 3.4 in XML Path Language ver 1.0 the format of %% the compared objects are depending on the type of the other