Skip to content

Commit 31d81e6

Browse files
committed
Replace 'or'/'and' with 'orelse'/'andalso' in test suites
1 parent dea9304 commit 31d81e6

17 files changed

+244
-244
lines changed

lib/crypto/test/crypto_SUITE.erl

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1514,7 +1514,7 @@ cipher_info_prop_aead_attr(Config) when is_list(Config) ->
15141514
case lists:foldl(fun(C,Ok) ->
15151515
case crypto:cipher_info(C) of
15161516
#{prop_aead := true} ->
1517-
true and Ok;
1517+
true andalso Ok;
15181518
_ ->
15191519
false
15201520
end
@@ -1532,7 +1532,7 @@ cipher_info_prop_aead_attr(Config) when is_list(Config) ->
15321532
case lists:foldl(fun(C,Ok) ->
15331533
case crypto:cipher_info(C) of
15341534
#{prop_aead := false} ->
1535-
true and Ok;
1535+
true andalso Ok;
15361536
_ ->
15371537
false
15381538
end
@@ -2075,7 +2075,7 @@ rand_uniform_aux_test(N) ->
20752075

20762076
crypto_rand_uniform(L,H) ->
20772077
R1 = (L-1) + rand:uniform(H-L),
2078-
case (R1 >= L) and (R1 < H) of
2078+
case R1 >= L andalso R1 < H of
20792079
true ->
20802080
ok;
20812081
false ->

lib/ssh/test/ssh_options_SUITE.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1076,7 +1076,7 @@ really_do_hostkey_fingerprint_check(Config, HashAlg) ->
10761076
end,
10771077
ct:log("check ~p == ~p (~p) and ~n~p~n in ~p (~p)~n",
10781078
[PeerName,Host,HostCheck,FP,FPs,FPCheck]),
1079-
HostCheck and FPCheck
1079+
HostCheck andalso FPCheck
10801080
end,
10811081

10821082
ssh_test_lib:connect(Host, Port, [{silently_accept_hosts,

lib/ssh/test/ssh_pubkey_SUITE.erl

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -573,11 +573,11 @@ ssh_list_public_key(Config) when is_list(Config) ->
573573
["openssh_rsa_pub", "openssh_dsa_pub", "openssh_ecdsa_pub"]),
574574

575575
true =
576-
(chk_decode(Data_openssh, Expect_openssh, openssh_key) and
577-
chk_decode(Data_ssh2, Expect_ssh2, rfc4716_key) and
578-
chk_decode(Data_openssh, Expect_openssh, public_key) and
579-
chk_decode(Data_ssh2, Expect_ssh2, public_key) and
580-
chk_encode(Expect_openssh, openssh_key) and
576+
(chk_decode(Data_openssh, Expect_openssh, openssh_key) andalso
577+
chk_decode(Data_ssh2, Expect_ssh2, rfc4716_key) andalso
578+
chk_decode(Data_openssh, Expect_openssh, public_key) andalso
579+
chk_decode(Data_ssh2, Expect_ssh2, public_key) andalso
580+
chk_encode(Expect_openssh, openssh_key) andalso
581581
chk_encode(Expect_ssh2, rfc4716_key)
582582
).
583583

@@ -702,7 +702,7 @@ ssh_known_hosts(Config) when is_list(Config) ->
702702

703703
Value1 = proplists:get_value(hostnames, Attributes1, undefined),
704704
Value2 = proplists:get_value(hostnames, Attributes2, undefined),
705-
true = (Value1 =/= undefined) and (Value2 =/= undefined),
705+
true = Value1 =/= undefined andalso Value2 =/= undefined,
706706

707707
Encoded = ssh_file:encode(Decoded, known_hosts),
708708
Decoded = ssh_file:decode(Encoded, known_hosts).
@@ -717,7 +717,7 @@ ssh1_known_hosts(Config) when is_list(Config) ->
717717

718718
Value1 = proplists:get_value(hostnames, Attributes1, undefined),
719719
Value2 = proplists:get_value(hostnames, Attributes2, undefined),
720-
true = (Value1 =/= undefined) and (Value2 =/= undefined),
720+
true = Value1 =/= undefined andalso Value2 =/= undefined,
721721

722722
Comment ="dhopson@VMUbuntu-DSH comment with whitespaces",
723723
Comment = proplists:get_value(comment, Attributes3),
@@ -761,7 +761,7 @@ ssh1_auth_keys(Config) when is_list(Config) ->
761761

762762
Value1 = proplists:get_value(bits, Attributes2, undefined),
763763
Value2 = proplists:get_value(bits, Attributes3, undefined),
764-
true = (Value1 =/= undefined) and (Value2 =/= undefined),
764+
true = Value1 =/= undefined andalso Value2 =/= undefined,
765765

766766
Comment2 = Comment3 = "dhopson@VMUbuntu-DSH",
767767
Comment4 = Comment5 ="dhopson@VMUbuntu-DSH comment with whitespaces",

lib/stdlib/test/beam_lib_SUITE.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -960,7 +960,7 @@ verify_error(S, R) ->
960960

961961
%% Also make sure that formatted message is not just the term printed.
962962
Handled = beam_lib:format_error(R) =/= io_lib:format("~p~n", [R]),
963-
true = ((FM > 0) or (BM > 0)) and Handled.
963+
true = (FM > 0 orelse BM > 0) andalso Handled.
964964

965965
ver(S, {error, beam_lib, R}) ->
966966
[S|_] = tuple_to_list(R),

lib/stdlib/test/binary_module_SUITE.erl

Lines changed: 9 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -745,12 +745,13 @@ encode_decode_loop(Range, X) ->
745745
R = binary:decode_unsigned(make_unaligned(PaddedLittle),little),
746746
S = binref:decode_unsigned(PaddedLittle,little),
747747
T = binref:decode_unsigned(PaddedBig),
748-
case (((A =:= B) and (B =:= C) and (C =:= D)) and
749-
((E =:= F)) and
750-
((N =:= G) and (G =:= H) and (H =:= I) and
751-
(I =:= J) and (J =:= K) and (K =:= L) and (L =:= M)) and
752-
((M =:= O) and (O =:= P) and (P =:= Q) and (Q =:= R) and
753-
(R =:= S) and (S =:= T)))of
748+
case (A =:= B andalso B =:= C andalso C =:= D)
749+
andalso (E =:= F) andalso (N =:= G andalso G =:= H andalso H =:= I
750+
andalso I =:= J andalso J =:= K
751+
andalso K =:= L andalso L =:= M)
752+
andalso (M =:= O andalso O =:= P andalso P =:= Q
753+
andalso Q =:= R andalso R =:= S andalso S =:= T)
754+
of
754755
true ->
755756
encode_decode_loop(Range,X-1);
756757
_ ->
@@ -1302,7 +1303,7 @@ do_split_comp(N,H,Opts) ->
13021303
A = ?MASK_ERROR(binref:split(H,N,Opts)),
13031304
D = ?MASK_ERROR(binary:split(H,binary:compile_pattern(N),Opts)),
13041305
if
1305-
(A =/= [N]) and is_list(A) ->
1306+
A =/= [N] andalso is_list(A) ->
13061307
put(success_counter,get(success_counter)+1);
13071308
true ->
13081309
ok
@@ -1350,7 +1351,7 @@ do_replace_comp(N,H,R,Opts) ->
13501351
A = ?MASK_ERROR(binref:replace(H,N,R,Opts)),
13511352
D = ?MASK_ERROR(binary:replace(H,binary:compile_pattern(N),R,Opts)),
13521353
if
1353-
(A =/= N) and is_binary(A) ->
1354+
A =/= N andalso is_binary(A) ->
13541355
put(success_counter,get(success_counter)+1);
13551356
true ->
13561357
ok

lib/stdlib/test/binref.erl

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ match(Haystack,{Needles},Options) ->
3434
match(Haystack,Needles,Options);
3535
match(Haystack,Needles,Options) ->
3636
try
37-
true = is_binary(Haystack) and is_list(Needles), % badarg, not function_clause
37+
true = is_binary(Haystack) andalso is_list(Needles), % badarg, not function_clause
3838
case get_opts_match(Options,nomatch) of
3939
nomatch ->
4040
mloop(Haystack,Needles);
@@ -61,7 +61,7 @@ matches(Haystack,{Needles},Options) ->
6161
matches(Haystack,Needles,Options);
6262
matches(Haystack,Needles,Options) ->
6363
try
64-
true = is_binary(Haystack) and is_list(Needles), % badarg, not function_clause
64+
true = is_binary(Haystack) andalso is_list(Needles), % badarg, not function_clause
6565
case get_opts_match(Options,nomatch) of
6666
nomatch ->
6767
msloop(Haystack,Needles);
@@ -377,7 +377,7 @@ list_to_bin(List) ->
377377
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
378378
longest_common_prefix(LB) ->
379379
try
380-
true = is_list(LB) and (length(LB) > 0), % Make badarg instead of function clause
380+
true = is_list(LB) andalso length(LB) > 0, % Make badarg instead of function clause
381381
do_longest_common_prefix(LB,0)
382382
catch
383383
_:_ ->
@@ -412,7 +412,7 @@ do_lcp([Bin|T],X,Ch) ->
412412
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
413413
longest_common_suffix(LB) ->
414414
try
415-
true = is_list(LB) and (length(LB) > 0), % Make badarg instead of function clause
415+
true = is_list(LB) andalso length(LB) > 0, % Make badarg instead of function clause
416416
do_longest_common_suffix(LB,0)
417417
catch
418418
_:_ ->
@@ -474,7 +474,7 @@ copy(Subject) ->
474474
copy(Subject,1).
475475
copy(Subject,N) ->
476476
try
477-
true = is_integer(N) and (N >= 0) and is_binary(Subject), % Badarg, not function clause
477+
true = is_integer(N) andalso N >= 0 andalso is_binary(Subject), % Badarg, not function clause
478478
erlang:list_to_binary(lists:duplicate(N,Subject))
479479
catch
480480
_:_ ->
@@ -488,7 +488,7 @@ encode_unsigned(Unsigned) ->
488488
encode_unsigned(Unsigned,big).
489489
encode_unsigned(Unsigned,Endian) ->
490490
try
491-
true = is_integer(Unsigned) and (Unsigned >= 0),
491+
true = is_integer(Unsigned) andalso Unsigned >= 0,
492492
if
493493
Unsigned =:= 0 ->
494494
<<0>>;

lib/stdlib/test/erl_eval_SUITE.erl

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -656,10 +656,10 @@ simple_cases(Config) when is_list(Config) ->
656656
"(2#101 band 2#10101) bor (2#110 bxor 2#010).", 5),
657657
check(fun() -> (2#1 bsl 4) + (2#10000 bsr 3) end,
658658
"(2#1 bsl 4) + (2#10000 bsr 3).", 18),
659-
check(fun() -> ((1<3) and ((1 =:= 2) or (1 =/= 2))) xor (1=<2) end,
660-
"((1<3) and ((1 =:= 2) or (1 =/= 2))) xor (1=<2).", false),
661-
check(fun() -> (a /= b) or (2 > 4) or (3 >= 3) end,
662-
"(a /= b) or (2 > 4) or (3 >= 3).", true),
659+
check(fun() -> (1<3 andalso (1 =:= 2 orelse 1 =/= 2)) xor (1=<2) end,
660+
"(1<3 andalso (1 =:= 2 orelse 1 =/= 2)) xor (1=<2).", false),
661+
check(fun() -> a /= b orelse 2 > 4 orelse 3 >= 3 end,
662+
"a /= b orelse 2 > 4 orelse 3 >= 3.", true),
663663
check(fun() -> "hej" ++ "san" =/= "hejsan" -- "san" end,
664664
"\"hej\" ++ \"san\" =/= \"hejsan\" -- \"san\".", true),
665665
check(fun() -> (bnot 1) < -0 end, "(bnot (+1)) < -0.", true),

lib/stdlib/test/erl_lint_SUITE.erl

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -616,7 +616,7 @@ unused_vars_warn_fun(Config) when is_list(Config) ->
616616
E;
617617
a([A,B,C,D,E]) -> % E unused.
618618
fun() ->
619-
(C == <<A:A>>) andalso (<<17:B>> == D)
619+
C == <<A:A>> andalso <<17:B>> == D
620620
end.
621621
">>,
622622
[warn_unused_vars],
@@ -1925,8 +1925,8 @@ guard(Config) when is_list(Config) ->
19251925
{guard7,
19261926
<<"-record(apa,{}).
19271927
t() ->
1928-
[X || X <- [1,#apa{},3], (3+is_record(X, apa)) orelse
1929-
(is_record(X, apa)*2)].
1928+
[X || X <- [1,#apa{},3], 3+is_record(X, apa) orelse
1929+
is_record(X, apa)*2].
19301930
">>,
19311931
[],
19321932
[]},

lib/stdlib/test/erl_pp_SUITE.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1542,7 +1542,7 @@ pp_expr(List, Options) when is_list(List) ->
15421542
if
15431543
PP1 =:= PP2 -> % same line numbers
15441544
case
1545-
(test_max_line(PP1) =:= ok) and (test_new_line(PPneg) =:= ok)
1545+
test_max_line(PP1) =:= ok andalso test_new_line(PPneg) =:= ok
15461546
of
15471547
true ->
15481548
ok;

lib/stdlib/test/ets_SUITE.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5400,8 +5400,8 @@ info_do(Opts) ->
54005400
end, set, Opts),
54015401
PublicOrCurr =
54025402
fun(Curr) ->
5403-
case lists:member({write_concurrency, false}, Opts) or
5404-
lists:member(private, Opts) or
5403+
case lists:member({write_concurrency, false}, Opts) orelse
5404+
lists:member(private, Opts) orelse
54055405
lists:member(protected, Opts) of
54065406
true -> Curr;
54075407
false -> public

0 commit comments

Comments
 (0)