File 2061-Do-not-merge-maps-when-they-are-the-same-or-empty.patch of Package erlang

From 97748b75b902deee852d92a50839778ec617820e Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@plataformatec.com.br>
Date: Tue, 29 Oct 2019 19:58:15 +0100
Subject: [PATCH] Do not merge maps when they are the same or empty

If merging two maps that are precisely the same
in memory or one of them is empty, we can avoid
the whole merge operation and simply return the
given map.

This can reduce memory allocation and CPU work for
algorithms that may be updating a map and merging
into a previous value. Or when providing defaults
which may be empty. The check is also very cheap,
which means the downsides are minimal.

The commit also adds coverage for a similar behaviour
already implemented for maps:put/3.
---
 erts/emulator/beam/erl_map.c   | 12 +++++++++++-
 lib/stdlib/test/maps_SUITE.erl | 26 ++++++++++++++++++++++++--
 2 files changed, 35 insertions(+), 3 deletions(-)

diff --git a/erts/emulator/beam/erl_map.c b/erts/emulator/beam/erl_map.c
index 62dd85e425..9097a36e62 100644
--- a/erts/emulator/beam/erl_map.c
+++ b/erts/emulator/beam/erl_map.c
@@ -973,7 +973,13 @@ BIF_RETTYPE maps_keys_1(BIF_ALIST_1) {
 HIPE_WRAPPER_BIF_DISABLE_GC(maps_merge, 2)
 
 BIF_RETTYPE maps_merge_2(BIF_ALIST_2) {
-    if (is_flatmap(BIF_ARG_1)) {
+    if (BIF_ARG_1 == BIF_ARG_2) {
+	/* Merging upon itself always returns itself */
+	if (is_map(BIF_ARG_1)) {
+	    return BIF_ARG_1;
+	}
+	BIF_P->fvalue = BIF_ARG_1;
+    } else if (is_flatmap(BIF_ARG_1)) {
 	if (is_flatmap(BIF_ARG_2)) {
 	    BIF_RET(flatmap_merge(BIF_P, BIF_ARG_1, BIF_ARG_2));
 	} else if (is_hashmap(BIF_ARG_2)) {
@@ -1008,6 +1014,9 @@ static Eterm flatmap_merge(Process *p, Eterm nodeA, Eterm nodeB) {
     n1   = flatmap_get_size(mp1);
     n2   = flatmap_get_size(mp2);
 
+    if (n1 == 0) return nodeB;
+    if (n2 == 0) return nodeA;
+
     need = MAP_HEADER_FLATMAP_SZ + 1 + 2 * (n1 + n2);
 
     hp     = HAlloc(p, need);
@@ -1127,6 +1136,7 @@ static Eterm map_merge_mixed(Process *p, Eterm flat, Eterm tree, int swap_args)
 
     mp = (flatmap_t*)flatmap_val(flat);
     n  = flatmap_get_size(mp);
+    if (n == 0) return tree;
 
     ks = flatmap_get_keys(mp);
     vs = flatmap_get_values(mp);
diff --git a/lib/stdlib/test/maps_SUITE.erl b/lib/stdlib/test/maps_SUITE.erl
index 6f3cd8bf1b..9853068478 100644
--- a/lib/stdlib/test/maps_SUITE.erl
+++ b/lib/stdlib/test/maps_SUITE.erl
@@ -37,6 +37,7 @@
 
 -export([t_get_3/1, t_filter_2/1,
          t_fold_3/1,t_map_2/1,t_size_1/1,
+         t_put_opt/1, t_merge_opt/1,
          t_with_2/1,t_without_2/1]).
 
 %-define(badmap(V,F,Args), {'EXIT', {{badmap,V}, [{maps,F,Args,_}|_]}}).
@@ -51,6 +52,7 @@ all() ->
 all() ->
     [t_get_3,t_filter_2,
      t_fold_3,t_map_2,t_size_1,
+     t_put_opt,t_merge_opt,
      t_with_2,t_without_2].
 
 init_per_suite(Config) ->
@@ -139,6 +141,27 @@ iter_kv(I) ->
     ?badarg(map,[<<>>,#{}]) = (catch maps:map(id(<<>>),#{})),
     ok.
 
+t_put_opt(Config) when is_list(Config) ->
+    Value = id(#{complex => map}),
+    Map = id(#{a => Value}),
+    true = erts_debug:same(maps:put(a, Value, Map), Map),
+    ok.
+
+t_merge_opt(Config) when is_list(Config) ->
+    Small = id(#{a => 1}),
+    true = erts_debug:same(maps:merge(#{}, Small), Small),
+    true = erts_debug:same(maps:merge(Small, #{}), Small),
+    true = erts_debug:same(maps:merge(Small, Small), Small),
+
+    Large = maps:from_list([{I,I}||I<-lists:seq(1,200)]),
+    true = erts_debug:same(maps:merge(#{}, Large), Large),
+    true = erts_debug:same(maps:merge(Large, #{}), Large),
+    true = erts_debug:same(maps:merge(Large, Large), Large),
+
+    List = id([a|b]),
+    ?badmap([a|b],merge,[[a|b],[a|b]]) = (catch maps:merge(List, List)),
+
+    ok.
 
 t_size_1(Config) when is_list(Config) ->
       0 = maps:size(#{}),
-- 
2.16.4

openSUSE Build Service is sponsored by