File 2721-Add-merge_with-3-intersect-2-and-intersect_with-3-to.patch of Package erlang
From 2736731d1c2acf17c216aae89e160a58d035d081 Mon Sep 17 00:00:00 2001
From: Kjell Winblad <kjellwinblad@gmail.com>
Date: Mon, 12 Oct 2020 11:52:50 +0200
Subject: [PATCH] Add `merge_with/3`, `intersect/2`, and `intersect_with/3` to
maps
Add three new functions to the maps module:
* `maps:merge_with/3` is the same as `merge/2` but takes an extra fun
that is used to combine items with the same key
* `maps:intersect/2` computes the intersection of two maps
* `maps:intersect_with/3` is the same as intersect/2 but takes an
extra fun that is used to combine intersecting items
---
lib/stdlib/doc/src/maps.xml | 74 ++++++++++
lib/stdlib/src/maps.erl | 104 +++++++++++++-
lib/stdlib/test/maps_SUITE.erl | 241 ++++++++++++++++++++++++++++++++-
3 files changed, 416 insertions(+), 3 deletions(-)
diff --git a/lib/stdlib/doc/src/maps.xml b/lib/stdlib/doc/src/maps.xml
index c445149f3b..aba390af7f 100644
--- a/lib/stdlib/doc/src/maps.xml
+++ b/lib/stdlib/doc/src/maps.xml
@@ -172,6 +172,53 @@ val1
</desc>
</func>
+ <func>
+ <name name="intersect" arity="2" since="OTP 24.0"/>
+ <fsummary></fsummary>
+ <desc>
+ <p>Intersects two maps into a single map
+ <c><anno>Map3</anno></c>. If a key exists in both maps, the
+ value in <c><anno>Map1</anno></c> is superseded by the value
+ in <c><anno>Map2</anno></c>.</p>
+ <p>The call fails with a <c>{badmap,Map}</c> exception if
+ <c><anno>Map1</anno></c> or <c><anno>Map2</anno></c> is not a
+ map.</p>
+ <p><em>Example:</em></p>
+ <code type="none">
+> Map1 = #{a => "value_one", b => "value_two"},
+ Map2 = #{a => 1, c => 2},
+ maps:intersect(Map1,Map2).
+#{a => 1}</code>
+ </desc>
+ </func>
+
+ <func>
+ <name name="intersect_with" arity="3" since="OTP 24.0"/>
+ <fsummary></fsummary>
+ <desc>
+ <p>Intersects two maps into a single map
+ <c><anno>Map3</anno></c>. If a key exists in both maps, the
+ value in <c><anno>Map1</anno></c> is combined with the value
+ in <c><anno>Map2</anno></c> by the
+ <c><anno>Combiner</anno></c> fun. When
+ <c><anno>Combiner</anno></c> is applied the key that exists in
+ both maps is the first parameter, the value from
+ <c><anno>Map1</anno></c> is the second parameter, and the value
+ from <c><anno>Map2</anno></c> is the third parameter.</p>
+ <p>The call fails with a <c>{badmap,Map}</c> exception if
+ <c><anno>Map1</anno></c> or <c><anno>Map2</anno></c> is not a
+ map. The call fails with a <c>badarg</c> exception if
+ <c><anno>Combiner</anno></c> is not a fun that takes three
+ arguments.</p>
+ <p><em>Example:</em></p>
+ <code type="none">
+> Map1 = #{a => "value_one", b => "value_two"},
+ Map2 = #{a => 1, c => 2},
+ maps:intersect_with(fun(_Key, Value1, Value2) -> {Value1, Value2} end, Map1, Map2).
+#{a => {"value_one",1}}</code>
+ </desc>
+ </func>
+
<func>
<name name="is_key" arity="2" since="OTP 17.0"/>
<fsummary></fsummary>
@@ -276,6 +323,33 @@ none</code>
</desc>
</func>
+ <func>
+ <name name="merge_with" arity="3" since="OTP 24.0"/>
+ <fsummary></fsummary>
+ <desc>
+ <p>Merges two maps into a single map
+ <c><anno>Map3</anno></c>. If a key exists in both maps, the
+ value in <c><anno>Map1</anno></c> is combined with the value
+ in <c><anno>Map2</anno></c> by the
+ <c><anno>Combiner</anno></c> fun. When
+ <c><anno>Combiner</anno></c> is applied the key that exists in
+ both maps is the first parameter, the value from
+ <c><anno>Map1</anno></c> is the second parameter, and the value
+ from <c><anno>Map2</anno></c> is the third parameter.</p>
+ <p>The call fails with a <c>{badmap,Map}</c> exception if
+ <c><anno>Map1</anno></c> or <c><anno>Map2</anno></c> is not a
+ map. The call fails with a <c>badarg</c> exception if
+ <c><anno>Combiner</anno></c> is not a fun that takes three
+ arguments.</p>
+ <p><em>Example:</em></p>
+ <code type="none">
+> Map1 = #{a => "value_one", b => "value_two"},
+ Map2 = #{a => 1, c => 2},
+ maps:merge_with(fun(_Key, Value1, Value2) -> {Value1, Value2} end, Map1, Map2).
+#{a => {"value_one",1},b => "value_two",c => 2}</code>
+ </desc>
+ </func>
+
<func>
<name name="new" arity="0" since="OTP 17.0"/>
<fsummary></fsummary>
diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl
index 49d6a12eb2..1f2b774eb9 100644
--- a/lib/stdlib/src/maps.erl
+++ b/lib/stdlib/src/maps.erl
@@ -24,7 +24,9 @@
map/2, size/1, new/0,
update_with/3, update_with/4,
without/2, with/2,
- iterator/1, next/1]).
+ iterator/1, next/1,
+ intersect/2, intersect_with/3,
+ merge_with/3]).
%% BIFs
-export([get/2, find/2, from_list/1,
@@ -65,6 +67,58 @@ find(_,_) -> erlang:nif_error(undef).
from_list(_) -> erlang:nif_error(undef).
+-spec intersect(Map1,Map2) -> Map3 when
+ Map1 :: #{Key => term()},
+ Map2 :: #{term() => Value2},
+ Map3 :: #{Key => Value2}.
+
+intersect(Map1, Map2) when is_map(Map1), is_map(Map2) ->
+ intersect_with(fun intersect_combiner/3, Map1,Map2);
+intersect(Map1, Map2) ->
+ erlang:error(error_type_two_maps(Map1, Map2),
+ [Map1,Map2]).
+
+intersect_combiner(_K, _V1, V2) ->
+ V2.
+
+-spec intersect_with(Combiner, Map1, Map2) -> Map3 when
+ Map1 :: #{Key => Value1},
+ Map2 :: #{term() => Value2},
+ Combiner :: fun((Key, Value1, Value2) -> CombineResult),
+ Map3 :: #{Key => CombineResult}.
+
+intersect_with(Combiner, Map1, Map2) when is_map(Map1),
+ is_map(Map2),
+ is_function(Combiner, 3) ->
+ case map_size(Map1) < map_size(Map2) of
+ true ->
+ Iterator = maps:iterator(Map1),
+ intersect_with_1(maps:next(Iterator),
+ Map1,
+ Map2,
+ Combiner);
+ false ->
+ Iterator = maps:iterator(Map2),
+ intersect_with_1(maps:next(Iterator),
+ Map2,
+ Map1,
+ fun(K, V1, V2) -> Combiner(K, V2, V1) end)
+ end;
+intersect_with(Combiner, Map1, Map2) ->
+ error(error_type_merge_intersect(Map1, Map2, Combiner),
+ [Combiner, Map1, Map2]).
+
+intersect_with_1({K, V1, Iterator}, Map1, Map2, Combiner) ->
+ case Map2 of
+ #{ K := V2 } ->
+ NewMap1 = Map1#{ K := Combiner(K, V1, V2) },
+ intersect_with_1(maps:next(Iterator), NewMap1, Map2, Combiner);
+ _ ->
+ intersect_with_1(maps:next(Iterator), maps:remove(K, Map1), Map2, Combiner)
+ end;
+intersect_with_1(none, Res, _, _) ->
+ Res.
+
%% Shadowed by erl_bif_types: maps:is_key/2
-spec is_key(Key,Map) -> boolean() when
@@ -89,6 +143,44 @@ keys(_) -> erlang:nif_error(undef).
merge(_,_) -> erlang:nif_error(undef).
+-spec merge_with(Combiner, Map1, Map2) -> Map3 when
+ Map1 :: #{Key1 => Value1},
+ Map2 :: #{Key2 => Value2},
+ Combiner :: fun((Key1, Value1, Value2) -> CombineResult),
+ Map3 :: #{Key1 => CombineResult, Key1 => Value1, Key2 => Value2}.
+
+merge_with(Combiner, Map1, Map2) when is_map(Map1),
+ is_map(Map2),
+ is_function(Combiner, 3) ->
+ case map_size(Map1) > map_size(Map2) of
+ true ->
+ Iterator = maps:iterator(Map2),
+ merge_with_1(maps:next(Iterator),
+ Map1,
+ Map2,
+ Combiner);
+ false ->
+ Iterator = maps:iterator(Map1),
+ merge_with_1(maps:next(Iterator),
+ Map2,
+ Map1,
+ fun(K, V1, V2) -> Combiner(K, V2, V1) end)
+ end;
+merge_with(Combiner, Map1, Map2) ->
+ erlang:error(error_type_merge_intersect(Map1, Map2, Combiner),
+ [Combiner, Map1, Map2]).
+
+merge_with_1({K, V2, Iterator}, Map1, Map2, Combiner) ->
+ case Map1 of
+ #{ K := V1 } ->
+ NewMap1 = Map1#{ K := Combiner(K, V1, V2) },
+ merge_with_1(maps:next(Iterator), NewMap1, Map2, Combiner);
+ #{ } ->
+ merge_with_1(maps:next(Iterator), maps:put(K, V2, Map1), Map2, Combiner)
+ end;
+merge_with_1(none, Result, _, _) ->
+ Result.
+
%% Shadowed by erl_bif_types: maps:put/3
-spec put(Key,Value,Map1) -> Map2 when
@@ -315,3 +407,13 @@ error_type(V) -> {badmap, V}.
error_type_iter(M) when is_map(M); ?IS_ITERATOR(M) -> badarg;
error_type_iter(V) -> {badmap, V}.
+
+error_type_two_maps(M1, M2) when is_map(M1) ->
+ {badmap, M2};
+error_type_two_maps(M1, _M2) ->
+ {badmap, M1}.
+
+error_type_merge_intersect(M1, M2, Combiner) when is_function(Combiner, 3) ->
+ error_type_two_maps(M1, M2);
+error_type_merge_intersect(_M1, _M2, _Combiner) ->
+ badarg.
diff --git a/lib/stdlib/test/maps_SUITE.erl b/lib/stdlib/test/maps_SUITE.erl
index 9f96336b37..3d5b0d7465 100644
--- a/lib/stdlib/test/maps_SUITE.erl
+++ b/lib/stdlib/test/maps_SUITE.erl
@@ -31,7 +31,9 @@
t_get_3/1, t_filter_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]).
+ t_with_2/1,t_without_2/1,
+ t_intersect/1, t_intersect_with/1,
+ t_merge_with/1]).
%%-define(badmap(V,F,Args), {'EXIT', {{badmap,V}, [{maps,F,Args,_}|_]}}).
%%-define(badarg(F,Args), {'EXIT', {badarg, [{maps,F,Args,_}|_]}}).
@@ -49,7 +51,9 @@ all() ->
t_get_3,t_filter_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].
+ t_with_2,t_without_2,
+ t_intersect, t_intersect_with,
+ t_merge_with].
t_update_with_3(Config) when is_list(Config) ->
V1 = value1,
@@ -226,6 +230,239 @@ t_merge_opt(Config) when is_list(Config) ->
ok.
+random_map(SizeConstant, InitSeed) ->
+ {Ret, _} =
+ lists:foldl(
+ fun(_, {Map, Seed}) ->
+ rand:uniform_s(Seed),
+ {K, Seed2} = rand:uniform_s(SizeConstant, Seed),
+ {V, Seed3} = rand:uniform_s(SizeConstant*100, Seed2),
+ {Map#{K => V}, Seed3}
+ end,
+ {#{}, rand:seed_s(exsss, SizeConstant + InitSeed)},
+ lists:seq(1, SizeConstant)),
+ Ret.
+
+check_map_combiners_same_small(MapCombiner1, MapCombiner2, Seed) ->
+ lists:foreach(
+ fun(SizeConstant) ->
+ lists:foreach(
+ fun(SeedMult) ->
+ RandMap1 = random_map(SizeConstant,
+ SizeConstant + 100000*SeedMult + Seed),
+ RandMap2 = random_map(SizeConstant,
+ SizeConstant + 200000*SeedMult + Seed),
+ Comb1Res = MapCombiner1(RandMap1, RandMap2),
+ Comb2Res = MapCombiner2(RandMap1, RandMap2),
+ Comb1Res = Comb2Res
+ end,
+ lists:seq(1,100))
+
+ end,
+ lists:seq(1,10)).
+
+
+check_map_combiners_same_large(MapCombiner1, MapCombiner2, Seed) ->
+ lists:foreach(
+ fun(SizeConstant) ->
+ RandMap1 = random_map(SizeConstant, SizeConstant + Seed),
+ RandMap2 = random_map(SizeConstant, SizeConstant + Seed),
+ Comb1Res = MapCombiner1(RandMap1, RandMap2),
+ Comb2Res = MapCombiner2(RandMap1, RandMap2),
+ Comb1Res = Comb2Res
+ end,
+ [1000, 10000]),
+ ok.
+
+t_merge_with(Config) when is_list(Config) ->
+ Small = #{1 => 1, 2 => 3},
+ Large = #{1 => 3, 2 => 2, 10=>10},
+ #{1 := {1,3}, 2 := {3,2}, 10 := 10} =
+ maps:merge_with(fun(1, 1, 3) -> {1, 3};
+ (2, 3, 2) -> {3, 2}
+ end,
+ Small,
+ Large),
+
+ %% Swapping input maps should reverse tuples
+
+ #{1 := {3,1}, 2 := {2,3}, 10 := 10} =
+ maps:merge_with(fun(1, V1, V2) -> {V1, V2};
+ (2, V1, V2) -> {V1, V2}
+ end,
+ Large,
+ Small),
+
+ %% Swapping parameters in the output of the fun should also reverse
+ %% tuples
+
+ #{1 := {3,1}, 2 := {2,3}, 10 := 10} =
+ maps:merge_with(fun(1, V1, V2) -> {V2, V1};
+ (2, V1, V2) -> {V2, V1}
+ end,
+ Small,
+ Large),
+
+ %% Should give the same result as maps:merge/2 with the right combiner
+
+ DefaultCombiner = fun(_, _, V2) -> V2 end,
+ Merge2FromMerge3 = fun (M1, M2) -> maps:merge_with(DefaultCombiner, M1, M2) end,
+ check_map_combiners_same_small(fun maps:merge/2, Merge2FromMerge3, 1),
+ check_map_combiners_same_large(fun maps:merge/2, Merge2FromMerge3, 2),
+
+ %% Should conceptually compute the same thing as
+ %% lists:ukey_merge/2 with the right combiner
+
+ MergeFromUKeyMerge =
+ fun(M1, M2) ->
+ L1 = lists:sort(maps:to_list(M1)),
+ L2 = lists:sort(maps:to_list(M2)),
+ %% ukeymerge takes from the first when collision
+ ResList = lists:ukeymerge(1, L2, L1),
+ maps:from_list(ResList)
+ end,
+ check_map_combiners_same_small(MergeFromUKeyMerge, Merge2FromMerge3, 3),
+ check_map_combiners_same_large(MergeFromUKeyMerge, Merge2FromMerge3, 4),
+
+ %% Empty maps
+
+ Large = maps:merge_with(fun(_K, _V1, _V2) -> error(should_not_happen) end,
+ Large,
+ #{}),
+ Large = maps:merge_with(fun(_K, _V1, _V2) -> error(should_not_happen) end,
+ #{},
+ Large),
+ #{} = maps:merge_with(fun(_K, _V1, _V2) -> error(should_not_happen) end,
+ #{},
+ #{}),
+
+ %% Errors
+
+ {'EXIT', {badarg, _}} =
+ (catch maps:merge_with(not_a_fun,#{},#{})),
+ {'EXIT', {{badmap, a}, _}} =
+ (catch maps:merge_with(fun(_K, _V1, _V2) -> error(should_not_happen) end, a, #{})),
+ {'EXIT', {{badmap, b}, _}} =
+ (catch maps:merge_with(fun(_K, _V1, _V2) -> error(ok) end, #{}, b)),
+ {'EXIT', {{badmap, a}, _}} =
+ (catch maps:merge_with(fun(_K, _V1, _V2) -> error(ok) end, a, b)),
+ ok.
+
+t_intersect(Config) when is_list(Config) ->
+ Small = #{1 => 1, 2 => 3},
+ Large = #{1 => 3, 2 => 2, 10=>10},
+ #{1 := 3,2 := 2} = maps:intersect(Small, Large),
+
+ %% Swapping input maps can make a difference
+
+ #{1 := 1, 2 := 3} = maps:intersect(Large, Small),
+
+ %% Should conceptually compute the same thing as
+ %% gb_sets:intersect/2 with the right combiner
+
+ IntersectFromGBSets =
+ fun(M1, M2) ->
+ Map1Keys = maps:keys(M1),
+ Map2Keys = maps:keys(M2),
+ GBSet1 = gb_sets:from_list(Map1Keys),
+ GBSet2 = gb_sets:from_list(Map2Keys),
+ GBSetIntersection = gb_sets:intersection(GBSet1, GBSet2),
+ IntersectList = gb_sets:to_list(GBSetIntersection),
+ lists:foldl(
+ fun(Key, SoFar) ->
+ SoFar#{Key => maps:get(Key, M2)}
+ end,
+ #{},
+ IntersectList)
+ end,
+ check_map_combiners_same_small(fun maps:intersect/2,
+ IntersectFromGBSets,
+ 11),
+ check_map_combiners_same_large(fun maps:intersect/2,
+ IntersectFromGBSets,
+ 13),
+
+ %% Empty maps
+
+ #{} = maps:intersect(Large, #{}),
+ #{} = maps:intersect(#{}, Large),
+ #{} = maps:intersect(#{}, #{}),
+
+ %% Errors
+
+ {'EXIT', {{badmap, a}, _}} =
+ (catch maps:intersect(a, #{})),
+ {'EXIT', {{badmap, b}, _}} =
+ (catch maps:intersect(#{}, b)),
+ {'EXIT', {{badmap, a}, _}} =
+ (catch maps:intersect(a, b)),
+ ok.
+
+t_intersect_with(Config) when is_list(Config) ->
+ Small = #{1 => 1, 2 => 3},
+ Large = #{1 => 3, 2 => 2, 10=>10},
+ #{1 := {1,3}, 2 := {3,2}} =
+ maps:intersect_with(fun(1, 1, 3) -> {1, 3};
+ (2, 3, 2) -> {3, 2}
+ end,
+ Small,
+ Large),
+
+ %% Swapping input maps should reverse tuples
+
+ #{1 := {3,1}, 2 := {2,3}} =
+ maps:intersect_with(fun(1, V1, V2) -> {V1, V2};
+ (2, V1, V2) -> {V1, V2}
+ end,
+ Large,
+ Small),
+
+ %% Swapping parameters in the output of the fun should also reverse
+ %% tuples
+
+ #{1 := {3,1}, 2 := {2,3}} =
+ maps:intersect_with(fun(1, V1, V2) -> {V2, V1};
+ (2, V1, V2) -> {V2, V1}
+ end,
+ Small,
+ Large),
+
+ %% Should give the same result as intersect/2 with the right combiner
+
+ DefaultCombiner = fun(_, _, V2) -> V2 end,
+ Intersect2FromIntersect3 =
+ fun (M1, M2) -> maps:intersect_with(DefaultCombiner, M1, M2) end,
+ check_map_combiners_same_small(fun maps:intersect/2,
+ Intersect2FromIntersect3,
+ 7),
+ check_map_combiners_same_large(fun maps:intersect/2,
+ Intersect2FromIntersect3,
+ 8),
+
+ %% Empty maps
+
+ #{} = maps:intersect_with(fun(_K, _V1, _V2) -> error(should_not_happen) end,
+ Large,
+ #{}),
+ #{} = maps:intersect_with(fun(_K, _V1, _V2) -> error(should_not_happen) end,
+ #{},
+ Large),
+ #{} = maps:intersect_with(fun(_K, _V1, _V2) -> error(should_not_happen) end,
+ #{},
+ #{}),
+
+ %% Errors
+
+ {'EXIT', {badarg, _}} =
+ (catch maps:intersect_with(not_a_fun,#{},#{})),
+ {'EXIT', {{badmap, a}, _}} =
+ (catch maps:intersect_with(fun(_K, _V1, _V2) -> error(should_not_happen) end, a, #{})),
+ {'EXIT', {{badmap, b}, _}} =
+ (catch maps:intersect_with(fun(_K, _V1, _V2) -> error(ok) end, #{}, b)),
+ {'EXIT', {{badmap, a}, _}} =
+ (catch maps:intersect_with(fun(_K, _V1, _V2) -> error(ok) end, a, b)),
+ ok.
+
t_size_1(Config) when is_list(Config) ->
0 = maps:size(#{}),
10 = maps:size(maps:from_list([{{"k",I},I}||I<-lists:seq(1,10)])),
--
2.26.2