Skip to content

Commit c4b379c

Browse files
committed
Make qlc generate andalso/orelse, not and/or
1 parent f2b12d5 commit c4b379c

19 files changed

+203
-204
lines changed

lib/crypto/test/crypto_SUITE.erl

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1578,7 +1578,7 @@ cipher_info_prop_aead_attr(Config) when is_list(Config) ->
15781578
case lists:foldl(fun(C,Ok) ->
15791579
case crypto:cipher_info(C) of
15801580
#{prop_aead := true} ->
1581-
true and Ok;
1581+
true andalso Ok;
15821582
_ ->
15831583
false
15841584
end
@@ -1596,7 +1596,7 @@ cipher_info_prop_aead_attr(Config) when is_list(Config) ->
15961596
case lists:foldl(fun(C,Ok) ->
15971597
case crypto:cipher_info(C) of
15981598
#{prop_aead := false} ->
1599-
true and Ok;
1599+
true andalso Ok;
16001600
_ ->
16011601
false
16021602
end
@@ -2163,7 +2163,7 @@ rand_uniform_aux_test(N) ->
21632163

21642164
crypto_rand_uniform(L,H) ->
21652165
R1 = (L-1) + rand:uniform(H-L),
2166-
case (R1 >= L) and (R1 < H) of
2166+
case R1 >= L andalso R1 < H of
21672167
true ->
21682168
ok;
21692169
false ->

lib/ssh/test/ssh_options_SUITE.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1124,7 +1124,7 @@ really_do_hostkey_fingerprint_check(Config, HashAlg) ->
11241124
end,
11251125
ct:log("check ~p == ~p (~p) and ~n~p~n in ~p (~p)~n",
11261126
[PeerName,Host,HostCheck,FP,FPs,FPCheck]),
1127-
HostCheck and FPCheck
1127+
HostCheck andalso FPCheck
11281128
end,
11291129

11301130
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
@@ -575,11 +575,11 @@ ssh_list_public_key(Config) when is_list(Config) ->
575575
["openssh_rsa_pub", "openssh_dsa_pub", "openssh_ecdsa_pub"]),
576576

577577
true =
578-
(chk_decode(Data_openssh, Expect_openssh, openssh_key) and
579-
chk_decode(Data_ssh2, Expect_ssh2, rfc4716_key) and
580-
chk_decode(Data_openssh, Expect_openssh, public_key) and
581-
chk_decode(Data_ssh2, Expect_ssh2, public_key) and
582-
chk_encode(Expect_openssh, openssh_key) and
578+
(chk_decode(Data_openssh, Expect_openssh, openssh_key) andalso
579+
chk_decode(Data_ssh2, Expect_ssh2, rfc4716_key) andalso
580+
chk_decode(Data_openssh, Expect_openssh, public_key) andalso
581+
chk_decode(Data_ssh2, Expect_ssh2, public_key) andalso
582+
chk_encode(Expect_openssh, openssh_key) andalso
583583
chk_encode(Expect_ssh2, rfc4716_key)
584584
).
585585

@@ -706,7 +706,7 @@ ssh_known_hosts(Config) when is_list(Config) ->
706706

707707
Value1 = proplists:get_value(hostnames, Attributes1, undefined),
708708
Value2 = proplists:get_value(hostnames, Attributes2, undefined),
709-
true = (Value1 =/= undefined) and (Value2 =/= undefined),
709+
true = Value1 =/= undefined andalso Value2 =/= undefined,
710710

711711
Encoded = ssh_file:encode(Decoded, known_hosts),
712712
Decoded = ssh_file:decode(Encoded, known_hosts).
@@ -721,7 +721,7 @@ ssh1_known_hosts(Config) when is_list(Config) ->
721721

722722
Value1 = proplists:get_value(hostnames, Attributes1, undefined),
723723
Value2 = proplists:get_value(hostnames, Attributes2, undefined),
724-
true = (Value1 =/= undefined) and (Value2 =/= undefined),
724+
true = Value1 =/= undefined andalso Value2 =/= undefined,
725725

726726
Comment ="dhopson@VMUbuntu-DSH comment with whitespaces",
727727
Comment = proplists:get_value(comment, Attributes3),
@@ -765,7 +765,7 @@ ssh1_auth_keys(Config) when is_list(Config) ->
765765

766766
Value1 = proplists:get_value(bits, Attributes2, undefined),
767767
Value2 = proplists:get_value(bits, Attributes3, undefined),
768-
true = (Value1 =/= undefined) and (Value2 =/= undefined),
768+
true = Value1 =/= undefined andalso Value2 =/= undefined,
769769

770770
Comment2 = Comment3 = "dhopson@VMUbuntu-DSH",
771771
Comment4 = Comment5 ="dhopson@VMUbuntu-DSH comment with whitespaces",

lib/stdlib/src/qlc.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2184,7 +2184,7 @@ join_merge_info(QNum, QInfo, Code, G, ExtraConstants) ->
21842184
A = anno0(),
21852185
Call = {call,A,{atom,A,element},[{integer,A,Col},EPV]},
21862186
F = list2op([{op,A,Op,abstract_term(Con),Call}
2187-
|| {Con,Op} <- ConstOps], 'or', A),
2187+
|| {Con,Op} <- ConstOps], 'orelse', A),
21882188
term_to_binary(F)
21892189
end ||
21902190
{Col,ConstOps} <- ExtraConstants],

lib/stdlib/src/qlc_pt.erl

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -950,7 +950,7 @@ join_handle(AP, Anno, [F, H, O, C], Constants) ->
950950
A = anno0(),
951951
G0 = [begin
952952
Call = {call,A,{atom,A,element},[{integer,A,Col},O]},
953-
list2op([{op,A,Op,Con,Call} || {Con,Op} <- Cs], 'or')
953+
list2op([{op,A,Op,Con,Call} || {Con,Op} <- Cs], 'orelse')
954954
end || {Col,Cs} <- Constants],
955955
G = if G0 =:= [] -> G0; true -> [G0] end,
956956
CC1 = {clause,Anno,[AP],G,
@@ -1713,10 +1713,9 @@ filter1({op, _, Op, L0, R0}, Fs, FS) when Op =:= '=:='; Op =:= '==' ->
17131713
F -> [F]
17141714
end
17151715
end, Fs);
1716-
filter1({op, _, Op, L, R}, Fs, FS) when Op =:= 'and'; Op =:= 'andalso' ->
1716+
filter1({op, _, Op, L, R}, Fs, FS) when Op =:= 'andalso' ->
17171717
filter1(R, filter1(L, Fs, FS), FS);
1718-
filter1({op, _, Op, L, R}, Fs, FS) when Op =:= 'or';
1719-
Op =:= 'orelse';
1718+
filter1({op, _, Op, L, R}, Fs, FS) when Op =:= 'orelse';
17201719
Op =:= 'xor' ->
17211720
filter1(L, Fs, FS) ++ filter1(R, Fs, FS);
17221721
filter1({atom,_,Atom}, _Fs, _FS) when Atom =/= true ->
@@ -1756,9 +1755,9 @@ safe_filter1({op, _, Op, L0, R0}, Fs, FS) when Op =:= '=:='; Op =:= '==' ->
17561755
F -> [F]
17571756
end
17581757
end, Fs);
1759-
safe_filter1({op, _, Op, L, R}, Fs, FS) when Op =:= 'and'; Op =:= 'andalso' ->
1758+
safe_filter1({op, _, Op, L, R}, Fs, FS) when Op =:= 'andalso' ->
17601759
safe_filter1(R, safe_filter1(L, Fs, FS), FS);
1761-
safe_filter1({op, _, Op, L, R}, Fs, FS) when Op =:= 'or'; Op =:= 'orelse' ->
1760+
safe_filter1({op, _, Op, L, R}, Fs, FS) when Op =:= 'orelse' ->
17621761
safe_filter1(L, Fs, FS) ++ safe_filter1(R, Fs, FS);
17631762
safe_filter1({atom,_,true}, Fs, _FS) ->
17641763
Fs;

lib/stdlib/test/beam_lib_SUITE.erl

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

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

967967
ver(S, {error, beam_lib, R}) ->
968968
[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
@@ -747,12 +747,13 @@ encode_decode_loop(Range, X) ->
747747
R = binary:decode_unsigned(make_unaligned(PaddedLittle),little),
748748
S = binref:decode_unsigned(PaddedLittle,little),
749749
T = binref:decode_unsigned(PaddedBig),
750-
case (((A =:= B) and (B =:= C) and (C =:= D)) and
751-
((E =:= F)) and
752-
((N =:= G) and (G =:= H) and (H =:= I) and
753-
(I =:= J) and (J =:= K) and (K =:= L) and (L =:= M)) and
754-
((M =:= O) and (O =:= P) and (P =:= Q) and (Q =:= R) and
755-
(R =:= S) and (S =:= T)))of
750+
case (A =:= B andalso B =:= C andalso C =:= D)
751+
andalso (E =:= F) andalso (N =:= G andalso G =:= H andalso H =:= I
752+
andalso I =:= J andalso J =:= K
753+
andalso K =:= L andalso L =:= M)
754+
andalso (M =:= O andalso O =:= P andalso P =:= Q
755+
andalso Q =:= R andalso R =:= S andalso S =:= T)
756+
of
756757
true ->
757758
encode_decode_loop(Range,X-1);
758759
_ ->
@@ -1304,7 +1305,7 @@ do_split_comp(N,H,Opts) ->
13041305
A = ?MASK_ERROR(binref:split(H,N,Opts)),
13051306
D = ?MASK_ERROR(binary:split(H,binary:compile_pattern(N),Opts)),
13061307
if
1307-
(A =/= [N]) and is_list(A) ->
1308+
A =/= [N] andalso is_list(A) ->
13081309
put(success_counter,get(success_counter)+1);
13091310
true ->
13101311
ok
@@ -1352,7 +1353,7 @@ do_replace_comp(N,H,R,Opts) ->
13521353
A = ?MASK_ERROR(binref:replace(H,N,R,Opts)),
13531354
D = ?MASK_ERROR(binary:replace(H,binary:compile_pattern(N),R,Opts)),
13541355
if
1355-
(A =/= N) and is_binary(A) ->
1356+
A =/= N andalso is_binary(A) ->
13561357
put(success_counter,get(success_counter)+1);
13571358
true ->
13581359
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
@@ -667,10 +667,10 @@ simple_cases(Config) when is_list(Config) ->
667667
"(2#101 band 2#10101) bor (2#110 bxor 2#010).", 5),
668668
check(fun() -> (2#1 bsl 4) + (2#10000 bsr 3) end,
669669
"(2#1 bsl 4) + (2#10000 bsr 3).", 18),
670-
check(fun() -> ((1<3) and ((1 =:= 2) or (1 =/= 2))) xor (1=<2) end,
671-
"((1<3) and ((1 =:= 2) or (1 =/= 2))) xor (1=<2).", false),
672-
check(fun() -> (a /= b) or (2 > 4) or (3 >= 3) end,
673-
"(a /= b) or (2 > 4) or (3 >= 3).", true),
670+
check(fun() -> (1<3 andalso (1 =:= 2 orelse 1 =/= 2)) xor (1=<2) end,
671+
"(1<3 andalso (1 =:= 2 orelse 1 =/= 2)) xor (1=<2).", false),
672+
check(fun() -> a /= b orelse 2 > 4 orelse 3 >= 3 end,
673+
"a /= b orelse 2 > 4 orelse 3 >= 3.", true),
674674
check(fun() -> "hej" ++ "san" =/= "hejsan" -- "san" end,
675675
"\"hej\" ++ \"san\" =/= \"hejsan\" -- \"san\".", true),
676676
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
@@ -620,7 +620,7 @@ unused_vars_warn_fun(Config) when is_list(Config) ->
620620
E;
621621
a([A,B,C,D,E]) -> % E unused.
622622
fun() ->
623-
(C == <<A:A>>) andalso (<<17:B>> == D)
623+
C == <<A:A>> andalso <<17:B>> == D
624624
end.
625625
">>,
626626
[warn_unused_vars],
@@ -1953,8 +1953,8 @@ guard(Config) when is_list(Config) ->
19531953
{guard7,
19541954
<<"-record(apa,{}).
19551955
t() ->
1956-
[X || X <- [1,#apa{},3], (3+is_record(X, apa)) orelse
1957-
(is_record(X, apa)*2)].
1956+
[X || X <- [1,#apa{},3], 3+is_record(X, apa) orelse
1957+
is_record(X, apa)*2].
19581958
">>,
19591959
[],
19601960
[]},

0 commit comments

Comments
 (0)