File 0136-Cover-code-in-beam_ssa_dead.patch of Package erlang

From 89f37d9ba5925e3bb570c15560d59ad2be8f1d19 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 29 Nov 2018 13:31:40 +0100
Subject: [PATCH 6/7] Cover code in beam_ssa_dead

---
 lib/compiler/test/guard_SUITE.erl | 52 +++++++++++++++++++++++++++++++++++++++
 lib/compiler/test/match_SUITE.erl | 26 +++++++++++++++++++-
 2 files changed, 77 insertions(+), 1 deletion(-)

diff --git a/lib/compiler/test/guard_SUITE.erl b/lib/compiler/test/guard_SUITE.erl
index 1c05129dc4..ed0a56f064 100644
--- a/lib/compiler/test/guard_SUITE.erl
+++ b/lib/compiler/test/guard_SUITE.erl
@@ -1295,6 +1295,32 @@ rel_ops(Config) when is_list(Config) ->
     Empty = id([]),
     ?T(==, [], Empty),
 
+    %% Cover beam_ssa_dead:turn_op('/=').
+    ok = (fun(A, B) when is_atom(A) ->
+                  X = id(A /= B),
+                  if
+                      X -> ok;
+                      true -> error
+                  end
+          end)(a, b),
+    ok = (fun(A, B) when is_atom(A) ->
+                  X = id(B /= A),
+                  if
+                        X -> ok;
+                        true -> error
+                    end
+            end)(a, b),
+
+    %% Cover beam_ssa_dead.
+    Arrow = fun([T1,T2]) when T1 == $>, T2 == $>;
+                              T1 == $<, T2 == $| ->  true;
+               (_) -> false
+            end,
+    true = Arrow(">>"),
+    true = Arrow("<|"),
+    false = Arrow("><"),
+    false = Arrow(""),
+
     ok.
 
 -undef(TestOp).
@@ -1328,6 +1354,9 @@ rel_op_combinations_1(N, Digits) ->
     Bool = is_digit_6(N),
     Bool = is_digit_7(N),
     Bool = is_digit_8(N),
+    Bool = is_digit_9(42, N),
+    Bool = is_digit_10(N, 0),
+    Bool = is_digit_11(N, 0),
     rel_op_combinations_1(N-1, Digits).
 
 is_digit_1(X) when 16#0660 =< X, X =< 16#0669 -> true;
@@ -1371,6 +1400,24 @@ is_digit_8(X) when X =< 16#0669, X > (16#0660-1) -> true;
 is_digit_8(16#0670) -> false;
 is_digit_8(_) -> false.
 
+is_digit_9(A, 0) when A =:= 42 -> false;
+is_digit_9(_, X) when X > 16#065F, X < 16#066A -> true;
+is_digit_9(_, X) when 16#0030 =< X, X =< 16#0039 -> true;
+is_digit_9(_, X) when 16#06F0 =< X, X =< 16#06F9 -> true;
+is_digit_9(_, _) -> false.
+
+is_digit_10(0, 0) -> false;
+is_digit_10(X, _) when X < 16#066A, 16#0660 =< X -> true;
+is_digit_10(X, _) when 16#0030 =< X, X =< 16#0039 -> true;
+is_digit_10(X, _) when 16#06F0 =< X, X =< 16#06F9 -> true;
+is_digit_10(_, _) -> false.
+
+is_digit_11(0, 0) -> false;
+is_digit_11(X, _) when X =< 16#0669, 16#0660 =< X -> true;
+is_digit_11(X, _) when 16#0030 =< X, X =< 16#0039 -> true;
+is_digit_11(X, _) when 16#06F0 =< X, X =< 16#06F9 -> true;
+is_digit_11(_, _) -> false.
+
 rel_op_combinations_2(0, _) ->
     ok;
 rel_op_combinations_2(N, Range) ->
@@ -1471,6 +1518,7 @@ rel_op_combinations_3(N, Red) ->
     Val = redundant_9(N),
     Val = redundant_10(N),
     Val = redundant_11(N),
+    Val = redundant_11(N),
     rel_op_combinations_3(N-1, Red).
 
 redundant_1(X) when X >= 51, X =< 80 -> 5*X;
@@ -1525,6 +1573,10 @@ redundant_11(X) when X =:= 10 -> 2*X;
 redundant_11(X) when X >= 51, X =< 80 -> 5*X;
 redundant_11(_) -> none.
 
+redundant_12(X) when X >= 50, X =< 80 -> 2*X;
+redundant_12(X) when X < 51 -> 5*X;
+redundant_12(_) -> none.
+
 %% Test type tests on literal values. (From emulator test suites.)
 literal_type_tests(Config) when is_list(Config) ->
     case ?MODULE of
diff --git a/lib/compiler/test/match_SUITE.erl b/lib/compiler/test/match_SUITE.erl
index eed2a31f70..10527775f4 100644
--- a/lib/compiler/test/match_SUITE.erl
+++ b/lib/compiler/test/match_SUITE.erl
@@ -641,13 +641,22 @@ do_map_vars_used(X, Y, Map) ->
 	    Val
     end.
 
+-record(coverage_id, {bool=false,id}).
 coverage(Config) when is_list(Config) ->
     %% Cover beam_dead.
     ok = coverage_1(x, a),
     ok = coverage_1(x, b),
 
     %% Cover sys_pre_expand.
-    ok = coverage_3("abc").
+    ok = coverage_3("abc"),
+
+    %% Cover beam_ssa_dead.
+    {expr,key} = coverage_4([literal,get], [[expr,key]]),
+    {expr,key} = coverage_4([expr,key], []),
+    a = coverage_5([8,8,8], #coverage_id{bool=true}),
+    b = coverage_5([], #coverage_id{bool=true}),
+
+    ok.
 
 coverage_1(B, Tag) ->
     case Tag of
@@ -660,6 +669,21 @@ coverage_2(2, b, x) -> ok.
 
 coverage_3([$a]++[]++"bc") -> ok.
 
+%% Cover beam_ssa_dead:eval_type_test_1(is_nonempty_list, Arg).
+coverage_4([literal,get], [Expr]) ->
+    coverage_4(Expr, []);
+coverage_4([Expr,Key], []) ->
+    {Expr,Key}.
+
+%% Cover beam_ssa_dead:eval_type_test_1(is_tagged_tuple, Arg).
+coverage_5(Config, TermId)
+  when TermId =:= #coverage_id{bool=true},
+       Config =:= [8,8,8] ->
+    a;
+coverage_5(_Config, #coverage_id{bool=true}) ->
+    b.
+
+
 grab_bag(_Config) ->
     [_|T] = id([a,b,c]),
     [b,c] = id(T),
-- 
2.16.4

openSUSE Build Service is sponsored by