File 0215-Enhance-creation-of-maps-with-literal-keys.patch of Package erlang

From 68e89fb4f10696b8ec41b82cb962f4b285fffe99 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 26 Jul 2022 16:23:11 +0200
Subject: [PATCH 1/2] Enhance creation of maps with literal keys
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit

An optimization in the loader was added in: https://github.com/erlang/otp/pull/1498

When a small map is created where all keys are literals, the key tuple
is created as a literal. That means that the key tuple can be shared
for all instances of the map created by the same code.

However, that does not always work, for example for code such
as:

    decimal(Int) ->
        #{type => decimal, int => Int, exp => 0}.

The compiler would try to be smart and rewrite the code to:

    decimal(Int) ->
        (#{type => decimal, exp => 0})#{int => Int}.

Expressed in that way, the loader optimization cannot be applied and
a new key tuple will be created every time `decimal/1` is called.

This commit removes that problematic transformation. The implementation
is based on José Valim's suggested implementation.

Fixes #6139
---
 lib/compiler/src/cerl.erl       | 41 +++++++++++++++++++--------------
 lib/compiler/test/map_SUITE.erl | 25 ++++++++++++++++++--
 2 files changed, 47 insertions(+), 19 deletions(-)

diff --git a/lib/compiler/src/cerl.erl b/lib/compiler/src/cerl.erl
index bc28f58712..99651ebc2f 100644
--- a/lib/compiler/src/cerl.erl
+++ b/lib/compiler/src/cerl.erl
@@ -1647,34 +1647,41 @@ ann_c_map(As, Es) ->
 
 -spec ann_c_map([term()], c_map() | c_literal(), [c_map_pair()]) -> c_map() | c_literal().
 
-ann_c_map(As,#c_literal{val=M},Es) when is_map(M) ->
-    fold_map_pairs(As,Es,M);
-ann_c_map(As,M,Es) ->
-    #c_map{arg=M, es=Es, anno=As }.
-
-fold_map_pairs(As,[],M) -> #c_literal{anno=As,val=M};
-%% M#{ K => V}
-fold_map_pairs(As,[#c_map_pair{op=#c_literal{val=assoc},key=Ck,val=Cv}=E|Es],M) ->
+ann_c_map(As, #c_literal{val=M0}=Lit, Es) when is_map(M0) ->
+    case update_map_literal(Es, M0) of
+        none ->
+            #c_map{arg=Lit, es=Es, anno=As};
+        M1 ->
+            #c_literal{anno=As, val=M1}
+    end;
+ann_c_map(As, M, Es) ->
+    #c_map{arg=M, es=Es, anno=As}.
+
+update_map_literal([#c_map_pair{op=#c_literal{val=assoc},key=Ck,val=Cv}|Es], M) ->
+    %% M#{K => V}
     case is_lit_list([Ck,Cv]) of
 	true ->
 	    [K,V] = lit_list_vals([Ck,Cv]),
-	    fold_map_pairs(As,Es,maps:put(K,V,M));
+	    update_map_literal(Es, M#{K => V});
 	false ->
-	    #c_map{arg=#c_literal{val=M,anno=As}, es=[E|Es], anno=As }
+	    none
     end;
-%% M#{ K := V}
-fold_map_pairs(As,[#c_map_pair{op=#c_literal{val=exact},key=Ck,val=Cv}=E|Es],M) ->
+update_map_literal([#c_map_pair{op=#c_literal{val=exact},key=Ck,val=Cv}|Es], M) ->
+    %% M#{K := V}
     case is_lit_list([Ck,Cv]) of
 	true ->
 	    [K,V] = lit_list_vals([Ck,Cv]),
-	    case maps:is_key(K,M) of
-		true -> fold_map_pairs(As,Es,maps:put(K,V,M));
+	    case is_map_key(K, M) of
+		true ->
+                    update_map_literal(Es, M#{K => V});
 		false ->
-		    #c_map{arg=#c_literal{val=M,anno=As}, es=[E|Es], anno=As }
+		    none
 	    end;
 	false ->
-	    #c_map{arg=#c_literal{val=M,anno=As}, es=[E|Es], anno=As }
-    end.
+            none
+    end;
+update_map_literal([], M) ->
+    M.
 
 -spec update_c_map(c_map(), cerl(), [cerl()]) -> c_map() | c_literal().
 
diff --git a/lib/compiler/test/map_SUITE.erl b/lib/compiler/test/map_SUITE.erl
index 4db5b01109..8716d85477 100644
--- a/lib/compiler/test/map_SUITE.erl
+++ b/lib/compiler/test/map_SUITE.erl
@@ -87,7 +87,8 @@
 
          %% miscellaneous
          t_conflicting_destinations/1,
-         t_cse_assoc/1
+         t_cse_assoc/1,
+         shared_key_tuples/1
         ]).
 
 -define(badmap(V, F, Args), {'EXIT', {{badmap,V}, [{maps,F,Args,_}|_]}}).
@@ -161,7 +162,8 @@ all() ->
 
      %% miscellaneous
      t_conflicting_destinations,
-     t_cse_assoc
+     t_cse_assoc,
+     shared_key_tuples
     ].
 
 groups() -> [].
@@ -2546,6 +2548,25 @@ do_cse_assoc(M, V) ->
             Assoc
     end.
 
+shared_key_tuples(_Config) ->
+    A = decimal(0),
+    B = decimal(1),
+
+    case ?MODULE of
+        map_inline_SUITE ->
+            %% With inlining, two separate map literals will be created. They
+            %% will not share keys.
+            ok;
+        _ ->
+            %% The two instances should share the key tuple.
+            true = erts_debug:same(erts_internal:map_to_tuple_keys(A),
+                                   erts_internal:map_to_tuple_keys(B))
+    end,
+    ok.
+
+decimal(Int) ->
+    #{type => decimal, int => Int, exp => 0}.
+
 %% aux
 
 rand_terms(0) -> [];
-- 
2.35.3

openSUSE Build Service is sponsored by