File 3442-Correct-unsafe-optimization-of-binary-matching.patch of Package erlang

From 39f97eefb6f9ec801f3ce87cbd30b42eedbcc1c0 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Sun, 26 Feb 2023 17:43:23 +0100
Subject: [PATCH] Correct unsafe optimization of binary matching

When compiling generated code from forms where the line numbers in the
annotations did not correspond to the actual order of the clauses, the
compiler could rearrange clauses even when it was not safe. For
example:

    match_route([<<"prefix">>, <<"action">>]) -> first;  %Line 4
    match_route([<<"prefix">>, _Ignore]) -> second.      %Line 2

The compiler would rearrange that to:

    match_route([<<"prefix">>, _Ignore]) -> second;      %Line 2
    match_route([<<"prefix">>, <<"action">>]) -> first.  %Line 4

which would make the second clause (former first clause) unreachable.

This bug was introduced in cadd19e84478ed (#6538).

Closes #6923
---
 lib/compiler/src/v3_kernel.erl       | 30 +++++++++++++---
 lib/compiler/test/bs_match_SUITE.erl | 53 ++++++++++++++++++++++++++--
 2 files changed, 76 insertions(+), 7 deletions(-)

diff --git a/lib/compiler/src/v3_kernel.erl b/lib/compiler/src/v3_kernel.erl
index f734e07350..3443f43959 100644
--- a/lib/compiler/src/v3_kernel.erl
+++ b/lib/compiler/src/v3_kernel.erl
@@ -1438,11 +1438,29 @@ reorder_bin_ints([_]=Cs) ->
     Cs;
 reorder_bin_ints(Cs0) ->
     %% It is safe to reorder clauses that matches binaries if the
-    %% first segments for all of them match the same number of bits.
-    Cs = sort([{reorder_bin_int_sort_key(C),C} || C <- Cs0]),
-    [C || {_,C} <- Cs].
+    %% first segments for all of them match the same number of bits
+    %% and if the patterns that follow are also safe to re-order.
+    try
+        Cs = sort([{reorder_bin_int_sort_key(C),C} || C <- Cs0]),
+        [C || {_,C} <- Cs]
+    catch
+        throw:not_possible ->
+            Cs0
+    end.
 
-reorder_bin_int_sort_key(#iclause{pats=[Pats|_]}) ->
+reorder_bin_int_sort_key(#iclause{pats=[Pats|More],guard=#c_literal{val=true}}) ->
+    case all(fun(#k_var{}) -> true;
+                (_) -> false
+             end, More) of
+        true ->
+            %% Only variables. Safe to re-order.
+            ok;
+        false ->
+            %% Not safe to re-order. For example:
+            %%    f([<<"prefix">>, <<"action">>]) -> ...
+            %%    f([<<"prefix">>, Variable]) -> ...
+            throw(not_possible)
+    end,
     case Pats of
         #k_bin_int{val=Val,next=#k_bin_end{}} ->
             %% Sort before clauses with additional segments. This usually results in
@@ -1450,7 +1468,9 @@ reorder_bin_int_sort_key(#iclause{pats=[Pats|_]}) ->
             [Val];
         #k_bin_int{val=Val} ->
             [Val,more]
-    end.
+    end;
+reorder_bin_int_sort_key(#iclause{}) ->
+    throw(not_possible).
 
 %% match_value([Var], Con, [Clause], Default, State) -> {SelectExpr,State}.
 %%  At this point all the clauses have the same constructor, we must
diff --git a/lib/compiler/test/bs_match_SUITE.erl b/lib/compiler/test/bs_match_SUITE.erl
index 853d434c52..1c379b70cf 100644
--- a/lib/compiler/test/bs_match_SUITE.erl
+++ b/lib/compiler/test/bs_match_SUITE.erl
@@ -50,6 +50,7 @@
          bs_saved_position_units/1,empty_matches/1,
          trim_bs_start_match_resume/1,
          gh_6410/1,
+         gh_6923/1,
          otp_19019/1]).
 
 -export([coverage_id/1,coverage_external_ignore/2]).
@@ -91,6 +92,7 @@ groups() ->
        bs_saved_position_units,empty_matches,
        trim_bs_start_match_resume,
        gh_6410,
+       gh_6923,
        otp_19019]}].
 
 init_per_suite(Config) ->
@@ -2670,6 +2672,54 @@ do_gh_6410(X) ->
             X
     end).
 
+gh_6923(_Config) ->
+    Mod = list_to_atom(?MODULE_STRING ++ "_" ++ atom_to_list(?FUNCTION_NAME)),
+
+    %% The second clause of match_route/1 has lower line numbers than
+    %% the first clause.
+    %%
+    %% -module(bs_match_SUITE_gh_6923).                     %Line 29
+    %% -export([match_route/1]).                            %Line 29
+    %% match_route([<<"prefix">>, <<"action">>]) -> first;  %Line 4
+    %% match_route([<<"prefix">>, _Ignore]) -> second.      %Line 2
+    Forms =
+        [{attribute,29,module,Mod},
+         {attribute,29,export,[{match_route,1}]},
+         {function,4,match_route,1,
+          [{clause,4,
+            [{cons,4,
+              {bin,4,[{bin_element,4,{string,4,"prefix"},default,default}]},
+              {cons,4,
+               {bin,4,
+                [{bin_element,4,
+                  {string,4,"action"},
+                  default,default}]},
+               {nil,4}}}],
+            [],
+            [{atom,4,first}]},
+           {clause,2,
+            [{cons,2,
+              {bin,2,[{bin_element,2,{string,2,"prefix"},default,default}]},
+              {cons,2,{var,2,'_Ignore'},{nil,2}}}],
+            [],
+            [{atom,2,second}]}]}],
+    Opts = test_lib:opt_opts(?MODULE),
+    {ok, Mod, Beam} = compile:forms(Forms, Opts),
+    {module, Mod} = code:load_binary(Mod, "", Beam),
+    first = Mod:match_route([<<"prefix">>, <<"action">>]),
+    second = Mod:match_route([<<"prefix">>, whatever]),
+    _ = code:delete(Mod),
+    _ = code:purge(Mod),
+
+    %% For coverage.
+    first = do_gh_6923([id(<<"abc">>), id(42)]),
+    second = do_gh_6923([id(<<"abc">>), id({a,b,c})]),
+
+    ok.
+
+do_gh_6923([<<"abc">>, A]) when is_integer(A) -> first;
+do_gh_6923([<<"abc">>, A]) when is_tuple(A) -> second.
+
 otp_19019(_Config) ->
     ok = do_otp_19019(id(<<42>>)),
     <<>> = do_otp_19019(id(<<>>)),
-- 
2.35.3

openSUSE Build Service is sponsored by