File 2683-Improve-coverage-for-the-compiler.patch of Package erlang

From e53027a11e7d0f81b167264867ce9e6548773c48 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Sat, 2 Mar 2024 08:33:08 +0100
Subject: [PATCH 3/3] Improve coverage for the compiler

Add tests found by `erlfuzz`, as well as some other tests, to cover
more lines in the compiler.
---
 lib/compiler/test/beam_block_SUITE.erl        |  7 +++
 lib/compiler/test/beam_type_SUITE.erl         | 55 ++++++++++++++++++-
 lib/compiler/test/beam_validator_SUITE.erl    | 27 ++++++++-
 lib/compiler/test/compilation_SUITE.erl       |  9 ++-
 .../test/compilation_SUITE_data/use_nifs.erl  | 19 +++++++
 lib/compiler/test/compile_SUITE.erl           | 33 ++++++++++-
 lib/compiler/test/guard_SUITE.erl             | 46 ++++++++++++++++
 7 files changed, 188 insertions(+), 8 deletions(-)
 create mode 100644 lib/compiler/test/compilation_SUITE_data/use_nifs.erl

diff --git a/lib/compiler/test/beam_block_SUITE.erl b/lib/compiler/test/beam_block_SUITE.erl
index f5a816fb9c..c7fa0fb61f 100644
--- a/lib/compiler/test/beam_block_SUITE.erl
+++ b/lib/compiler/test/beam_block_SUITE.erl
@@ -317,6 +317,10 @@ coverage(Config) ->
 
     {'EXIT',{badarg,_}} = catch coverage_4(a, b),
 
+    ~"true" = coverage_5(id(latin1), id(true)),
+    ~"true" = coverage_5(id(utf8), id(false)),
+    {'EXIT',{badarg,_}} = catch coverage_5(id(42), id(42)),
+
     ok.
 
 coverage_1() ->
@@ -347,6 +351,9 @@ coverage_4(A, B) ->
 do_coverage_4(_, _, _, _) ->
     ok.
 
+coverage_5(B, A) ->
+    atom_to_binary((A or A) == A, B).
+
 %%%
 %%% Common functions.
 %%%
diff --git a/lib/compiler/test/beam_type_SUITE.erl b/lib/compiler/test/beam_type_SUITE.erl
index dd2eacbce1..81cc79782d 100644
--- a/lib/compiler/test/beam_type_SUITE.erl
+++ b/lib/compiler/test/beam_type_SUITE.erl
@@ -31,7 +31,8 @@
          switch_fail_inference/1,failures/1,
          cover_maps_functions/1,min_max_mixed_types/1,
          not_equal/1,infer_relops/1,binary_unit/1,premature_concretization/1,
-         funs/1,will_succeed/1,float_confusion/1]).
+         funs/1,will_succeed/1,float_confusion/1,
+         cover_convert_ext/1]).
 
 %% Force id/1 to return 'any'.
 -export([id/1]).
@@ -77,7 +78,8 @@ groups() ->
        premature_concretization,
        funs,
        will_succeed,
-       float_confusion
+       float_confusion,
+       cover_convert_ext
       ]}].
 
 init_per_suite(Config) ->
@@ -365,6 +367,16 @@ coverage(Config) ->
     {'EXIT',{badarg,_}} = catch false ++ true,
     {'EXIT',{badarg,_}} = catch false -- true,
 
+    ok = coverage_5(id(0)),
+    {'EXIT',{function_clause,_}} = catch coverage_5(id(0.0)),
+    ok = coverage_5(id(16)),
+    {'EXIT',{{case_clause,false},_}} = catch coverage_5(id(-1)),
+
+    ok = coverage_6(id(0)),
+    ok = catch coverage_6(id(0.0)),
+    ok = coverage_6(id(16)),
+    {'EXIT',{{case_clause,false},_}} = catch coverage_6(id(-1)),
+
     ok.
 
 coverage_1() ->
@@ -387,6 +399,23 @@ coverage_3("a" = V) when is_function(V, false) ->
 coverage_4(X, Y) ->
     10 * (X + Y).
 
+coverage_5(A) when is_integer(A) ->
+    case 15 < A of
+        _ when 0 =< A ->
+            ok;
+        true ->
+            error
+    end.
+
+coverage_6(A) ->
+    case 15 < A of
+        _ when 0 =< A ->
+            ok;
+        true ->
+            error
+    end.
+
+
 booleans(_Config) ->
     {'EXIT',{{case_clause,_},_}} = (catch do_booleans_1(42)),
 
@@ -619,6 +648,10 @@ cons(_Config) ->
 
     {$a,"bc"} = cons_hdtl(true),
     {$d,"ef"} = cons_hdtl(false),
+
+    {'EXIT',{badarg,_}} = catch hd(ok),
+    {'EXIT',{badarg,_}} = catch tl(ok),
+
     ok.
 
 cons(assigned, Instrument) ->
@@ -1375,6 +1408,7 @@ min_max_mixed_types(_Config) ->
     -10 = id(min(id(0)+1, -10)),
     43 = id(max(3, id(42)+1)),
     42 = id(max(-99, id(41)+1)),
+    -42 = id(min(id(0), -id(42))),
 
     ok.
 
@@ -1564,6 +1598,23 @@ float_confusion_6() ->
         end)
     >>.
 
+cover_convert_ext(_Config) ->
+
+    Otp26AllTypes = 2#1111_1111_1111,
+    Otp26Version = 2,
+    Otp26Types = <<Otp26AllTypes:16, -1:16,0:64,0:64,1:8>>,
+    _ = beam_types:decode_ext(beam_types:convert_ext(Otp26Version, Otp26Types)),
+
+    Otp25AllTypes = 2#1111_1111_1111,
+    Otp25Version = 1,
+    Otp25Types = <<Otp25AllTypes:16,1:64,0:64, Otp25AllTypes:16,7:64,10:64>>,
+    _ = beam_types:decode_ext(beam_types:convert_ext(Otp25Version, Otp25Types)),
+
+    none = beam_types:convert_ext(0, <<>>),
+
+    ok.
+
+
 %%%
 %%% Common utilities.
 %%%
diff --git a/lib/compiler/test/beam_validator_SUITE.erl b/lib/compiler/test/beam_validator_SUITE.erl
index 7a663272a8..1acba08d1d 100644
--- a/lib/compiler/test/beam_validator_SUITE.erl
+++ b/lib/compiler/test/beam_validator_SUITE.erl
@@ -44,7 +44,7 @@
          infer_relops/1,
          not_equal_inference/1,bad_bin_unit/1,singleton_inference/1,
          inert_update_type/1,range_inference/1,
-         too_many_arguments/1,ensure_bits/1]).
+         bif_inference/1,too_many_arguments/1,ensure_bits/1]).
 
 -include_lib("common_test/include/ct.hrl").
 
@@ -82,7 +82,7 @@ groups() ->
        container_performance,infer_relops,
        not_equal_inference,bad_bin_unit,singleton_inference,
        inert_update_type,range_inference,
-       too_many_arguments,ensure_bits]}].
+       bif_inference,too_many_arguments,ensure_bits]}].
 
 init_per_suite(Config) ->
     test_lib:recompile(?MODULE),
@@ -1148,6 +1148,27 @@ range_inference_1(<<X/utf8>>) ->
             ok
     end.
 
+bif_inference(_Config) ->
+    ok = bif_inference_is_bitstring(id(<<>>), id(<<>>)),
+    error = bif_inference_is_bitstring(id(a), id(a)),
+
+    ok = bif_inference_is_function(id(fun id/1), id(fun id/1)),
+    ok = bif_inference_is_function(true, true),
+    error = bif_inference_is_function(id(fun id/1), a),
+    error = bif_inference_is_function(a, a),
+
+    ok.
+
+bif_inference_is_bitstring(A, A) when A andalso ok; is_bitstring(A) ->
+    ok;
+bif_inference_is_bitstring(_, _) ->
+    error.
+
+bif_inference_is_function(A, A)  when A orelse ok; is_function(A) ->
+    ok;
+bif_inference_is_function(_, _) ->
+    error.
+
 %% GH-9113: We didn't reject funs, comprehensions, and the likes which exceeded
 %% the argument limit.
 too_many_arguments(_Config) ->
diff --git a/lib/compiler/test/compilation_SUITE.erl b/lib/compiler/test/compilation_SUITE.erl
index f8c61a354c..e94b3220cb 100644
--- a/lib/compiler/test/compilation_SUITE.erl
+++ b/lib/compiler/test/compilation_SUITE.erl
@@ -58,7 +58,8 @@
 	 vsn_1/1,
 	 vsn_2/1,
          vsn_3/1,
-         infinite_loop/0,infinite_loop/1]).
+         infinite_loop/0,infinite_loop/1,
+         use_nifs/1]).
 
 -include_lib("common_test/include/ct.hrl").
 
@@ -86,7 +87,8 @@ groups() ->
        otp_5553,otp_5632,otp_5714,otp_5872,otp_6121,
        otp_7202,on_load,on_load_inline,
        string_table,otp_8949_a,split_cases,
-       infinite_loop]}].
+       infinite_loop,
+       use_nifs]}].
 
 init_per_suite(Config) ->
     test_lib:recompile(?MODULE),
@@ -138,6 +140,8 @@ end_per_group(_GroupName, Config) ->
 ?comp(on_load).
 ?comp(on_load_inline).
 
+?comp(use_nifs).
+
 infinite_loop() -> [{timetrap,{minutes,1}}].
 ?comp(infinite_loop).
 
@@ -442,5 +446,4 @@ do_split_cases(A) ->
     end,
     Z.
 
-
 id(I) -> I.
diff --git a/lib/compiler/test/compilation_SUITE_data/use_nifs.erl b/lib/compiler/test/compilation_SUITE_data/use_nifs.erl
new file mode 100644
index 0000000000..8f2f41267e
--- /dev/null
+++ b/lib/compiler/test/compilation_SUITE_data/use_nifs.erl
@@ -0,0 +1,19 @@
+-module(use_nifs).
+-export([?MODULE/0,calculator_nif/0,id/1]).
+-nifs([calculator_nif/0]).
+
+?MODULE() ->
+    case id(false) of
+        true ->
+            erlang:load_nif("my_nif", 42),
+            calculator_nif();
+        false ->
+            ok
+    end,
+    ok.
+
+calculator_nif() ->
+    erlang:nif_error(undef).
+
+id(I) ->
+    I.
diff --git a/lib/compiler/test/compile_SUITE.erl b/lib/compiler/test/compile_SUITE.erl
index c5b6fa585a..2467c6bfe2 100644
--- a/lib/compiler/test/compile_SUITE.erl
+++ b/lib/compiler/test/compile_SUITE.erl
@@ -35,6 +35,7 @@
 	 cover/1, env/1, core_pp/1, tuple_calls/1,
 	 core_roundtrip/1, asm/1, asm_labels/1,
 	 sys_pre_attributes/1, dialyzer/1, no_core_prepare/1,
+         beam_ssa_pp_smoke_test/1,
 	 warnings/1, pre_load_check/1, env_compiler_options/1,
          bc_options/1, deterministic_include/1, deterministic_paths/1,
          deterministic_docs/1,
@@ -55,7 +56,8 @@ all() ->
      other_output, kernel_listing, encrypted_abstr, tuple_calls,
      strict_record, utf8_atoms, utf8_functions, extra_chunks,
      cover, env, core_pp, core_roundtrip, asm, asm_labels, no_core_prepare,
-     sys_pre_attributes, dialyzer, warnings, pre_load_check,
+     sys_pre_attributes, dialyzer, beam_ssa_pp_smoke_test,
+     warnings, pre_load_check,
      env_compiler_options, custom_debug_info, bc_options,
      custom_compile_info, deterministic_include, deterministic_paths,
      deterministic_docs,
@@ -1427,6 +1429,35 @@ dialyzer(Config) ->
     [{a,b,c}] = M:M(),
     ok.
 
+beam_ssa_pp_smoke_test(Config) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+    Outdir = filename:join(PrivDir, atom_to_list(?FUNCTION_NAME)),
+    ok = file:make_dir(Outdir),
+    TestBeams = get_unique_beam_files(),
+    test_lib:p_run(fun(F) -> beam_ssa_pp(F, Outdir) end, TestBeams).
+
+beam_ssa_pp(Beam, Outdir) ->
+    try
+	{ok,{Mod,[{abstract_code,{raw_abstract_v1,Abstr}}]}} =
+	    beam_lib:chunks(Beam, [abstract_code]),
+	beam_ssa_pp_1(Mod, Abstr, Outdir)
+    catch
+	throw:{error,Error} ->
+	    io:format("*** compilation failure '~p' for file ~s\n",
+		      [Error,Beam]),
+	    error;
+	Class:Error:Stk ->
+	    io:format("~p: ~p ~p\n~p\n", [Beam,Class,Error,Stk]),
+	    error
+    end.
+
+beam_ssa_pp_1(Mod, Abstr, Outdir) ->
+    Opts = test_lib:opt_opts(Mod),
+    {ok,Mod,SSA} = compile:forms(Abstr, [dssaopt|Opts]),
+    ListFile = filename:join(Outdir, atom_to_list(Mod) ++ ".ssaopt"),
+    {ok,Fd} = file:open(ListFile, [write,{encoding,utf8}]),
+    beam_listing:module(Fd, SSA),
+    ok = file:close(Fd).
 
 %% Test that warnings contain filenames and line numbers.
 warnings(_Config) ->
diff --git a/lib/compiler/test/guard_SUITE.erl b/lib/compiler/test/guard_SUITE.erl
index 143f320491..b9c616be0b 100644
--- a/lib/compiler/test/guard_SUITE.erl
+++ b/lib/compiler/test/guard_SUITE.erl
@@ -129,6 +129,8 @@ misc(Config) when is_list(Config) ->
     error = if abs(Zero > One) -> ok; true -> error end,
     ok = if is_integer(Zero) >= is_integer(One) -> ok end,
 
+    {'EXIT',{function_clause,_}} = catch misc_4(),
+
     ok.
 
 misc_1([{W},{X},{Y},{Z}]) ->
@@ -150,6 +152,9 @@ misc_3(LenUp, LenDw) ->
 	true -> false
     end.
 
+misc_4() when <<(is_atom((#{} #{ ok := ok })) orelse <<>>)/bytes>> >= ok ->
+    ok.
+
 get_data({o,Active,Raw}, BytesToRead, Buffer) 
   when Raw =:= raw; Raw =:= 0 ->
     if 
@@ -3143,6 +3148,18 @@ beam_ssa_bool_coverage() ->
     error = beam_ssa_bool_coverage_3(42),
     error = beam_ssa_bool_coverage_3(a),
 
+    error = beam_ssa_bool_coverage_4(42, 42),
+    error = beam_ssa_bool_coverage_4(ok, ok),
+    error = beam_ssa_bool_coverage_4(a, b),
+
+    ok = beam_ssa_bool_coverage_5(ok),
+    ok = beam_ssa_bool_coverage_5(2.0),
+    ok = beam_ssa_bool_coverage_5(42),
+
+    ok = beam_ssa_bool_coverage_6(<<>>),
+    error = beam_ssa_bool_coverage_6(a),
+    error = beam_ssa_bool_coverage_6(42),
+
     ok.
 
 collect_modifiers([H | T], Buffer)
@@ -3167,6 +3184,35 @@ beam_ssa_bool_coverage_3(A) when ok; ((ok =< A + 1) or false) and true orelse ok
 beam_ssa_bool_coverage_3(_) ->
     error.
 
+beam_ssa_bool_coverage_4(A, A) when ok == A andalso ok ->
+    ok;
+beam_ssa_bool_coverage_4(_, _) ->
+    error.
+
+beam_ssa_bool_coverage_5(A) ->
+    maybe
+        case case maybe ok end of
+                 2.0 ->
+                     false;
+                 A ->
+                     true;
+                 _ ->
+                     true
+             end of
+            true ->
+                ok;
+            _ ->
+                error
+        end
+    end.
+
+beam_ssa_bool_coverage_6(A) when is_bitstring(A) orelse ok;
+                                 is_bitstring(A) andalso ok bsr ok ->
+    ok;
+beam_ssa_bool_coverage_6(_) ->
+    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