File 2190-erts-Add-BIF-maps-take-2.patch of Package erlang

From 65bd8ade865eebe0d8a3c3210a4e2e9f334e229f Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn-Egil=20Dahlberg?= <egil@erlang.org>
Date: Sun, 10 Apr 2016 22:48:55 +0200
Subject: [PATCH 1/6] erts: Add BIF maps:take/2

---
 erts/emulator/beam/bif.tab   |  2 ++
 erts/emulator/beam/erl_map.c | 75 +++++++++++++++++++++++++++++++++-----------
 erts/emulator/beam/erl_map.h |  1 +
 erts/emulator/beam/erl_nif.c |  5 ++-
 lib/stdlib/src/maps.erl      |  9 +++++-
 5 files changed, 70 insertions(+), 22 deletions(-)

diff --git a/erts/emulator/beam/bif.tab b/erts/emulator/beam/bif.tab
index 58cd31c..872f0f9 100644
--- a/erts/emulator/beam/bif.tab
+++ b/erts/emulator/beam/bif.tab
@@ -652,6 +652,8 @@ bif erts_debug:size_shared/1
 bif erts_debug:copy_shared/1
 bif erlang:has_prepared_code_on_load/1
 
+bif maps:take/2
+
 #
 # Obsolete
 #
diff --git a/erts/emulator/beam/erl_map.c b/erts/emulator/beam/erl_map.c
index 03a96cb..8efc983 100644
--- a/erts/emulator/beam/erl_map.c
+++ b/erts/emulator/beam/erl_map.c
@@ -54,6 +54,7 @@
  * - maps:new/0
  * - maps:put/3
  * - maps:remove/2
+ * - maps:take/2
  * - maps:to_list/1
  * - maps:update/3
  * - maps:values/1
@@ -93,7 +94,7 @@ static Uint hashmap_subtree_size(Eterm node);
 static Eterm hashmap_to_list(Process *p, Eterm map);
 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);
+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 hashmap_from_unsorted_array(ErtsHeapFactory*, hxnode_t *hxns, Uint n, int reject_dupkeys);
@@ -1521,10 +1522,45 @@ BIF_RETTYPE maps_put_3(BIF_ALIST_3) {
     BIF_ERROR(BIF_P, BADMAP);
 }
 
-/* maps:remove/3 */
+/* maps:take/2 */
 
-int erts_maps_remove(Process *p, Eterm key, Eterm map, Eterm *res) {
+BIF_RETTYPE maps_take_2(BIF_ALIST_2) {
+    if (is_map(BIF_ARG_2)) {
+        Eterm res, map, val;
+        if (erts_maps_take(BIF_P, BIF_ARG_1, BIF_ARG_2, &map, &val)) {
+            Eterm *hp = HAlloc(BIF_P, 3);
+            res   = make_tuple(hp);
+            *hp++ = make_arityval(2);
+            *hp++ = val;
+            *hp++ = map;
+            BIF_RET(res);
+        }
+        BIF_RET(am_error);
+    }
+    BIF_P->fvalue = BIF_ARG_2;
+    BIF_ERROR(BIF_P, BADMAP);
+}
+
+/* maps:remove/2 */
+
+BIF_RETTYPE maps_remove_2(BIF_ALIST_2) {
+    if (is_map(BIF_ARG_2)) {
+        Eterm res;
+        (void) erts_maps_take(BIF_P, BIF_ARG_1, BIF_ARG_2, &res, NULL);
+        BIF_RET(res);
+    }
+    BIF_P->fvalue = BIF_ARG_2;
+    BIF_ERROR(BIF_P, BADMAP);
+}
+
+/* erts_maps_take
+ * return 1 if key is found, otherwise 0
+ * If the key is not found res (output map) will be map (input map)
+ */
+int erts_maps_take(Process *p, Eterm key, Eterm map,
+                   Eterm *res, Eterm *value) {
     Uint32 hx;
+    Eterm ret;
     if (is_flatmap(map)) {
 	Sint n;
 	Uint need;
@@ -1537,7 +1573,7 @@ int erts_maps_remove(Process *p, Eterm key, Eterm map, Eterm *res) {
 
 	if (n == 0) {
 	    *res = map;
-	    return 1;
+	    return 0;
 	}
 
 	ks = flatmap_get_keys(mp);
@@ -1564,6 +1600,7 @@ int erts_maps_remove(Process *p, Eterm key, Eterm map, Eterm *res) {
 	if (is_immed(key)) {
 	    while (1) {
 		if (*ks == key) {
+                    if (value) *value = *vs;
 		    goto found_key;
 		} else if (--n) {
 		    *mhp++ = *vs++;
@@ -1574,6 +1611,7 @@ int erts_maps_remove(Process *p, Eterm key, Eterm map, Eterm *res) {
 	} else {
 	    while(1) {
 		if (EQ(*ks, key)) {
+                    if (value) *value = *vs;
 		    goto found_key;
 		} else if (--n) {
 		    *mhp++ = *vs++;
@@ -1589,7 +1627,7 @@ int erts_maps_remove(Process *p, Eterm key, Eterm map, Eterm *res) {
 	HRelease(p, hp_start + need, hp_start);
 
 	*res = map;
-	return 1;
+	return 0;
 
 found_key:
 	/* Copy rest of keys and values */
@@ -1601,19 +1639,13 @@ found_key:
     }
     ASSERT(is_hashmap(map));
     hx = hashmap_make_hash(key);
-    *res = hashmap_delete(p, hx, key, map);
-    return 1;
-}
-
-BIF_RETTYPE maps_remove_2(BIF_ALIST_2) {
-    if (is_map(BIF_ARG_2)) {
-	Eterm res;
-	if (erts_maps_remove(BIF_P, BIF_ARG_1, BIF_ARG_2, &res)) {
-	    BIF_RET(res);
-	}
+    ret = hashmap_delete(p, hx, key, map, value);
+    if (is_value(ret)) {
+        *res = ret;
+        return 1;
     }
-    BIF_P->fvalue = BIF_ARG_2;
-    BIF_ERROR(BIF_P, BADMAP);
+    *res = map;
+    return 0;
 }
 
 int erts_maps_update(Process *p, Eterm key, Eterm value, Eterm map, Eterm *res) {
@@ -2322,7 +2354,8 @@ static Eterm hashmap_values(Process* p, Eterm node) {
     return res;
 }
 
-static Eterm hashmap_delete(Process *p, Uint32 hx, Eterm key, Eterm map) {
+static Eterm hashmap_delete(Process *p, Uint32 hx, Eterm key,
+                            Eterm map, Eterm *value) {
     Eterm *hp = NULL, *nhp = NULL, *hp_end = NULL;
     Eterm *ptr;
     Eterm hdr, res = map, node = map;
@@ -2337,8 +2370,12 @@ static Eterm hashmap_delete(Process *p, Uint32 hx, Eterm key, Eterm map) {
 	switch(primary_tag(node)) {
 	    case TAG_PRIMARY_LIST:
 		if (EQ(CAR(list_val(node)), key)) {
+                    if (value) {
+                        *value = CDR(list_val(node));
+                    }
 		    goto unroll;
 		}
+                res = THE_NON_VALUE;
 		goto not_found;
 	    case TAG_PRIMARY_BOXED:
 		ptr = boxed_val(node);
@@ -2365,6 +2402,7 @@ static Eterm hashmap_delete(Process *p, Uint32 hx, Eterm key, Eterm map) {
                             n    = hashmap_bitcount(hval);
                         } else {
                             /* not occupied */
+                            res = THE_NON_VALUE;
                             goto not_found;
                         }
 
@@ -2394,6 +2432,7 @@ static Eterm hashmap_delete(Process *p, Uint32 hx, Eterm key, Eterm map) {
 			    break;
 			}
 			/* not occupied */
+                        res = THE_NON_VALUE;
 			goto not_found;
 		    default:
 			erts_exit(ERTS_ERROR_EXIT, "bad header tag %ld\r\n", hdr & _HEADER_MAP_SUBTAG_MASK);
diff --git a/erts/emulator/beam/erl_map.h b/erts/emulator/beam/erl_map.h
index 7af9100..8b5c958 100644
--- a/erts/emulator/beam/erl_map.h
+++ b/erts/emulator/beam/erl_map.h
@@ -82,6 +82,7 @@ struct ErtsEStack_;
 Eterm  erts_maps_put(Process *p, Eterm key, Eterm value, Eterm map);
 int    erts_maps_update(Process *p, Eterm key, Eterm value, Eterm map, Eterm *res);
 int    erts_maps_remove(Process *p, Eterm key, Eterm map, Eterm *res);
+int    erts_maps_take(Process *p, Eterm key, Eterm map, Eterm *res, Eterm *value);
 
 Eterm  erts_hashmap_insert(Process *p, Uint32 hx, Eterm key, Eterm value,
 			   Eterm node, int is_update);
diff --git a/erts/emulator/beam/erl_nif.c b/erts/emulator/beam/erl_nif.c
index 73c0eb8..24e72cc 100644
--- a/erts/emulator/beam/erl_nif.c
+++ b/erts/emulator/beam/erl_nif.c
@@ -2443,14 +2443,13 @@ int enif_make_map_remove(ErlNifEnv* env,
 			 Eterm key,
 			 Eterm *map_out)
 {
-    int res;
     if (!is_map(map_in)) {
 	return 0;
     }
     flush_env(env);
-    res = erts_maps_remove(env->proc, key, map_in, map_out);
+    (void) erts_maps_take(env->proc, key, map_in, map_out, NULL);
     cache_env(env);
-    return res;
+    return 1;
 }
 
 int enif_map_iterator_create(ErlNifEnv *env,
diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl
index a52928f..a8c2740 100644
--- a/lib/stdlib/src/maps.erl
+++ b/lib/stdlib/src/maps.erl
@@ -28,7 +28,7 @@
 %%% BIFs
 -export([get/2, find/2, from_list/1,
          is_key/2, keys/1, merge/2,
-         new/0, put/3, remove/2,
+         new/0, put/3, remove/2, take/2,
          to_list/1, update/3, values/1]).
 
 -spec get(Key,Map) -> Value when
@@ -102,6 +102,13 @@ put(_,_,_) -> erlang:nif_error(undef).
 
 remove(_,_) -> erlang:nif_error(undef).
 
+-spec take(Key,Map1) -> {Value,Map2} | error when
+    Key :: term(),
+    Map1 :: map(),
+    Value :: term(),
+    Map2 :: map().
+
+take(_,_) -> erlang:nif_error(undef).
 
 -spec to_list(Map) -> [{Key,Value}] when
     Map :: map(),
-- 
2.1.4

openSUSE Build Service is sponsored by