File 2191-Add-take-2-to-all-dictionary-modules.patch of Package erlang

From a2d92dff3a8acc534daeeb3dea5edda406a6ab0d Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Fri, 16 Dec 2016 12:50:28 +0100
Subject: [PATCH] Add take/2 to all dictionary modules

Similar to maps:take/2, add take/2 to the other dictionary
modules in STDLIB:

  orddict:take(Key, Dict) -> {Val,NewDict} | 'error'.
  dict:take(Key, Dict) -> {Val,NewDict} | 'error'.
  gb_trees:take(Key, Dict) -> {Val,NewDict}.

For gb_trees also add:

  gb_trees:take_any(Key, Dict) -> {Val,NewDict} | 'error'.

gb_trees already has delete() and delete_any(), so we will
follow that design pattern.

Suggested by Boris Bochkaryov in https://github.com/erlang/otp/pull/1209.
---
 lib/stdlib/doc/src/dict.xml       | 10 +++++++++
 lib/stdlib/doc/src/gb_trees.xml   | 22 +++++++++++++++++++
 lib/stdlib/doc/src/orddict.xml    |  9 ++++++++
 lib/stdlib/src/dict.erl           | 23 +++++++++++++++++++-
 lib/stdlib/src/gb_trees.erl       | 45 ++++++++++++++++++++++++++++++++++++++-
 lib/stdlib/src/orddict.erl        | 19 ++++++++++++++++-
 lib/stdlib/test/dict_SUITE.erl    | 27 ++++++++++++++++++++---
 lib/stdlib/test/dict_test_lib.erl | 20 ++++++++++++++++-
 8 files changed, 168 insertions(+), 7 deletions(-)

diff --git a/lib/stdlib/doc/src/dict.xml b/lib/stdlib/doc/src/dict.xml
index c926ff1b5..c229a1872 100644
--- a/lib/stdlib/doc/src/dict.xml
+++ b/lib/stdlib/doc/src/dict.xml
@@ -106,6 +106,16 @@
     </func>
 
     <func>
+      <name name="take" arity="2"/>
+      <fsummary>Return value and new dictionary without element with this value.</fsummary>
+      <desc>
+        <p>This function returns value from dictionary and a
+        new dictionary without this value.
+        Returns <c>error</c> if the key is not present in the dictionary.</p>
+      </desc>
+    </func>
+
+    <func>
       <name name="filter" arity="2"/>
       <fsummary>Select elements that satisfy a predicate.</fsummary>
       <desc>
diff --git a/lib/stdlib/doc/src/gb_trees.xml b/lib/stdlib/doc/src/gb_trees.xml
index 790d4b8bf..5cfff021c 100644
--- a/lib/stdlib/doc/src/gb_trees.xml
+++ b/lib/stdlib/doc/src/gb_trees.xml
@@ -109,6 +109,28 @@
     </func>
 
     <func>
+      <name name="take" arity="2"/>
+      <fsummary>Returns a value and new tree without node with key <c>Key</c>.</fsummary>
+      <desc>
+        <p>Returns a value <c><anno>Value</anno></c> from node with key <c><anno>Key</anno></c>
+          and new <c><anno>Tree2</anno></c> without the node with this value.
+          Assumes that the node with key is present in the tree,
+         crashes otherwise.</p>
+      </desc>
+    </func>
+
+    <func>
+      <name name="take_any" arity="2"/>
+      <fsummary>Returns a value and new tree without node with key <c>Key</c>.</fsummary>
+      <desc>
+        <p>Returns a value <c><anno>Value</anno></c> from node with key <c><anno>Key</anno></c>
+          and new <c><anno>Tree2</anno></c> without the node with this value.
+          Returns <c>error</c> if the node with the key is not present in
+          the tree.</p>
+      </desc>
+    </func>
+
+    <func>
       <name name="empty" arity="0"/>
       <fsummary>Return an empty tree.</fsummary>
       <desc>
diff --git a/lib/stdlib/doc/src/orddict.xml b/lib/stdlib/doc/src/orddict.xml
index 109b038cb..26bbf499c 100644
--- a/lib/stdlib/doc/src/orddict.xml
+++ b/lib/stdlib/doc/src/orddict.xml
@@ -113,6 +113,15 @@
     </func>
 
     <func>
+      <name name="take" arity="2"/>
+      <fsummary>Return value and new dictionary without element with this value.</fsummary>
+      <desc>
+        <p>This function returns value from dictionary and new dictionary without this value.
+            Returns <c>error</c> if the key is not present in the dictionary.</p>
+      </desc>
+    </func>
+
+    <func>
       <name name="filter" arity="2"/>
       <fsummary>Select elements that satisfy a predicate.</fsummary>
       <desc>
diff --git a/lib/stdlib/src/dict.erl b/lib/stdlib/src/dict.erl
index f921e28ef..9449ba3dc 100644
--- a/lib/stdlib/src/dict.erl
+++ b/lib/stdlib/src/dict.erl
@@ -38,7 +38,7 @@
 
 %% Standard interface.
 -export([new/0,is_key/2,to_list/1,from_list/1,size/1,is_empty/1]).
--export([fetch/2,find/2,fetch_keys/1,erase/2]).
+-export([fetch/2,find/2,fetch_keys/1,erase/2,take/2]).
 -export([store/3,append/3,append_list/3,update/3,update/4,update_counter/3]).
 -export([fold/3,map/2,filter/2,merge/3]).
 
@@ -172,6 +172,27 @@ erase_key(Key, [E|Bkt0]) ->
     {[E|Bkt1],Dc};
 erase_key(_, []) -> {[],0}.
 
+-spec take(Key, Dict) -> {Value, Dict1} | error when
+      Dict :: dict(Key, Value),
+      Dict1 :: dict(Key, Value),
+      Key :: term(),
+      Value :: term().
+
+take(Key, D0) ->
+    Slot = get_slot(D0, Key),
+    case on_bucket(fun (B0) -> take_key(Key, B0) end, D0, Slot) of
+	{D1,{Value,Dc}} ->
+            {Value, maybe_contract(D1, Dc)};
+	{_,error} -> error
+    end.
+
+take_key(Key, [?kv(Key,Val)|Bkt]) ->
+    {Bkt,{Val,1}};
+take_key(Key, [E|Bkt0]) ->
+    {Bkt1,Res} = take_key(Key, Bkt0),
+    {[E|Bkt1],Res};
+take_key(_, []) -> {[],error}.
+
 -spec store(Key, Value, Dict1) -> Dict2 when
       Dict1 :: dict(Key, Value),
       Dict2 :: dict(Key, Value).
diff --git a/lib/stdlib/src/gb_trees.erl b/lib/stdlib/src/gb_trees.erl
index 457287fa5..c0cdde012 100644
--- a/lib/stdlib/src/gb_trees.erl
+++ b/lib/stdlib/src/gb_trees.erl
@@ -52,6 +52,13 @@
 %% - delete_any(X, T): removes key X from tree T if the key is present
 %%   in the tree, otherwise does nothing; returns new tree.
 %%
+%% - take(X, T): removes element with key X from tree T; returns new tree
+%%   without removed element. Assumes that the key is present in the tree.
+%%
+%% - take_any(X, T): removes element with key X from tree T and returns
+%%   a new tree if the key is present; otherwise does nothing and returns
+%%   'error'.
+%%
 %% - balance(T): rebalances tree T. Note that this is rarely necessary,
 %%   but may be motivated when a large number of entries have been
 %%   deleted from the tree without further insertions. Rebalancing could
@@ -114,7 +121,8 @@
 -export([empty/0, is_empty/1, size/1, lookup/2, get/2, insert/3,
 	 update/3, enter/3, delete/2, delete_any/2, balance/1,
 	 is_defined/2, keys/1, values/1, to_list/1, from_orddict/1,
-	 smallest/1, largest/1, take_smallest/1, take_largest/1,
+	 smallest/1, largest/1, take/2, take_any/2,
+         take_smallest/1, take_largest/1,
 	 iterator/1, iterator_from/2, next/1, map/2]).
 
 
@@ -416,6 +424,41 @@ merge(Smaller, Larger) ->
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
+-spec take_any(Key, Tree1) -> {Value, Tree2} | 'error' when
+      Tree1 :: tree(Key, _),
+      Tree2 :: tree(Key, _),
+      Key   :: term(),
+      Value :: term().
+
+take_any(Key, Tree) ->
+    case is_defined(Key, Tree) of
+        true -> take(Key, Tree);
+        false -> error
+    end.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+-spec take(Key, Tree1) -> {Value, Tree2} when
+      Tree1 :: tree(Key, _),
+      Tree2 :: tree(Key, _),
+      Key   :: term(),
+      Value :: term().
+
+take(Key, {S, T}) when is_integer(S), S >= 0 ->
+    {Value, Res} = take_1(Key, T),
+    {Value, {S - 1, Res}}.
+
+take_1(Key, {Key1, Value, Smaller, Larger}) when Key < Key1 ->
+    {Value2, Smaller1} = take_1(Key, Smaller),
+    {Value2, {Key1, Value, Smaller1, Larger}};
+take_1(Key, {Key1, Value, Smaller, Bigger}) when Key > Key1 ->
+    {Value2, Bigger1} = take_1(Key, Bigger),
+    {Value2, {Key1, Value, Smaller, Bigger1}};
+take_1(_, {_Key, Value, Smaller, Larger}) ->
+    {Value, merge(Smaller, Larger)}.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
 -spec take_smallest(Tree1) -> {Key, Value, Tree2} when
       Tree1 :: tree(Key, Value),
       Tree2 :: tree(Key, Value).
diff --git a/lib/stdlib/src/orddict.erl b/lib/stdlib/src/orddict.erl
index 37cf0084f..caa59099a 100644
--- a/lib/stdlib/src/orddict.erl
+++ b/lib/stdlib/src/orddict.erl
@@ -22,7 +22,7 @@
 
 %% Standard interface.
 -export([new/0,is_key/2,to_list/1,from_list/1,size/1,is_empty/1]).
--export([fetch/2,find/2,fetch_keys/1,erase/2]).
+-export([fetch/2,find/2,fetch_keys/1,erase/2,take/2]).
 -export([store/3,append/3,append_list/3,update/3,update/4,update_counter/3]).
 -export([fold/3,map/2,filter/2,merge/3]).
 
@@ -106,6 +106,23 @@ erase(Key, [{K,_}=E|Dict]) when Key > K ->
 erase(_Key, [{_K,_Val}|Dict]) -> Dict;		%Key == K
 erase(_, []) -> [].
 
+-spec take(Key, Orddict) -> {Value, Orddict1} | error when
+      Orddict :: orddict(Key, Value),
+      Orddict1 :: orddict(Key, Value),
+      Key :: term(),
+      Value :: term().
+
+take(Key, Dict) ->
+    take_1(Key, Dict, []).
+
+take_1(Key, [{K,_}|_], _Acc) when Key < K ->
+    error;
+take_1(Key, [{K,_}=P|D], Acc) when Key > K ->
+    take_1(Key, D, [P|Acc]);
+take_1(_Key, [{_K,Value}|D], Acc) ->
+    {Value,lists:reverse(Acc, D)};
+take_1(_, [], _) -> error.
+
 -spec store(Key, Value, Orddict1) -> Orddict2 when
       Orddict1 :: orddict(Key, Value),
       Orddict2 :: orddict(Key, Value).
diff --git a/lib/stdlib/test/dict_SUITE.erl b/lib/stdlib/test/dict_SUITE.erl
index 47358d729..e99af9ad4 100644
--- a/lib/stdlib/test/dict_SUITE.erl
+++ b/lib/stdlib/test/dict_SUITE.erl
@@ -23,10 +23,10 @@
 
 -module(dict_SUITE).
 
--export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
 	 init_per_group/2,end_per_group/2,
 	 init_per_testcase/2,end_per_testcase/2,
-         create/1,store/1,iterate/1]).
+	 create/1,store/1,iterate/1,remove/1]).
 
 -include_lib("common_test/include/ct.hrl").
 
@@ -37,7 +37,7 @@ suite() ->
      {timetrap,{minutes,5}}].
 
 all() -> 
-    [create, store, iterate].
+    [create, store, remove, iterate].
 
 groups() -> 
     [].
@@ -92,6 +92,27 @@ store_1(List, M) ->
     end,
     D0.
 
+remove(_Config) ->
+    test_all([{0,87}], fun remove_1/2).
+
+remove_1(List0, M) ->
+    %% Make sure that keys are unique. Randomize key order.
+    List1 = orddict:from_list(List0),
+    List2 = lists:sort([{rand:uniform(),E} || E <- List1]),
+    List = [E || {_,E} <- List2],
+    D0 = M(from_list, List),
+    remove_2(List, D0, M).
+
+remove_2([{Key,Val}|T], D0, M) ->
+    {Val,D1} = M(take, {Key,D0}),
+    error = M(take, {Key,D1}),
+    D2 = M(erase, {Key,D0}),
+    true = M(equal, {D1,D2}),
+    remove_2(T, D1, M);
+remove_2([], D, M) ->
+    true = M(is_empty, D),
+    D.
+
 %%%
 %%% Test specifics for gb_trees.
 %%%
diff --git a/lib/stdlib/test/dict_test_lib.erl b/lib/stdlib/test/dict_test_lib.erl
index 7c4c3572a..f6fef7bdf 100644
--- a/lib/stdlib/test/dict_test_lib.erl
+++ b/lib/stdlib/test/dict_test_lib.erl
@@ -33,7 +33,9 @@ new(Mod, Eq) ->
         (iterator, S) -> Mod:iterator(S);
         (iterator_from, {Start, S}) -> Mod:iterator_from(Start, S);
         (next, I) -> Mod:next(I);
-	(to_list, D) -> to_list(Mod, D)
+	(to_list, D) -> to_list(Mod, D);
+	(erase, {K,D}) -> erase(Mod, K, D);
+	(take, {K,D}) -> take(Mod, K, D)
     end.
 
 empty(Mod) ->
@@ -67,3 +69,19 @@ enter(Mod, Key, Val, Dict) ->
 	true ->
 	    Mod:store(Key, Val, Dict)
     end.
+
+erase(Mod, Key, Val) when Mod =:= dict; Mod =:= orddict ->
+    Mod:erase(Key, Val);
+erase(gb_trees, Key, Val) ->
+    gb_trees:delete_any(Key, Val).
+
+take(gb_trees, Key, Val) ->
+    Res = try
+	      gb_trees:take(Key, Val)
+	  catch
+	      error:_ ->
+		  error
+	  end,
+    Res = gb_trees:take_any(Key, Val);
+take(Mod, Key, Val) ->
+    Mod:take(Key, Val).
-- 
2.11.0

openSUSE Build Service is sponsored by