File 2853-Fix-exponential-time-algorithm.patch of Package erlang

From 7d79897d1f1424aaf97802869ae5298a1aa1703d Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Wed, 26 Apr 2023 15:45:09 +0200
Subject: [PATCH] Fix exponential time algorithm

The function `beam_ssa_bool:covered/1` ran in exponential time.

The new implementation does not always produce the same list of
covered vertices, but the same code is generated for every module
compiled by `scripts/diffable`.

Closes #7338
---
 lib/compiler/src/beam_ssa_bool.erl | 41 ++++++++++++++--------------
 lib/compiler/test/andor_SUITE.erl  | 43 ++++++++++++++++++++++++++++--
 2 files changed, 61 insertions(+), 23 deletions(-)

diff --git a/lib/compiler/src/beam_ssa_bool.erl b/lib/compiler/src/beam_ssa_bool.erl
index 7ad38dc3ca..4c25769478 100644
--- a/lib/compiler/src/beam_ssa_bool.erl
+++ b/lib/compiler/src/beam_ssa_bool.erl
@@ -1631,35 +1631,34 @@ del_out_edges(V, G) ->
     beam_digraph:del_edges(G, beam_digraph:out_edges(G, V)).
 
 covered(From, To, G) ->
-    Seen0 = sets:new([{version, 2}]),
+    Seen0 = #{},
     {yes,Seen} = covered_1(From, To, G, Seen0),
-    sets:to_list(Seen).
+    [V || {V,reached} <- maps:to_list(Seen)].
 
 covered_1(To, To, _G, Seen) ->
     {yes,Seen};
-covered_1(From, To, G, Seen0) ->
-    Vs0 = beam_digraph:out_neighbours(G, From),
-    Vs = [V || V <- Vs0, not sets:is_element(V, Seen0)],
-    Seen = sets:union(sets:from_list(Vs, [{version, 2}]), Seen0),
-    case Vs of
-        [] ->
-            no;
-        [_|_] ->
-            covered_list(Vs, To, G, Seen, false)
-    end.
+covered_1(From, To, G, Seen) ->
+    Vs = beam_digraph:out_neighbours(G, From),
+    covered_list(Vs, To, G, Seen, no).
 
 covered_list([V|Vs], To, G, Seen0, AnyFound) ->
-    case covered_1(V, To, G, Seen0) of
-        {yes,Seen} ->
-            covered_list(Vs, To, G, Seen, true);
-        no ->
-            covered_list(Vs, To, G, Seen0, AnyFound)
+    case Seen0 of
+        #{V := reached} ->
+            covered_list(Vs, To, G, Seen0, yes);
+        #{V := not_reached} ->
+            covered_list(Vs, To, G, Seen0, AnyFound);
+        #{} ->
+            case covered_1(V, To, G, Seen0) of
+                {yes,Seen1} ->
+                    Seen = Seen1#{V => reached},
+                    covered_list(Vs, To, G, Seen, yes);
+                {no,Seen1} ->
+                    Seen = Seen1#{V => not_reached},
+                    covered_list(Vs, To, G, Seen, AnyFound)
+            end
     end;
 covered_list([], _, _, Seen, AnyFound) ->
-    case AnyFound of
-        true -> {yes,Seen};
-        false -> no
-    end.
+    {AnyFound,Seen}.
 
 digraph_roots(G) ->
     digraph_roots_1(beam_digraph:vertices(G), G).
diff --git a/lib/compiler/test/andor_SUITE.erl b/lib/compiler/test/andor_SUITE.erl
index 250f2c5803..22cf4a2cb8 100644
--- a/lib/compiler/test/andor_SUITE.erl
+++ b/lib/compiler/test/andor_SUITE.erl
@@ -486,11 +486,25 @@ in_case_1_guard(LenUp, LenDw, LenN, Rotation, Count) ->
     end.
 
 -record(state, {stack = []}).
+-record(conf, {e1=[], e2=[], e3=[], e4=[], e5=[], e6=[]}).
 
 slow_compilation(_) ->
-    %% The function slow_compilation_1 used to compile very slowly.
-    ok = slow_compilation_1({a}, #state{}).
+    ok = slow_compilation_1({a}, #state{}),
 
+    {'EXIT', {function_clause,_}} = catch slow_compilation_2(#{}),
+    {'EXIT', {function_clause,_}} = catch slow_compilation_2(true),
+
+    true = #conf{} =:= slow_compilation_3(#conf{}, #conf{}),
+    #conf{e1=a, e2=[], e3=[], e4=[], e5=[], e6=[]} =
+        slow_compilation_3(#conf{e1=a}, #conf{}),
+    #conf{e1=[], e2=[], e3=c, e4=[], e5=[], e6=[]} =
+        slow_compilation_3(#conf{e3=c}, #conf{}),
+    #conf{e1=[], e2=[], e3=[], e4=[], e5=[], e6=f} =
+        slow_compilation_3(#conf{e6=f}, #conf{}),
+
+    ok.
+
+%% This function used to compile very slowly.
 slow_compilation_1(T1, #state{stack = [T2|_]})
     when element(1, T2) == a, element(1, T1) == b, element(1, T1) == c ->
     ok;
@@ -514,6 +528,31 @@ slow_compilation_1(_, T) when element(1, T) == b ->
 slow_compilation_1(T, _) when element(1, T) == a ->
     ok.
 
+%% The following function used to compile really slowly (about one and
+%% a half minutes on my computer). The culprit was
+%% beam_ssa_bool:covered/1. (Thanks to Robin Morisset and erlfuzz.)
+slow_compilation_2(X)
+  when X or is_function(ok, ok);
+       X#{ok := ok}#{ok := ok}#{ok := ok}#{ok := ok}#{ok := ok}#{ok := ok}
+       #{ok := ok}#{ok := ok}#{ok := ok}#{ok := ok}#{ok := ok}#{ok := ok}
+       #{ok := ok}#{ok := ok}#{ok := ok}#{ok := ok}#{ok := ok}#{ok := ok}
+       #{ok := ok}#{ok := ok}#{ok := ok}#{ok := ok}#{ok := ok}#{ok := ok}
+       #{ok := ok} ->
+    ok.
+
+%% GH-7338. Very slow compilation time (the culprit was beam_ssa_bool:covered/1).
+slow_compilation_3(Old, New) ->
+    if Old#conf.e1 =/= New#conf.e1;
+       Old#conf.e2 =/= New#conf.e2;
+       Old#conf.e3 =/= New#conf.e3;
+       Old#conf.e4 =/= New#conf.e4;
+       Old#conf.e5 =/= New#conf.e5;
+       Old#conf.e6 =/= New#conf.e6 ->
+	    Old;
+       true ->
+	    New
+    end.
+
 %% Utilities.
 
 echo(X) ->	    
-- 
2.35.3

openSUSE Build Service is sponsored by