-
Notifications
You must be signed in to change notification settings - Fork 3k
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Property-based tests for the sets module
- Loading branch information
1 parent
2c864f2
commit 40f058a
Showing
3 changed files
with
423 additions
and
0 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,320 @@ | ||
-module(sets_prop). | ||
|
||
-include_lib("common_test/include/ct_property_test.hrl"). | ||
|
||
prop_add_element() -> | ||
?FORALL( | ||
{S1, S2, E}, | ||
?LET( | ||
{L, E}, | ||
{list(), any()}, | ||
begin | ||
LFiltered = lists:filter(fun(X) -> X=/=E end, L), | ||
{gen_set(LFiltered), gen_set([E|LFiltered]), E} | ||
end | ||
), | ||
equal(sets:add_element(E, S1), S2) andalso | ||
equal(sets:add_element(E, S2), S2) | ||
). | ||
|
||
prop_del_element() -> | ||
?FORALL( | ||
{S1, S2, E}, | ||
?LET( | ||
{L, E}, | ||
{list(), any()}, | ||
begin | ||
LFiltered = lists:filter(fun(X) -> X=/=E end, L), | ||
{gen_set([E|LFiltered]), gen_set(LFiltered), E} | ||
end | ||
), | ||
equal(sets:del_element(E, S1), S2) andalso | ||
equal(sets:del_element(E, S2), S2) | ||
). | ||
|
||
prop_filter() -> | ||
?FORALL( | ||
{S1, S2, Fun}, | ||
?LET( | ||
{L, F}, | ||
{list(), function1(boolean())}, | ||
{gen_set(L), gen_set(lists:filter(F, L)), F} | ||
), | ||
equal(sets:filter(Fun, S1), S2) | ||
). | ||
|
||
prop_fold() -> | ||
?FORALL( | ||
{S, Fun, Acc0, R}, | ||
?LET( | ||
{L, F, Acc0}, | ||
{list(), fun(X, Acc) -> Acc + erlang:phash2(X) end, integer()}, | ||
{gen_set(L), F, Acc0, lists:foldl(F, Acc0, usort(L))} | ||
), | ||
R =:= sets:fold(Fun, Acc0, S) | ||
). | ||
|
||
prop_list_conversion() -> | ||
?FORALL( | ||
L, | ||
list(), | ||
begin | ||
Sv1 = sets:from_list(L, [{version, 1}]), | ||
Sv2 = sets:from_list(L, [{version, 2}]), | ||
LUSorted = usort(L), | ||
equal(Sv1, Sv2) andalso | ||
lists:all(fun(X) -> | ||
sets:is_element(X, Sv1) andalso | ||
sets:is_element(X, Sv2) | ||
end, | ||
L) andalso | ||
LUSorted =:= sort(sets:to_list(Sv1)) andalso | ||
LUSorted =:= sort(sets:to_list(Sv2)) | ||
end | ||
). | ||
|
||
prop_intersection_1() -> | ||
?FORALL( | ||
{Ss, SExp}, | ||
?LET( | ||
Ls, | ||
list(list()), | ||
{[gen_set(L) || L <- Ls], gen_set(list_intersection(Ls))} | ||
), | ||
try sets:intersection(Ss) of | ||
SR -> equal(SR, SExp) | ||
catch | ||
error:_ -> | ||
Ss =:= [] | ||
end | ||
). | ||
|
||
prop_intersection_2() -> | ||
?FORALL( | ||
{S1, S2, SR}, | ||
?LET( | ||
{L1, L2}, | ||
{list(), list()}, | ||
{gen_set(L1), gen_set(L2), gen_set(list_intersection([L1, L2]))} | ||
), | ||
equal(sets:intersection(S1, S2), SR) | ||
). | ||
|
||
prop_is_disjoint() -> | ||
?FORALL( | ||
{S1, S2, Exp}, | ||
?LET( | ||
{L1, L2, B}, | ||
{list(), list(), list()}, | ||
begin | ||
L1Filtered = usort(L1) -- L2, | ||
L2Filtered = usort(L2) -- L1, | ||
{gen_set(L1Filtered ++ B), gen_set(L2Filtered ++ B), B =:= []} | ||
end | ||
), | ||
Exp =:= sets:is_disjoint(S1, S2) | ||
). | ||
|
||
prop_is_element() -> | ||
?FORALL( | ||
{S1, S2, E}, | ||
?LET( | ||
{L, E}, | ||
{list(), any()}, | ||
begin | ||
LFiltered = lists:filter(fun(X) -> X=/=E end, L), | ||
{gen_set(LFiltered), gen_set([E|LFiltered]), E} | ||
end | ||
), | ||
not sets:is_element(E, S1) andalso | ||
sets:is_element(E, S2) | ||
). | ||
|
||
prop_is_empty() -> | ||
?FORALL( | ||
{S, Exp}, | ||
?LET( | ||
L, | ||
list(), | ||
{gen_set(L), L =:= []} | ||
), | ||
Exp =:= sets:is_empty(S) | ||
). | ||
|
||
prop_is_set() -> | ||
?FORALL( | ||
{Exp, S}, | ||
oneof([{true, gen_set()}, | ||
{false, ?SUCHTHAT(T, | ||
any(), | ||
not (is_map(T) orelse | ||
is_tuple(T) andalso | ||
tuple_size(T)=:=9 andalso | ||
element(1, T)=:=set))}]), | ||
Exp =:= sets:is_set(S) | ||
). | ||
|
||
%% Subset test | ||
%% | ||
%% +-----------------------------+ | ||
%% | S0 +----------------------+ | | ||
%% | | S1 +-------------+ | | | ||
%% | | | S2 | | | | ||
%% | | +----+-----------+ | | | | ||
%% | | | S3 | +-------+ | | | | | ||
%% | | | | | Empty | | | | | | ||
%% | | | | +-------+ | | | | | ||
%% | | | +-----------+-+ | | | ||
%% | | +----------------+ | | | ||
%% | +----------------------+ | | ||
%% +-----------------------------+ | ||
%% * Empty is a subset of S2 and S3 | ||
%% | ||
%% * S2 is a subset of S1 but not of S3 | ||
%% * S3 is a subset of S1 but not of S2 | ||
%% --> Empty is a subset of S1 | ||
%% | ||
%% * S1 is a subset of S0 | ||
%% --> S2, S3 and Empty are subsets of S0 | ||
prop_is_subset() -> | ||
?FORALL( | ||
{S0, S1, S2, S3, Empty}, | ||
?LET( | ||
{L1, L2}, | ||
{list(), list()}, | ||
begin | ||
L3Extra = [make_ref()|L2], | ||
L2Extra = [make_ref()|L1], | ||
L1Extra = [make_ref()|L2Extra ++ L3Extra], | ||
L0Extra = [make_ref()|L1Extra], | ||
{{gen_set(L0Extra, 1), gen_set(L0Extra, 2)}, | ||
{gen_set(L1Extra, 1), gen_set(L1Extra, 2)}, | ||
{gen_set(L2Extra, 1), gen_set(L2Extra, 2)}, | ||
{gen_set(L3Extra, 1), gen_set(L3Extra, 2)}, | ||
{gen_set([], 1), gen_set([], 2)}} | ||
end | ||
), | ||
%% Test all combinations of sets, in both versions | ||
%% | ||
%% S0 contains all the other sets, including itself | ||
subset_1(S0, [{Empty, true}, {S0, true}, {S1, true}, {S2, true}, {S3, true}]) andalso | ||
%% S1 contains all sets except S0, including itself | ||
subset_1(S1, [{Empty, true}, {S0, false}, {S1, true}, {S2, true}, {S3, true}]) andalso | ||
%% S2 contains S2 and Empty, and itself | ||
subset_1(S2, [{Empty, true}, {S0, false}, {S1, false}, {S2, true}, {S3, false}]) andalso | ||
%% S3 contains S2 and Empty, and itself | ||
subset_1(S3, [{Empty, true}, {S0, false}, {S1, false}, {S2, false}, {S3, true}]) andalso | ||
%% Empty contains only itself | ||
subset_1(Empty, [{Empty, true}, {S0, false}, {S1, false}, {S2, false}, {S3, false}]) | ||
). | ||
|
||
subset_1({TopSetV1, TopSetV2}, SubSets) -> | ||
subset_2(TopSetV1, SubSets) andalso | ||
subset_2(TopSetV2, SubSets). | ||
|
||
subset_2(_TopSet, []) -> | ||
true; | ||
subset_2(TopSet, [{{SubSetV1, SubSetV2}, Exp}|SubSets]) -> | ||
Exp =:= sets:is_subset(SubSetV1, TopSet) andalso | ||
Exp =:= sets:is_subset(SubSetV2, TopSet) andalso | ||
subset_2(TopSet, SubSets). | ||
|
||
prop_size() -> | ||
?FORALL( | ||
{S, Size}, | ||
?LET( | ||
L, | ||
list(), | ||
{gen_set(L), length(usort(L))} | ||
), | ||
Size =:= sets:size(S) | ||
). | ||
|
||
prop_subtract() -> | ||
?FORALL( | ||
{S1, S2, SExp}, | ||
?LET( | ||
{L1, L2, B}, | ||
{list(), list(), list()}, | ||
{gen_set(L1 ++ B), gen_set(L2 ++ B), gen_set(usort(L1) -- (L2 ++ B))} | ||
), | ||
equal(sets:subtract(S1, S2), SExp) | ||
). | ||
|
||
prop_union_1() -> | ||
?FORALL( | ||
{Ss, SR}, | ||
?LET( | ||
Ls, | ||
list(list()), | ||
{[gen_set(L) || L <- Ls], gen_set(lists:append(Ls))} | ||
), | ||
equal(sets:union(Ss), SR) | ||
). | ||
|
||
prop_union_2() -> | ||
?FORALL( | ||
{S1, S2, SR}, | ||
?LET( | ||
{L1, L2}, | ||
{list(), list()}, | ||
{gen_set(L1), gen_set(L2), gen_set(L1 ++ L2)} | ||
), | ||
equal(sets:union(S1, S2), SR) | ||
). | ||
|
||
|
||
gen_set() -> | ||
?LET( | ||
{L, V}, | ||
{list(), oneof([1, 2])}, | ||
gen_set(L, V) | ||
). | ||
|
||
gen_set(List) when is_list(List) -> | ||
?LET( | ||
V, | ||
oneof([1, 2]), | ||
gen_set(List, V) | ||
); | ||
gen_set(Version) when is_integer(Version) -> | ||
?LET( | ||
L, | ||
list(), | ||
gen_set(L, Version) | ||
). | ||
|
||
gen_set(List, Version) -> | ||
sets:from_list(List, [{version, Version}]). | ||
|
||
|
||
sort_fun(A, B) when is_float(A), is_integer(B) -> | ||
true; | ||
sort_fun(A, B) when is_integer(A), is_float(B) -> | ||
false; | ||
sort_fun(A, B) -> | ||
A =< B. | ||
|
||
sort(L) -> | ||
lists:sort(fun sort_fun/2, L). | ||
|
||
usort(L) -> | ||
lists:usort(fun sort_fun/2, L). | ||
|
||
equal(S1, S2) -> | ||
sets:is_subset(S1, S2) andalso sets:is_subset(S2, S1). | ||
|
||
list_intersection([]) -> | ||
[]; | ||
list_intersection([L|Ls]) -> | ||
list_intersection(Ls, usort(L)). | ||
|
||
list_intersection([], Acc) -> | ||
Acc; | ||
list_intersection(_Ls, []) -> | ||
[]; | ||
list_intersection([[]|_Ls], _Acc) -> | ||
[]; | ||
list_intersection([L|Ls], Acc) -> | ||
list_intersection(Ls, Acc -- (Acc -- L)). | ||
|
Oops, something went wrong.