Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
Please login to access the resource
home:Ledest:erlang:24
erlang
6561-Add-equality-check-functions-to-sets-ordse...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 6561-Add-equality-check-functions-to-sets-ordsets-and-gb_.patch of Package erlang
From 41544381428927c2c6e892e75173f1f4add4ff6b Mon Sep 17 00:00:00 2001 From: Jan Uhlig <juhlig@hnc-agency.org> Date: Wed, 7 Jun 2023 14:57:37 +0200 Subject: [PATCH] Add equality check functions to sets, ordsets and gb_sets MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Co-authored-by: Maria Scott <maria-12648430@hnc-agency.org> Co-authored-by: Björn Gustavsson <bgustavsson@gmail.com> --- lib/stdlib/doc/src/gb_sets.xml | 11 +++++ lib/stdlib/doc/src/ordsets.xml | 11 +++++ lib/stdlib/doc/src/sets.xml | 13 ++++++ lib/stdlib/src/gb_sets.erl | 37 ++++++++++++--- lib/stdlib/src/ordsets.erl | 12 ++++- lib/stdlib/src/sets.erl | 21 ++++++++- lib/stdlib/test/sets_SUITE.erl | 75 +++++++++++++++++++------------ lib/stdlib/test/sets_test_lib.erl | 8 +++- 8 files changed, 150 insertions(+), 38 deletions(-) diff --git a/lib/stdlib/doc/src/gb_sets.xml b/lib/stdlib/doc/src/gb_sets.xml index 4107ba0c63..d8271f9608 100644 --- a/lib/stdlib/doc/src/gb_sets.xml +++ b/lib/stdlib/doc/src/gb_sets.xml @@ -270,6 +270,17 @@ </desc> </func> + <func> + <name name="is_equal" arity="2" since="OTP 26.1"/> + <fsummary>Test for equality.</fsummary> + <desc> + <p>Returns <c>true</c> if <c><anno>Set1</anno></c> and + <c><anno>Set2</anno></c> are equal, that is when every element of + one set is also a member of the respective other set, otherwise + <c>false</c>.</p> + </desc> + </func> + <func> <name name="is_member" arity="2" since=""/> <fsummary>Test for membership of a set.</fsummary> diff --git a/lib/stdlib/doc/src/ordsets.xml b/lib/stdlib/doc/src/ordsets.xml index 0026377f73..b7575ea31b 100644 --- a/lib/stdlib/doc/src/ordsets.xml +++ b/lib/stdlib/doc/src/ordsets.xml @@ -164,6 +164,17 @@ </desc> </func> + <func> + <name name="is_equal" arity="2" since="OTP 26.1"/> + <fsummary>Test for equality.</fsummary> + <desc> + <p>Returns <c>true</c> if <c><anno>Ordset1</anno></c> and + <c><anno>Ordset2</anno></c> are equal, that is when every element of + one set is also a member of the respective other set, otherwise + <c>false</c>.</p> + </desc> + </func> + <func> <name name="is_set" arity="1" since=""/> <fsummary>Test for an <c>Ordset</c>.</fsummary> diff --git a/lib/stdlib/doc/src/sets.xml b/lib/stdlib/doc/src/sets.xml index 4465172848..45a8959556 100644 --- a/lib/stdlib/doc/src/sets.xml +++ b/lib/stdlib/doc/src/sets.xml @@ -98,6 +98,8 @@ </item> <item><seemfa marker="#is_empty/1"><c>is_empty/1</c></seemfa> </item> + <item><seemfa marker="#is_equal/2"><c>is_equal/2</c></seemfa> + </item> <item><seemfa marker="#is_set/1"><c>is_set/1</c></seemfa> </item> <item><seemfa marker="#is_subset/2"><c>is_subset/2</c></seemfa> @@ -257,6 +259,17 @@ true</pre> </desc> </func> + <func> + <name name="is_equal" arity="2" since="OTP 26.1"/> + <fsummary>Test for equality.</fsummary> + <desc> + <p>Returns <c>true</c> if <c><anno>Set1</anno></c> and + <c><anno>Set2</anno></c> are equal, that is when every element of + one set is also a member of the respective other set, otherwise + <c>false</c>.</p> + </desc> + </func> + <func> <name name="is_set" arity="1" since=""/> <fsummary>Test for a <c>Set</c>.</fsummary> diff --git a/lib/stdlib/src/gb_sets.erl b/lib/stdlib/src/gb_sets.erl index 217dff2b3c..f94996a669 100644 --- a/lib/stdlib/src/gb_sets.erl +++ b/lib/stdlib/src/gb_sets.erl @@ -153,11 +153,12 @@ -export([empty/0, is_empty/1, size/1, singleton/1, is_member/2, insert/2, add/2, delete/2, delete_any/2, balance/1, union/2, - union/1, intersection/2, intersection/1, is_disjoint/2, difference/2, - is_subset/2, to_list/1, from_list/1, from_ordset/1, smallest/1, - largest/1, take_smallest/1, take_largest/1, iterator/1, - iterator_from/2, next/1, filter/2, fold/3, map/2, filtermap/2, - is_set/1]). + union/1, intersection/2, intersection/1, is_equal/2, + is_disjoint/2, difference/2, is_subset/2, to_list/1, + from_list/1, from_ordset/1, smallest/1, largest/1, + take_smallest/1, take_largest/1, iterator/1, + iterator_from/2, next/1, filter/2, fold/3, map/2, + filtermap/2, is_set/1]). %% `sets' compatibility aliases: @@ -230,6 +231,32 @@ is_empty(_) -> size({Size, _}) -> Size. +-spec is_equal(Set1, Set2) -> boolean() when + Set1 :: set(), + Set2 :: set(). + +is_equal({Size, S1}, {Size, _} = S2) -> + try is_equal_1(S1, to_list(S2)) of + [] -> + true + catch + throw:not_equal -> + false + end; +is_equal({_, _}, {_, _}) -> + false. + +is_equal_1(nil, Keys) -> + Keys; +is_equal_1({Key1, Smaller, Bigger}, Keys0) -> + [Key2 | Keys] = is_equal_1(Smaller, Keys0), + if + Key1 == Key2 -> + is_equal_1(Bigger, Keys); + true -> + throw(not_equal) + end. + -spec singleton(Element) -> set(Element). singleton(Key) -> diff --git a/lib/stdlib/src/ordsets.erl b/lib/stdlib/src/ordsets.erl index bad539c9f4..2001a1338b 100644 --- a/lib/stdlib/src/ordsets.erl +++ b/lib/stdlib/src/ordsets.erl @@ -22,7 +22,7 @@ -export([new/0,is_set/1,size/1,is_empty/1,to_list/1,from_list/1]). -export([is_element/2,add_element/2,del_element/2]). -export([union/2,union/1,intersection/2,intersection/1]). --export([is_disjoint/2]). +-export([is_equal/2, is_disjoint/2]). -export([subtract/2,is_subset/2]). -export([fold/3,filter/2,map/2,filtermap/2]). @@ -67,6 +67,16 @@ size(S) -> length(S). is_empty(S) -> S=:=[]. +%% is_equal(OrdSet1, OrdSet2) -> boolean(). +%% Return 'true' if OrdSet1 and OrdSet2 contain the same elements, +%% otherwise 'false'. +-spec is_equal(Ordset1, Ordset2) -> boolean() when + Ordset1 :: ordset(_), + Ordset2 :: ordset(_). + +is_equal(S1, S2) when is_list(S1), is_list(S2) -> + S1 == S2. + %% to_list(OrdSet) -> [Elem]. %% Return the elements in OrdSet as a list. diff --git a/lib/stdlib/src/sets.erl b/lib/stdlib/src/sets.erl index 27e6038f67..5cf42560fc 100644 --- a/lib/stdlib/src/sets.erl +++ b/lib/stdlib/src/sets.erl @@ -44,7 +44,7 @@ -export([new/0,is_set/1,size/1,is_empty/1,to_list/1,from_list/1]). -export([is_element/2,add_element/2,del_element/2]). -export([union/2,union/1,intersection/2,intersection/1]). --export([is_disjoint/2]). +-export([is_equal/2, is_disjoint/2]). -export([subtract/2,is_subset/2]). -export([fold/3,filter/2,map/2,filtermap/2]). -export([new/1, from_list/2]). @@ -146,6 +146,22 @@ size(#set{size=Size}) -> Size. is_empty(#{}=S) -> map_size(S)=:=0; is_empty(#set{size=Size}) -> Size=:=0. +%% is_equal(Set1, Set2) -> boolean(). +%% Return 'true' if Set1 and Set2 contain the same elements, +%% otherwise 'false'. +-spec is_equal(Set1, Set2) -> boolean() when + Set1 :: set(), + Set2 :: set(). +is_equal(S1, S2) -> + case size(S1) =:= size(S2) of + true when S1 =:= S2 -> + true; + true -> + is_subset(S1, S2); + false -> + false + end. + %% to_list(Set) -> [Elem]. %% Return the elements in Set as a list. -spec to_list(Set) -> List when diff --git a/lib/stdlib/test/sets_SUITE.erl b/lib/stdlib/test/sets_SUITE.erl index ea0b8c32b0..b7bbaa96c7 100644 --- a/lib/stdlib/test/sets_SUITE.erl +++ b/lib/stdlib/test/sets_SUITE.erl @@ -28,8 +28,8 @@ init_per_testcase/2,end_per_testcase/2, create/1,add_element/1,del_element/1, subtract/1,intersection/1,union/1,is_subset/1, - is_disjoint/1,is_set/1,is_empty/1,fold/1,filter/1, map/1, - filtermap/1, take_smallest/1,take_largest/1, iterate/1]). + is_equal/1, is_disjoint/1,is_set/1,is_empty/1,fold/1,filter/1, + map/1, filtermap/1, take_smallest/1,take_largest/1, iterate/1]). -include_lib("common_test/include/ct.hrl"). @@ -49,7 +49,7 @@ all() -> [create, add_element, del_element, subtract, intersection, union, is_subset, is_set, fold, filter, map, filtermap, take_smallest, take_largest, iterate, is_empty, - is_disjoint]. + is_disjoint, is_equal]. groups() -> []. @@ -94,13 +94,13 @@ add_element_1(List, M) -> %% elements one at the time. S2 = foldl(fun(El, Set) -> M(add_element, {El,Set}) end, M(empty, []), List), - true = M(equal, {S,S2}), + true = M(is_equal, {S,S2}), %% Insert elements, randomly delete inserted elements, %% and re-inserted all deleted elements at the end. S3 = add_element_del(List, M, M(empty, []), [], []), - true = M(equal, {S2,S3}), - true = M(equal, {S,S3}), + true = M(is_equal, {S2,S3}), + true = M(is_equal, {S,S3}), S. add_element_del([H|T], M, S, Del, []) -> @@ -124,12 +124,12 @@ del_element(Config) when is_list(Config) -> del_element_1(List, M) -> S0 = M(from_list, List), Empty = foldl(fun(El, Set) -> M(del_element, {El,Set}) end, S0, List), - true = M(equal, {Empty,M(empty, [])}), + true = M(is_equal, {Empty,M(empty, [])}), true = M(is_empty, Empty), S1 = foldl(fun(El, Set) -> M(add_element, {El,Set}) end, S0, reverse(List)), - true = M(equal, {S0,S1}), + true = M(is_equal, {S0,S1}), S1. subtract(Config) when is_list(Config) -> @@ -149,7 +149,7 @@ subtract_1(List, M) -> %% Trivial cases. true = M(is_empty, M(subtract, {Empty,S0})), - true = M(equal, {S0,M(subtract, {S0,Empty})}), + true = M(is_equal, {S0,M(subtract, {S0,Empty})}), %% Not so trivial. subtract_check(List, mutate_some(remove_some(List, 0.4)), M), @@ -168,7 +168,7 @@ one_subtract_check(A, B, M) -> BSet = M(from_list, B), DiffSet = M(subtract, {ASet,BSet}), Diff = ASorted -- BSorted, - true = M(equal, {DiffSet,M(from_list, Diff)}), + true = M(is_equal, {DiffSet,M(from_list, Diff)}), Diff = lists:sort(M(to_list, DiffSet)), DiffSet. @@ -180,15 +180,15 @@ intersection_1(List, M) -> S0 = M(from_list, List), %% Intersection with self. - true = M(equal, {S0,M(intersection, {S0,S0})}), - true = M(equal, {S0,M(intersection, [S0,S0])}), - true = M(equal, {S0,M(intersection, [S0,S0,S0])}), - true = M(equal, {S0,M(intersection, [S0])}), + true = M(is_equal, {S0,M(intersection, {S0,S0})}), + true = M(is_equal, {S0,M(intersection, [S0,S0])}), + true = M(is_equal, {S0,M(intersection, [S0,S0,S0])}), + true = M(is_equal, {S0,M(intersection, [S0])}), %% Intersection with empty. Empty = M(empty, []), - true = M(equal, {Empty,M(intersection, {S0,Empty})}), - true = M(equal, {Empty,M(intersection, [S0,Empty,S0,Empty])}), + true = M(is_equal, {Empty,M(intersection, {S0,Empty})}), + true = M(is_equal, {Empty,M(intersection, [S0,Empty,S0,Empty])}), %% The intersection of no sets is undefined. {'EXIT',_} = (catch M(intersection, [])), @@ -229,7 +229,7 @@ check_intersection(Orig, Mutated, M) -> Intersection = [El || El <- Mutated, not is_tuple(El)], SortedIntersection = lists:usort(Intersection), IntersectionSet = M(intersection, {OrigSet,MutatedSet}), - true = M(equal, {IntersectionSet,M(from_list, SortedIntersection)}), + true = M(is_equal, {IntersectionSet,M(from_list, SortedIntersection)}), SortedIntersection = lists:sort(M(to_list, IntersectionSet)), IntersectionSet. @@ -244,12 +244,12 @@ union_1(List, M) -> %% Union with self and empty. Empty = M(empty, []), - true = M(equal, {S,M(union, {S,S})}), - true = M(equal, {S,M(union, [S,S])}), - true = M(equal, {S,M(union, [S,S,Empty])}), - true = M(equal, {S,M(union, [S,Empty,S])}), - true = M(equal, {S,M(union, {S,Empty})}), - true = M(equal, {S,M(union, [S])}), + true = M(is_equal, {S,M(union, {S,S})}), + true = M(is_equal, {S,M(union, [S,S])}), + true = M(is_equal, {S,M(union, [S,S,Empty])}), + true = M(is_equal, {S,M(union, [S,Empty,S])}), + true = M(is_equal, {S,M(union, {S,Empty})}), + true = M(is_equal, {S,M(union, [S])}), true = M(is_empty, M(union, [])), %% Partial overlap. @@ -272,9 +272,26 @@ check_union(Orig, Other, M) -> SortedUnion = lists:usort(Union), UnionSet = M(union, {OrigSet,OtherSet}), SortedUnion = lists:sort(M(to_list, UnionSet)), - M(equal, {UnionSet,M(from_list, Union)}), + M(is_equal, {UnionSet,M(from_list, Union)}), UnionSet. +is_equal(Config) when is_list(Config) -> + test_all([{1,132},{253,270},{299,311}], fun is_equal_1/2). + +is_equal_1(List, M) -> + S = M(from_list, List), + Empty = M(empty, []), + + true = M(is_equal, {Empty, Empty}), + false = M(is_equal, {Empty, S}) andalso List =/= [], + false = M(is_equal, {S, Empty}) andalso List =/= [], + true = M(is_equal, {S, S}), + + S1 = M(from_list, [make_ref()|List]), + false = M(is_equal, {S, S1}), + + S. + is_subset(Config) when is_list(Config) -> test_all([{1,132},{253,270},{299,311}], fun is_subset_1/2). @@ -390,7 +407,7 @@ filter(Config) when is_list(Config) -> filter_1(List, M) -> S = M(from_list, List), IsNumber = fun(X) -> is_number(X) end, - M(equal, {M(from_list, lists:filter(IsNumber, List)), + M(is_equal, {M(from_list, lists:filter(IsNumber, List)), M(filter, {IsNumber,S})}), M(filter, {fun(X) -> is_atom(X) end,S}). @@ -401,8 +418,8 @@ map(Config) when is_list(Config) -> map_1(List, M) -> S = M(from_list, List), ToTuple = fun(X) -> {X} end, - M(equal, {M(from_list, lists:map(ToTuple, List)), - M(map, {ToTuple, S})}), + M(is_equal, {M(from_list, lists:map(ToTuple, List)), + M(map, {ToTuple, S})}), M(map, {fun(_) -> x end, S}). filtermap(Config) when is_list(Config) -> @@ -416,8 +433,8 @@ filtermap_1(List, M) -> (X) when is_integer(X) -> true; (X) -> {true, {X}} end, - M(equal, {M(from_list, lists:filtermap(FMFun, List)), - M(filtermap, {FMFun, S})}), + M(is_equal, {M(from_list, lists:filtermap(FMFun, List)), + M(filtermap, {FMFun, S})}), M(empty, []). %%% diff --git a/lib/stdlib/test/sets_test_lib.erl b/lib/stdlib/test/sets_test_lib.erl index 340dd9b1f2..5c1811aecb 100644 --- a/lib/stdlib/test/sets_test_lib.erl +++ b/lib/stdlib/test/sets_test_lib.erl @@ -25,17 +25,21 @@ new(Mod, Eq) -> new(Mod, Eq, fun Mod:new/0, fun Mod:from_list/1). -new(Mod, Eq, New, FromList) -> +new(Mod, Eq0, New, FromList) -> + Eq = fun(S1, S2) -> + IsEqual = Eq0(S1, S2), + IsEqual = Mod:is_equal(S1, S2) + end, fun (add_element, {El,S}) -> add_element(Mod, El, S); (del_element, {El,S}) -> del_element(Mod, El, S); (empty, []) -> New(); - (equal, {S1,S2}) -> Eq(S1, S2); (filter, {F,S}) -> filter(Mod, F, S); (filtermap, {F,S}) -> filtermap(Mod, F, S); (fold, {F,A,S}) -> fold(Mod, F, A, S); (from_list, L) -> FromList(L); (intersection, {S1,S2}) -> intersection(Mod, Eq, S1, S2); (intersection, Ss) -> intersection(Mod, Eq, Ss); + (is_equal, {S,Set}) -> Eq(S, Set); (is_disjoint, {S,Set}) -> Mod:is_disjoint(S, Set); (is_empty, S) -> Mod:is_empty(S); (is_set, S) -> Mod:is_set(S); -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor