File 1291-Cover-more-code-in-the-compiler.patch of Package erlang

From bf999baaa8ba553f9872b22cd57a41256d9b73a2 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 6 Mar 2023 05:42:55 +0100
Subject: [PATCH] Cover more code in the compiler

Most of the new test cases were found by erlfuzz.
---
 lib/compiler/test/beam_bounds_SUITE.erl | 12 ++++++++++++
 lib/compiler/test/beam_ssa_SUITE.erl    | 15 ++++++++++++++
 lib/compiler/test/bs_bincomp_SUITE.erl  |  6 ++++++
 lib/compiler/test/bs_match_SUITE.erl    | 23 +++++++++++++++++++++-
 lib/compiler/test/guard_SUITE.erl       | 26 +++++++++++++++++++++++++
 5 files changed, 81 insertions(+), 1 deletion(-)

diff --git a/lib/compiler/test/beam_bounds_SUITE.erl b/lib/compiler/test/beam_bounds_SUITE.erl
index 3076e32926..424a8b0a84 100644
--- a/lib/compiler/test/beam_bounds_SUITE.erl
+++ b/lib/compiler/test/beam_bounds_SUITE.erl
@@ -197,8 +197,11 @@ bnot_bounds(_Config) ->
     {'-inf',-8} = beam_bounds:bounds('bnot', {7,'+inf'}),
     {'-inf',9} = beam_bounds:bounds('bnot', {-10,'+inf'}),
     {-1114111,'+inf'} = beam_bounds:bounds('bnot', {'-inf', 1114110}),
+    any = beam_bounds:bounds('bnot', {0, 1 bsl 256}),
 
     -1 = bnot_bounds_2(0),
+    -43 = bnot_bounds_2_coverage(id(42)),
+    {'EXIT',{badarith,_}} = catch bnot_bounds_2_coverage(id(bad)),
 
     {'EXIT',{_,_}} = catch bnot_bounds_3(id(true)),
     {'EXIT',{_,_}} = catch bnot_bounds_3(id(false)),
@@ -218,6 +221,8 @@ bnot_bounds_1(R) ->
 bnot_bounds_2(0) -> -1;
 bnot_bounds_2(N) -> abs(bnot bnot_bounds_2(N)).
 
+bnot_bounds_2_coverage(N) -> bnot N.
+
 %% GH-7468. Would result in a bad_typed_register failure in beam_validator.
 bnot_bounds_3(A) ->
     (bnot round(((A xor false) andalso 1) + 2)) bsr ok.
diff --git a/lib/compiler/test/beam_ssa_SUITE.erl b/lib/compiler/test/beam_ssa_SUITE.erl
index 41193739c2..489a39bbb9 100644
--- a/lib/compiler/test/beam_ssa_SUITE.erl
+++ b/lib/compiler/test/beam_ssa_SUITE.erl
@@ -76,6 +76,11 @@ calls(Config) ->
     {'EXIT',{badarg,_}} = (catch call_error()),
     {'EXIT',{badarg,_}} = (catch call_error(42)),
     5 = start_it([erlang,length,1,2,3,4,5]),
+
+    {_,ok} = cover_call(id(true)),
+    {_,ok} = cover_call(id(false)),
+    {'EXIT',{{case_clause,ok},_}} = catch cover_call(id(ok)),
+
     ok.
 
 fun_call(Fun, X0) ->
@@ -106,6 +111,16 @@ start_it([_|_]=MFA) ->
 	[M,F|Args] -> M:F(Args)
     end.
 
+cover_call(A) ->
+    case A =/= ok of
+        B ->
+            {(term_to_binary(ok)),
+             case ok of
+                 _  when B -> ok
+             end}
+    end.
+
+
 tuple_matching(_Config) ->
     do_tuple_matching({tag,42}),
 
diff --git a/lib/compiler/test/bs_bincomp_SUITE.erl b/lib/compiler/test/bs_bincomp_SUITE.erl
index 4e7adcb7c5..0a03aa9400 100644
--- a/lib/compiler/test/bs_bincomp_SUITE.erl
+++ b/lib/compiler/test/bs_bincomp_SUITE.erl
@@ -182,8 +182,14 @@ mixed(Config) when is_list(Config) ->
 
     {'EXIT',{{bad_filter,<<>>},_}} = catch inconsistent_types_2(),
 
+    %% Cover some code in beam_ssa_pre_codegen.
+    [] = fun(A) ->
+                 [] = [ok || <<A:A, _:(A bsr 1)>> <= A]
+         end(id(<<>>)),
+
     cs_end().
 
+
 mixed_nested(L) ->
     << << << << E:16 >> || E <- L >> || true >>/binary, 99:(id(8))>>.
 
diff --git a/lib/compiler/test/bs_match_SUITE.erl b/lib/compiler/test/bs_match_SUITE.erl
index dd47641c2d..30a5c9fcc7 100644
--- a/lib/compiler/test/bs_match_SUITE.erl
+++ b/lib/compiler/test/bs_match_SUITE.erl
@@ -127,7 +127,11 @@ verify_highest_opcode(_Config) ->
                     ok;
                 TooHigh ->
                     ct:fail({too_high_opcode_for_21,TooHigh})
-            end;
+            end,
+
+            %% Cover min/max for OTP 25.
+            10 = max(0, min(10, id(42))),
+            ok;
         _ ->
             ok
     end.
@@ -869,6 +873,10 @@ coverage(Config) when is_list(Config) ->
     %% Cover code in beam_ssa_bsm.
     {'EXIT',{{badarg,<<>>},_}} = catch coverage_beam_ssa_bsm_error(id(<<>>)),
 
+    %% Cover code for merging registers in beam_validator.
+    42 = coverage_beam_validator(id(fun() -> 42 end)),
+    ok = coverage_beam_validator(id(fun() -> throw(whatever) end)),
+
     ok.
 
 coverage_fold(Fun, Acc, <<H,T/binary>>) ->
@@ -1025,6 +1033,19 @@ coverage_beam_ssa_pre_codegen(<<V0:0, V1:(V0 div V0), _:(V0 bsl V1)/bits>>) ->
 coverage_beam_ssa_bsm_error(<<B/bitstring>>) ->
     B andalso ok.
 
+coverage_beam_validator(F) ->
+    coverage_beam_validator(ok, ok, ok,
+       try
+           F()
+       catch
+           <<V:ok/binary>> ->
+               V;
+           _ ->
+               ok
+       end).
+
+coverage_beam_validator(_, _, _, Result) -> Result.
+
 multiple_uses(Config) when is_list(Config) ->
     {344,62879,345,<<245,159,1,89>>} = multiple_uses_1(<<1,88,245,159,1,89>>),
     true = multiple_uses_2(<<0,0,197,18>>),
diff --git a/lib/compiler/test/guard_SUITE.erl b/lib/compiler/test/guard_SUITE.erl
index a8cca96935..7bccbef9db 100644
--- a/lib/compiler/test/guard_SUITE.erl
+++ b/lib/compiler/test/guard_SUITE.erl
@@ -1156,11 +1156,19 @@ do_complex_guard_2(X, Y, Z) ->
 gbif(Config) when is_list(Config) ->
     error = gbif_1(1, {false,true}),
     ok = gbif_1(2, {false,true}),
+
+    error = gbif_2(id(0)),
+    error = gbif_2(id(<<>>)),
+
     ok.
 
 gbif_1(P, T) when element(P, T) -> ok;
 gbif_1(_, _) -> error.
 
+gbif_2(A) when bnot trunc((<<(true orelse ok)>> =/= A orelse 0) + 1) =:= A ->
+    ok;
+gbif_2(_) ->
+    error.
 
 t_is_boolean(Config) when is_list(Config) ->
     true = is_boolean(true),
@@ -2405,6 +2413,8 @@ binary_part(Config) when is_list(Config) ->
 		    true ->
 			error
 		end,
+    error = bp_coverage_1(id(<<>>)),
+
     ok.
 
 
@@ -2463,6 +2473,11 @@ bptest(B,A,C)  when erlang:binary_part(B,{A,C}) =:= <<3,3>> ->
 bptest(_,_,_) ->
     error.
 
+bp_coverage_1(A) when binary_part(A, A, floor(float(0))) ->
+    ok;
+bp_coverage_1(_) ->
+    error.
+
 -define(FAILING(C),
 	if
 	    C -> ct:fail(should_fail);
@@ -3117,6 +3132,12 @@ do_gh4788(N) ->
 beam_ssa_bool_coverage() ->
     {"*","abc"} = collect_modifiers("abc*", []),
     error = beam_ssa_bool_coverage_1(true),
+
+    ok = beam_ssa_bool_coverage_2(self()),
+    ok = beam_ssa_bool_coverage_2(true),
+    error = beam_ssa_bool_coverage_2(false),
+    error = beam_ssa_bool_coverage_2(42),
+
     ok.
 
 collect_modifiers([H | T], Buffer)
@@ -3131,6 +3152,11 @@ beam_ssa_bool_coverage_1(V) when V andalso 0, tuple_size(0) ->
 beam_ssa_bool_coverage_1(_) ->
     error.
 
+beam_ssa_bool_coverage_2(A) when is_pid(A) andalso true; A ->
+    ok;
+beam_ssa_bool_coverage_2(_) ->
+    error.
+
 gh_6164() ->
     true = do_gh_6164(id([])),
     {'EXIT',{{case_clause,42},_}} = catch do_gh_6164(id(0)),
-- 
2.35.3

openSUSE Build Service is sponsored by