File 2831-Add-maps-from_keys-2-BIF.patch of Package erlang

From c7baedef43bb677646e77fc7f518107249f71f7d Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@dashbit.co>
Date: Tue, 1 Dec 2020 10:02:35 +0100
Subject: [PATCH] Add maps:from_keys/2 BIF

It creates a new map from a set of keys and a
single value. This function can be used to
to optimize sets operations such as from_list/1,
filter/2, intersection/2, and subtract/2.
---
 erts/emulator/beam/bif.tab           |  1 +
 erts/emulator/beam/erl_map.c         | 88 +++++++++++++++++++++-------
 lib/compiler/src/beam_call_types.erl |  4 ++
 lib/dialyzer/src/erl_bif_types.erl   | 10 ++++
 lib/stdlib/doc/src/maps.xml          | 14 +++++
 lib/stdlib/src/maps.erl              | 10 +++-
 lib/stdlib/test/maps_SUITE.erl       | 20 ++++++-
 7 files changed, 124 insertions(+), 23 deletions(-)

diff --git a/erts/emulator/beam/bif.tab b/erts/emulator/beam/bif.tab
index 998abd3d0e..32ff995b9e 100644
--- a/erts/emulator/beam/bif.tab
+++ b/erts/emulator/beam/bif.tab
@@ -770,3 +770,9 @@
 #
 
 bif erts_internal:get_creation/0
+
+#
+# New in 24
+#
+
+bif maps:from_keys/2
diff --git a/erts/emulator/beam/erl_map.c b/erts/emulator/beam/erl_map.c
index b8c7337bf4..e1650b9356 100644
--- a/erts/emulator/beam/erl_map.c
+++ b/erts/emulator/beam/erl_map.c
@@ -94,8 +94,8 @@ static Uint hashmap_subtree_size(Eterm node);
 static Eterm hashmap_keys(Process *p, Eterm map);
 static Eterm hashmap_values(Process *p, Eterm map);
 static Eterm hashmap_delete(Process *p, Uint32 hx, Eterm key, Eterm node, Eterm *value);
-static Eterm flatmap_from_validated_list(Process *p, Eterm list, Uint size);
-static Eterm hashmap_from_validated_list(Process *p, Eterm list, Uint size);
+static Eterm flatmap_from_validated_list(Process *p, Eterm list, Eterm fill_value, Uint size);
+static Eterm hashmap_from_validated_list(Process *p, Eterm list, Eterm fill_value, Uint size);
 static Eterm hashmap_from_unsorted_array(ErtsHeapFactory*, hxnode_t *hxns, Uint n, int reject_dupkeys);
 static Eterm hashmap_from_sorted_unique_array(ErtsHeapFactory*, hxnode_t *hxns, Uint n, int is_root);
 static Eterm hashmap_from_chunked_array(ErtsHeapFactory*, hxnode_t *hxns, Uint n, Uint size, int is_root);
@@ -232,6 +232,35 @@ BIF_RETTYPE map_get_2(BIF_ALIST_2) {
     BIF_RET(maps_get_2(BIF_CALL_ARGS));
 }
 
+/* maps:from_keys/2
+ * List may be unsorted
+ */
+
+BIF_RETTYPE maps_from_keys_2(BIF_ALIST_2) {
+    Eterm item = BIF_ARG_1;
+    Uint  size = 0;
+    if (is_list(item) || is_nil(item)) {
+        /* Calculate size and check validity */
+        while(is_list(item)) {
+            size++;
+            item = CDR(list_val(item));
+        }
+
+        if (is_not_nil(item))
+            goto error;
+
+        if (size > MAP_SMALL_MAP_LIMIT) {
+            BIF_RET(hashmap_from_validated_list(BIF_P, BIF_ARG_1, BIF_ARG_2, size));
+        } else {
+            BIF_RET(flatmap_from_validated_list(BIF_P, BIF_ARG_1, BIF_ARG_2, size));
+        }
+    }
+
+error:
+
+    BIF_ERROR(BIF_P, BADARG);
+}
+
 /* maps:from_list/1
  * List may be unsorted [{K,V}]
  */
@@ -260,9 +289,9 @@ BIF_RETTYPE maps_from_list_1(BIF_ALIST_1) {
 	    goto error;
 
 	if (size > MAP_SMALL_MAP_LIMIT) {
-	    BIF_RET(hashmap_from_validated_list(BIF_P, BIF_ARG_1, size));
+	    BIF_RET(hashmap_from_validated_list(BIF_P, BIF_ARG_1, THE_NON_VALUE, size));
 	} else {
-	    BIF_RET(flatmap_from_validated_list(BIF_P, BIF_ARG_1, size));
+	    BIF_RET(flatmap_from_validated_list(BIF_P, BIF_ARG_1, THE_NON_VALUE, size));
 	}
     }
 
@@ -271,9 +300,9 @@ error:
     BIF_ERROR(BIF_P, BADARG);
 }
 
-static Eterm flatmap_from_validated_list(Process *p, Eterm list, Uint size) {
+static Eterm flatmap_from_validated_list(Process *p, Eterm list, Eterm fill_value, Uint size) {
     Eterm *kv, item = list;
-    Eterm *hp, *thp,*vs, *ks, keys, res;
+    Eterm *hp, *thp,*vs, *ks, key, value, keys, res;
     flatmap_t *mp;
     Uint  unused_size = 0;
     Sint  c = 0;
@@ -299,16 +328,27 @@ static Eterm flatmap_from_validated_list(Process *p, Eterm list, Uint size) {
 	return res;
 
     /* first entry */
-    kv    = tuple_val(CAR(list_val(item)));
-    ks[0] = kv[1];
-    vs[0] = kv[2];
+    if (is_value(fill_value)) {
+	ks[0] = CAR(list_val(item));
+	vs[0] = fill_value;
+    } else {
+	kv    = tuple_val(CAR(list_val(item)));
+	ks[0] = kv[1];
+	vs[0] = kv[2];
+    }
     size  = 1;
     item  = CDR(list_val(item));
 
     /* insert sort key/value pairs */
     while(is_list(item)) {
-
-	kv = tuple_val(CAR(list_val(item)));
+	if (is_value(fill_value)) {
+	    key = CAR(list_val(item));
+	    value = fill_value;
+	} else {
+	    kv = tuple_val(CAR(list_val(item)));
+	    key = kv[1];
+	    value = kv[2];
+	}
 
 	/* compare ks backwards
 	 * idx represent word index to be written (hole position).
@@ -323,15 +363,15 @@ static Eterm flatmap_from_validated_list(Process *p, Eterm list, Uint size) {
 
 	idx = size;
 
-	while(idx > 0 && (c = CMP_TERM(kv[1],ks[idx-1])) < 0) { idx--; }
+	while(idx > 0 && (c = CMP_TERM(key,ks[idx-1])) < 0) { idx--; }
 
 	if (c == 0) {
 	    /* last compare was equal,
 	     * i.e. we have to release memory
 	     * and overwrite that key/value
 	     */
-	    ks[idx-1] = kv[1];
-	    vs[idx-1] = kv[2];
+	    ks[idx-1] = key;
+	    vs[idx-1] = value;
 	    unused_size++;
 	} else {
 	    Uint i = size;
@@ -340,8 +380,8 @@ static Eterm flatmap_from_validated_list(Process *p, Eterm list, Uint size) {
 		vs[i] = vs[i-1];
 		i--;
 	    }
-	    ks[idx] = kv[1];
-	    vs[idx] = kv[2];
+	    ks[idx] = key;
+	    vs[idx] = value;
 	    size++;
 	}
 	item = CDR(list_val(item));
@@ -373,10 +413,11 @@ static Eterm flatmap_from_validated_list(Process *p, Eterm list, Uint size) {
 #define maskval(V,L)      (((V) >> ((7 - (L))*4)) & 0xf)
 #define cdepth(V1,V2)     (hashmap_clz((V1) ^ (V2)) >> 2)
 
-static Eterm hashmap_from_validated_list(Process *p, Eterm list, Uint size) {
+static Eterm hashmap_from_validated_list(Process *p, Eterm list, Eterm fill_value, Uint size) {
     Eterm item = list;
     Eterm *hp;
     Eterm *kv, res;
+    Eterm key, value;
     Uint32 sw, hx;
     Uint ix = 0;
     hxnode_t *hxns;
@@ -392,11 +433,18 @@ static Eterm hashmap_from_validated_list(Process *p, Eterm list, Uint size) {
     UseTmpHeap(2,p);
     while(is_list(item)) {
 	res = CAR(list_val(item));
-	kv  = tuple_val(res);
-	hx  = hashmap_restore_hash(tmp,0,kv[1]);
+	if(is_value(fill_value)) {
+	    key = res;
+	    value = fill_value;
+	} else {
+	    kv = tuple_val(res);
+	    key = kv[1];
+	    value = kv[2];
+	}
+	hx  = hashmap_restore_hash(tmp,0,key);
 	swizzle32(sw,hx);
 	hxns[ix].hx   = sw;
-	hxns[ix].val  = CONS(hp, kv[1], kv[2]); hp += 2;
+	hxns[ix].val  = CONS(hp, key, value); hp += 2;
 	hxns[ix].skip = 1; /* will be reassigned in from_array */
 	hxns[ix].i    = ix;
 	ix++;
diff --git a/lib/compiler/src/beam_call_types.erl b/lib/compiler/src/beam_call_types.erl
index 7433d02940..c38bf806c3 100644
--- a/lib/compiler/src/beam_call_types.erl
+++ b/lib/compiler/src/beam_call_types.erl
@@ -566,6 +566,10 @@ types(maps, fold, [Fun, Init, _Map]) ->
                       any
               end,
     sub_unsafe(RetType, [#t_fun{arity=3}, any, #t_map{}]);
+types(maps, from_keys, [Keys, Value]) ->
+    RetType = #t_map{super_key=erlang_hd_type(Keys),
+                     super_value=Value},
+    sub_unsafe(RetType, [proper_list(), any]);
 types(maps, from_list, [Pairs]) ->
     PairType = erlang_hd_type(Pairs),
     RetType = case beam_types:normalize(PairType) of
diff --git a/lib/stdlib/doc/src/maps.xml b/lib/stdlib/doc/src/maps.xml
index aba390af7f..ed82f70618 100644
--- a/lib/stdlib/doc/src/maps.xml
+++ b/lib/stdlib/doc/src/maps.xml
@@ -115,6 +115,20 @@
       </desc>
     </func>
 
+    <func>
+      <name name="from_keys" arity="2" since="OTP 14.0"/>
+      <fsummary></fsummary>
+      <desc>
+        <p>Takes a list of keys and a value and builds a map where all keys
+          point to the same value. The key can be in any order, and keys
+          and value can be of any term.</p>
+        <p><em>Example:</em></p>
+        <code type="none">
+> Keys = ["a", "b", "c"], maps:from_keys(Keys, ok).
+#{"a" => ok,"b" => ok,"c" => ok}</code>
+      </desc>
+    </func>
+
     <func>
       <name name="from_list" arity="1" since="OTP 17.0"/>
       <fsummary></fsummary>
diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl
index 1f2b774eb9..434356d71b 100644
--- a/lib/stdlib/src/maps.erl
+++ b/lib/stdlib/src/maps.erl
@@ -29,7 +29,7 @@
          merge_with/3]).
 
 %% BIFs
--export([get/2, find/2, from_list/1,
+-export([get/2, find/2, from_list/1, from_keys/2,
          is_key/2, keys/1, merge/2,
          put/3, remove/2, take/2,
          to_list/1, update/3, values/1]).
@@ -67,6 +67,14 @@ find(_,_) -> erlang:nif_error(undef).
 
 from_list(_) -> erlang:nif_error(undef).
 
+%% Shadowed by erl_bif_types: maps:from_keys/2
+-spec from_keys(Keys, Value) -> Map when
+    Keys :: list(),
+    Value :: term(),
+    Map :: map().
+
+from_keys(_, _) -> erlang:nif_error(undef).
+
 -spec intersect(Map1,Map2) -> Map3 when
     Map1 :: #{Key => term()},
     Map2 :: #{term() => Value2},
diff --git a/lib/stdlib/test/maps_SUITE.erl b/lib/stdlib/test/maps_SUITE.erl
index 3d5b0d7465..61e2b8f6e4 100644
--- a/lib/stdlib/test/maps_SUITE.erl
+++ b/lib/stdlib/test/maps_SUITE.erl
@@ -33,7 +33,7 @@
          t_iterator_1/1, t_put_opt/1, t_merge_opt/1,
          t_with_2/1,t_without_2/1,
          t_intersect/1, t_intersect_with/1,
-         t_merge_with/1]).
+         t_merge_with/1, t_from_keys/1]).
 
 %%-define(badmap(V,F,Args), {'EXIT', {{badmap,V}, [{maps,F,Args,_}|_]}}).
 %%-define(badarg(F,Args), {'EXIT', {badarg, [{maps,F,Args,_}|_]}}).
@@ -53,7 +53,23 @@ all() ->
      t_iterator_1,t_put_opt,t_merge_opt,
      t_with_2,t_without_2,
      t_intersect, t_intersect_with,
-     t_merge_with].
+     t_merge_with, t_from_keys].
+
+t_from_keys(Config) when is_list(Config) ->
+    Map0 = maps:from_keys(["a", 2, {three}], value),
+    3 = map_size(Map0),
+    #{"a":=value,2:=value,{three}:=value} = Map0,
+
+    Map1 = maps:from_keys([1, 2, 2], {complex,value}),
+    2 = map_size(Map1),
+    #{1:={complex,value},2:={complex,value}} = Map1,
+
+    Map2 = maps:from_keys([], value),
+    0 = map_size(Map2),
+
+    ?badarg(from_keys,[[a|b],value]) = (catch maps:from_keys([a|b],value)),
+    ?badarg(from_keys,[not_list,value]) = (catch maps:from_keys(not_list,value)),
+    ok.
 
 t_update_with_3(Config) when is_list(Config) ->
     V1 = value1,
-- 
2.26.2

openSUSE Build Service is sponsored by