File 1171-Inline-safe-calls-to-maps-put-3.patch of Package erlang

From 39756ebdf76715bd04e861ff48e36c0bbb5598b2 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Wed, 29 May 2024 08:12:42 +0200
Subject: [PATCH] Inline safe calls to maps:put/3

Using the map syntax instead of `maps:put/3` is slightly more
efficient in itself, but also reduces register shuffling and can open
up for combining multiple adjacent map update operations into a single
update operation.
---
 lib/compiler/src/beam_ssa_type.erl  | 12 ++++++++
 system/doc/efficiency_guide/maps.md | 48 +++++++++++++++++++++++++++--
 2 files changed, 57 insertions(+), 3 deletions(-)

diff --git a/lib/compiler/src/beam_ssa_type.erl b/lib/compiler/src/beam_ssa_type.erl
index 9b4db89983..790d4ed364 100644
--- a/lib/compiler/src/beam_ssa_type.erl
+++ b/lib/compiler/src/beam_ssa_type.erl
@@ -1497,6 +1497,8 @@ will_succeed_1(#b_set{op=has_map_field}, _Src, _Ts) ->
     yes;
 will_succeed_1(#b_set{op=get_tuple_element}, _Src, _Ts) ->
     yes;
+will_succeed_1(#b_set{op=put_map,args=[#b_literal{val=assoc}|_]}, _Src, _Ts) ->
+    yes;
 will_succeed_1(#b_set{op=put_tuple}, _Src, _Ts) ->
     yes;
 will_succeed_1(#b_set{op=update_tuple,args=[Tuple | Updates]}, _Src, Ts) ->
@@ -1671,6 +1673,16 @@ simplify_remote_call(erlang, throw, [Term], Ts, I) ->
     beam_ssa:add_anno(thrown_type, Type, I);
 simplify_remote_call(erlang, '++', [#b_literal{val=[]},Tl], _Ts, _I) ->
     Tl;
+simplify_remote_call(maps=Mod, put=Name, [Key,Val,Map], Ts, I) ->
+    case concrete_type(Map, Ts) of
+        #t_map{} ->
+            %% This call to maps:put/3 cannot fail. Replace with the
+            %% slightly more efficient `put_map` instruction.
+            Args = [#b_literal{val=assoc},Map,Key,Val],
+            I#b_set{op=put_map,args=Args};
+        _ ->
+            simplify_pure_call(Mod, Name, [Key,Val,Map], I)
+    end;
 simplify_remote_call(Mod, Name, Args, _Ts, I) ->
     case erl_bifs:is_pure(Mod, Name, length(Args)) of
         true ->
diff --git a/system/doc/efficiency_guide/maps.md b/system/doc/efficiency_guide/maps.md
index 380f17760a..9613009970 100644
--- a/system/doc/efficiency_guide/maps.md
+++ b/system/doc/efficiency_guide/maps.md
@@ -459,9 +459,51 @@ constructing an empty map.
 If the key is known to already exist in the map, `maps:update/3` is slightly
 more efficient than `maps:put/3`.
 
-If the keys are constants known at compile-time, using the map update syntax
-with the `=>` operator is more efficient than multiple calls to `maps:put/3`,
-especially for small maps.
+If the compiler can determine that the third argument is always a map, it
+will rewrite the call to `maps:put/3` to use the map syntax for updating the map.
+
+For example, consider the following function:
+
+```erlang
+add_to_known_map(Map0, A, B, C) when is_map(Map0) ->
+    Map1 = maps:put(a, A, Map0),
+    Map2 = maps:put(b, B, Map1),
+    maps:put(c, C, Map2).
+```
+
+The compiler first rewrites each call to `maps:put/3` to use the map
+syntax, and subsequently combines the three update operations to a
+single update operation:
+
+```erlang
+add_to_known_map(Map0, A, B, C) when is_map(Map0) ->
+    Map0#{a => A, b => B, c => C}.
+```
+
+If the compiler cannot determine that the third argument is always a
+map, it retains the `maps:put/3` call. For example, given this
+function:
+
+```erlang
+add_to_map(Map0, A, B, C) ->
+    Map1 = maps:put(a, A, Map0),
+    Map2 = maps:put(b, B, Map1),
+    maps:put(c, C, Map2).
+```
+
+the compiler keeps the first call to `maps:put/3`, but rewrites
+and combines the other two calls:
+
+```erlang
+add_to_map(Map0, A, B, C) ->
+    Map1 = maps:put(a, A, Map0),
+    Map1#{b => B, c => C}.
+```
+
+> #### Change {: .info }
+>
+> The rewriting of `maps:put/3` to the map syntax was introduced in
+> Erlang/OTP 28.
 
 ### maps:remove/2
 
-- 
2.35.3

openSUSE Build Service is sponsored by