File 4131-Add-maps-foreach-2-function.patch of Package erlang

From 7a77388273a96f12023e9d30d188542556ac3342 Mon Sep 17 00:00:00 2001
From: gearnode <bryan@frimin.fr>
Date: Mon, 18 Jan 2021 17:18:36 +0100
Subject: [PATCH] Add maps:foreach/2 function

The only way to iterate over maps without an accumulator is to
manipulate maps iterator manually. It's a bit painful to write
the same boilerplate code every time to iterate over a map without
an accumulator.

The maps:foreach/2 function is similar to lists:foreach/2 but for
map.
---
 lib/stdlib/doc/src/maps.xml          | 14 ++++++++++++++
 lib/stdlib/src/erl_stdlib_errors.erl |  2 ++
 lib/stdlib/src/maps.erl              | 27 +++++++++++++++++++++++++--
 lib/stdlib/test/maps_SUITE.erl       | 28 ++++++++++++++++++++++++++--
 4 files changed, 67 insertions(+), 4 deletions(-)

diff --git a/lib/stdlib/doc/src/maps.xml b/lib/stdlib/doc/src/maps.xml
index efd0fff239..d90d566c14 100644
--- a/lib/stdlib/doc/src/maps.xml
+++ b/lib/stdlib/doc/src/maps.xml
@@ -142,6 +142,20 @@
       </desc>
     </func>
 
+    <func>
+      <name name="foreach" arity="2" since="OTP 24.0"/>
+      <fsummary>Apply a function to each element of a map.</fsummary>
+      <desc>
+        <p>Calls <c>fun F(Key, Value)</c> for every <c><anno>Key</anno></c>
+          to value <c><anno>Value</anno></c> association in
+          <c><anno>MapOrIter</anno></c> in any order.</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 2.</p>
+      </desc>
+    </func>
+
     <func>
       <name name="from_keys" arity="2" since="OTP 14.0"/>
       <fsummary></fsummary>
diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl
index 03a00c3a4b..dbdd1ae5b7 100644
--- a/lib/stdlib/src/maps.erl
+++ b/lib/stdlib/src/maps.erl
@@ -20,7 +20,7 @@
 
 -module(maps).
 
--export([get/3, filter/2, filtermap/2, fold/3,
+-export([get/3, filter/2, filtermap/2, fold/3, foreach/2,
          map/2, size/1, new/0,
          update_with/3, update_with/4,
          without/2, with/2,
@@ -290,7 +290,6 @@ get(Key,Map,Default) when is_map(Map) ->
 get(Key,Map,Default) ->
     erlang:error({badmap,Map},[Key,Map,Default]).
 
-
 -spec filter(Pred, MapOrIter) -> Map when
       Pred :: fun((Key, Value) -> boolean()),
       MapOrIter :: #{Key => Value} | iterator(Key, Value),
@@ -344,6 +343,30 @@ filtermap_1(Pred, {K, V, Iter}) ->
 	    []
     end.
 
+-spec foreach(Fun,MapOrIter) -> ok when
+      Fun :: fun((Key, Value) -> term()),
+      MapOrIter :: #{Key => Value} | iterator(Key, Value).
+
+foreach(Fun, MapOrIter) when is_function(Fun, 2) ->
+    Iter = if is_map(MapOrIter) -> iterator(MapOrIter);
+              true -> MapOrIter
+           end,
+    try next(Iter) of
+        Next ->
+            foreach_1(Fun, Next)
+    catch
+        error:_ ->
+            erlang:error(error_type(MapOrIter), [Fun, MapOrIter])
+    end;
+foreach(Pred, Map) ->
+    erlang:error(badarg, [Pred, Map]).
+
+foreach_1(Fun, {K, V, Iter}) ->
+    Fun(K,V),
+    foreach_1(Fun, next(Iter));
+foreach_1(_Fun, none) ->
+    ok.
+
 -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 cc234f2b46..f369b3ebaa 100644
--- a/lib/stdlib/test/maps_SUITE.erl
+++ b/lib/stdlib/test/maps_SUITE.erl
@@ -29,7 +29,7 @@
 
 -export([t_update_with_3/1, t_update_with_4/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_fold_3/1,t_map_2/1,t_size_1/1, t_foreach_2/1,
          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,
@@ -47,7 +47,7 @@ suite() ->
 all() ->
     [t_update_with_3,t_update_with_4,
      t_get_3,t_filter_2,t_filtermap_2,
-     t_fold_3,t_map_2,t_size_1,
+     t_fold_3,t_map_2,t_size_1,t_foreach_2,
      t_iterator_1,t_put_opt,t_merge_opt,
      t_with_2,t_without_2,
      t_intersect, t_intersect_with,
@@ -202,6 +202,25 @@ t_map_2(Config) when is_list(Config) ->
     ?badarg(map,[<<>>,#{}]) = (catch maps:map(id(<<>>),#{})),
     ok.
 
+t_foreach_2(Config) when is_list(Config) ->
+    %% error case
+    ?badmap(a,foreach,[_,a]) = (catch maps:foreach(fun(_,_) -> ok end, id(a))),
+    ?badmap([],foreach,[_,[]]) = (catch maps:foreach(fun(_,_) -> ok end, id([]))),
+    ?badmap({},foreach,[_,{}]) = (catch maps:foreach(fun(_,_) -> ok end, id({}))),
+    ?badmap(42,foreach,[_,42]) = (catch maps:foreach(fun(_,_) -> ok end, id(42))),
+    ?badmap(<<>>,foreach,[_,<<>>]) = (catch maps:foreach(fun(_,_) -> ok end, id(<<>>))),
+
+    ?badarg(foreach,[<<>>,#{}]) = (catch maps:foreach(id(<<>>),#{})),
+    F0 = fun() -> ok end,
+    F3 = fun(_, _, _) -> ok end,
+    ?badarg(foreach,[F0, #{}]) = (catch maps:foreach(id(F0), #{})),
+    ?badarg(foreach,[F3, #{}]) = (catch maps:foreach(id(F3), #{})),
+    ?badarg(foreach,[a, #{}]) = (catch maps:foreach(id(a), #{})),
+    ?badarg(foreach,[[], #{}]) = (catch maps:foreach(id([]), #{})),
+    ?badarg(foreach,[{}, #{}]) = (catch maps:foreach(id({}), #{})),
+    ?badarg(foreach,[42, #{}]) = (catch maps:foreach(id(42), #{})),
+    ok.
+
 t_iterator_1(Config) when is_list(Config) ->
 
     %% Small map test
-- 
2.26.2

openSUSE Build Service is sponsored by