File 2723-Add-maps-filtermap-2.patch of Package erlang

From 12c1200dc83f51d0cfe055b7fec449152af7530d Mon Sep 17 00:00:00 2001
From: Maria-12648430 <maria-12648430@gmx.net>
Date: Tue, 1 Dec 2020 15:39:14 +0100
Subject: [PATCH] Add maps:filtermap/2

---
 lib/stdlib/doc/src/maps.xml    | 27 +++++++++++++++++++++++++++
 lib/stdlib/src/maps.erl        | 30 +++++++++++++++++++++++++++++-
 lib/stdlib/test/maps_SUITE.erl | 18 ++++++++++++++++--
 3 files changed, 72 insertions(+), 3 deletions(-)

diff --git a/lib/stdlib/doc/src/maps.xml b/lib/stdlib/doc/src/maps.xml
index aba390af7f..d04b34b32b 100644
--- a/lib/stdlib/doc/src/maps.xml
+++ b/lib/stdlib/doc/src/maps.xml
@@ -72,6 +72,33 @@
       </desc>
     </func>
 
+    <func>
+      <name name="filtermap" arity="2" since=""/>
+      <fsummary>Filter and map a map.</fsummary>
+      <desc>
+        <p>Returns a map <c><anno>Map</anno></c> that is the result of calling
+          <c><anno>Fun</anno>(<anno>Key</anno>, <anno>Value1</anno>)</c> for
+          every <c><anno>Key</anno></c> to value <c><anno>Value1</anno></c>
+          association in <c><anno>MapOrIter</anno></c> in any order.</p>
+        <p>If <c><anno>Fun</anno>(<anno>Key</anno>, <anno>Value1</anno>)</c>
+          returns <c>true</c>, the association is copied to the result map. If
+          it returns <c>false</c>, the association is not copied. If it returns
+          <c>{true, NewValue}</c>, the value for <c><anno>Key</anno></c> is
+          replaced with <c>NewValue</c>at this position is replaced in the
+          result map.</p>
+        <p>The call fails with a <c>{badmap,Map}</c> exception if
+          <c><anno>MapOrIter</anno></c> is not a map or valid iterator,
+          or with <c>badarg</c> if <c><anno>Fun</anno></c> is not a
+          function of arity 3.</p>
+        <p><em>Example:</em></p>
+        <code type="none">
+> Fun = fun(K,V) when is_atom(K) -> {true, V*2}; (_,V) -> (V rem 2) =:= 0 end,
+  Map = #{k1 => 1, "k2" => 2, "k3" => 3},
+  maps:filtermap(Fun,Map).
+#{k1 => 2,"k2" => 2}</code>
+      </desc>
+    </func>
+
     <func>
       <name name="find" arity="2" since="OTP 17.0"/>
       <fsummary></fsummary>
diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl
index 1f2b774eb9..8d94f6d430 100644
--- a/lib/stdlib/src/maps.erl
+++ b/lib/stdlib/src/maps.erl
@@ -20,7 +20,7 @@
 
 -module(maps).
 
--export([get/3, filter/2,fold/3,
+-export([get/3, filter/2, filtermap/2, fold/3,
          map/2, size/1, new/0,
          update_with/3, update_with/4,
          without/2, with/2,
@@ -305,6 +305,34 @@ filter_1(Pred, Iter) ->
             []
     end.
 
+
+-spec filtermap(Fun, MapOrIter) -> Map when
+      Fun :: fun((Key, Value1) -> boolean() | {true, Value2}),
+      MapOrIter :: #{Key => Value1} | iterator(Key, Value1),
+      Map :: #{Key => Value1 | Value2}.
+
+filtermap(Fun, Map) when is_function(Fun, 2), is_map(Map) ->
+    maps:from_list(filtermap_1(Fun, iterator(Map)));
+filtermap(Fun, Iterator) when is_function(Fun, 2), ?IS_ITERATOR(Iterator) ->
+    maps:from_list(filtermap_1(Fun, Iterator));
+filtermap(Fun, Map) ->
+    erlang:error(error_type(Map), [Fun, Map]).
+
+filtermap_1(Pred, Iter) ->
+    case next(Iter) of
+	{K, V, NextIter} ->
+	    case Pred(K, V) of
+		true ->
+		    [{K, V} | filtermap_1(Pred, NextIter)];
+		{true, NewV} ->
+		    [{K, NewV} | filtermap_1(Pred, NextIter)];
+		false ->
+		    filtermap_1(Pred, NextIter)
+	    end;
+	none ->
+	    []
+    end.
+
 -spec fold(Fun,Init,MapOrIter) -> Acc when
     Fun :: fun((Key, Value, AccIn) -> AccOut),
     Init :: term(),
diff --git a/lib/stdlib/test/maps_SUITE.erl b/lib/stdlib/test/maps_SUITE.erl
index 3d5b0d7465..451b1b54e9 100644
--- a/lib/stdlib/test/maps_SUITE.erl
+++ b/lib/stdlib/test/maps_SUITE.erl
@@ -28,7 +28,7 @@
 -export([all/0, suite/0]).
 
 -export([t_update_with_3/1, t_update_with_4/1,
-         t_get_3/1, t_filter_2/1,
+         t_get_3/1, t_filter_2/1, t_filtermap_2/1,
          t_fold_3/1,t_map_2/1,t_size_1/1,
          t_iterator_1/1, t_put_opt/1, t_merge_opt/1,
          t_with_2/1,t_without_2/1,
@@ -45,7 +45,7 @@ suite() ->
 
 all() ->
     [t_update_with_3,t_update_with_4,
-     t_get_3,t_filter_2,
+     t_get_3,t_filter_2,t_filtermap_2,
      t_fold_3,t_map_2,t_size_1,
      t_iterator_1,t_put_opt,t_merge_opt,
      t_with_2,t_without_2,
@@ -141,6 +141,20 @@ t_filter_2(Config) when is_list(Config) ->
     ?badarg(filter,[<<>>,#{}]) = (catch maps:filter(id(<<>>),#{})),
     ok.
 
+t_filtermap_2(Config) when is_list(Config) ->
+    M0 = maps:from_list([{I, I} || I <- lists:seq(1, 30)]),
+    Pred = fun(K,_) when K=<10 -> true; (K,_) when K=<20 -> false; (_,V) -> {true, V * V} end,
+    M1 = maps:filtermap(Pred, M0),
+    M2 = maps:filtermap(Pred, maps:iterator(M0)),
+    #{1 := 1, 10 := 10, 21 := 21 * 21, 30 := 30 * 30} = M1,
+    false = maps:is_key(11, M1),
+    false = maps:is_key(20, M1),
+    true = M1 =:= M2,
+    %% error case
+    ?badmap(a,filtermap,[_,a]) = (catch maps:filtermap(fun(_,_) -> ok end,id(a))),
+    ?badarg(filtermap,[<<>>,#{}]) = (catch maps:filtermap(id(<<>>),#{})),
+    ok.
+
 t_fold_3(Config) when is_list(Config) ->
     Vs = lists:seq(1,200),
     M0 = maps:from_list([{{k,I},I}||I<-Vs]),
-- 
2.26.2

openSUSE Build Service is sponsored by