Skip to content

Commit

Permalink
Use ct_proper_ext generators
Browse files Browse the repository at this point in the history
  • Loading branch information
Maria-12648430 committed Jun 29, 2023
1 parent 5fb9016 commit 2b1799c
Showing 1 changed file with 40 additions and 24 deletions.
64 changes: 40 additions & 24 deletions lib/stdlib/test/property_test/sets_prop.erl
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,9 @@ subprop_add_element(Mod) ->
{{S0, M0}, Es},
?LET(
{L1, L2, B},
{list(), list(), list()},
{ct_proper_ext:safe_list(),
ct_proper_ext:safe_list(),
ct_proper_ext:safe_list()},
{gen_set(Mod, L1 ++ B), L2 ++ B}
),
begin
Expand All @@ -39,7 +41,9 @@ subprop_del_element(Mod) ->
{{S0, M0}, Es},
?LET(
{L1, L2, B},
{list(), list(), list()},
{ct_proper_ext:safe_list(),
ct_proper_ext:safe_list(),
ct_proper_ext:safe_list()},
{gen_set(Mod, L1 ++ B), L2 ++ B}
),
begin
Expand Down Expand Up @@ -74,7 +78,8 @@ prop_filtermap() ->
subprop_filtermap(Mod) ->
?FORALL(
{{S0, M0}, Fun},
{gen_set(Mod), function1(oneof([true, false, {true, any()}]))},
{gen_set(Mod),
function1(oneof([true, false, {true, ct_proper_ext:safe_any()}]))},
is_equal(Mod:filtermap(Fun, S0),
model_filtermap(Fun, M0))
).
Expand Down Expand Up @@ -102,14 +107,14 @@ prop_from_list() ->
subprop_from_list(sets) ->
?FORALL(
{L, V},
{list(), gen_version()},
{ct_proper_ext:safe_list(), gen_version()},
is_equal(sets:from_list(L, [{version, V}]),
model_from_list(sets, L))
);
subprop_from_list(Mod) ->
?FORALL(
L,
list(),
ct_proper_ext:safe_list(),
is_equal(Mod:from_list(L),
model_from_list(Mod, L))
).
Expand All @@ -124,7 +129,8 @@ subprop_intersection_1(Mod) ->
SMs,
?LET(
{Ls, A},
{non_empty(list(list())), list()},
{non_empty(list(ct_proper_ext:safe_list())),
ct_proper_ext:safe_list()},
[gen_set(Mod, L ++ A) || L <- Ls]
),
begin
Expand All @@ -144,7 +150,9 @@ subprop_intersection_2(Mod) ->
{{S1, M1}, {S2, M2}},
?LET(
{L1, L2, B},
{list(), list(), list()},
{ct_proper_ext:safe_list(),
ct_proper_ext:safe_list(),
ct_proper_ext:safe_list()},
{gen_set(Mod, L1 ++ B), gen_set(Mod, L2 ++ B)}
),
is_equal(Mod:intersection(S1, S2),
Expand All @@ -161,7 +169,9 @@ subprop_is_disjoint(Mod) ->
{{S1, M1}, {S2, M2}},
?LET(
{L1, L2, B},
{list(), list(), list()},
{ct_proper_ext:safe_list(),
ct_proper_ext:safe_list(),
ct_proper_ext:safe_list()},
begin
{gen_set(Mod, L1 ++ B), gen_set(Mod, L2 ++ B)}
end
Expand All @@ -179,7 +189,7 @@ subprop_is_element(Mod) ->
{{S, M}, Es},
?LET(
{L, Extra},
{list(), list()},
{ct_proper_ext:safe_list(), ct_proper_ext:safe_list()},
{gen_set(Mod, L), L ++ Extra}
),
lists:all(fun(E) ->
Expand Down Expand Up @@ -223,7 +233,7 @@ subprop_is_set(sets) ->
{Exp, {S, _M}},
oneof([{true, gen_set(sets)},
{false, {?SUCHTHAT(T,
any(),
ct_proper_ext:safe_any(),
not (is_map(T) orelse
is_tuple(T) andalso
tuple_size(T)=:=9 andalso
Expand All @@ -236,7 +246,7 @@ subprop_is_set(ordsets) ->
{Exp, {S, _M}},
oneof([{true, gen_set(ordsets)},
{false, {?SUCHTHAT(T,
any(),
ct_proper_ext:safe_any(),
not is_list(T)),
undefined}}]),
Exp =:= ordsets:is_set(S)
Expand All @@ -246,7 +256,7 @@ subprop_is_set(gb_sets) ->
{Exp, {S, _M}},
oneof([{true, gen_set(gb_sets)},
{false, {?SUCHTHAT(T,
any(),
ct_proper_ext:safe_any(),
not (is_tuple(T) andalso
tuple_size(T) =:= 2 andalso
is_integer(element(1, T)) andalso
Expand Down Expand Up @@ -289,7 +299,7 @@ subprop_is_subset(Mod) ->
SMs,
?LET(
{L1, L2},
{list(), list()},
{ct_proper_ext:safe_list(), ct_proper_ext:safe_list()},
begin
L3Extra = [make_ref()|L2],
L2Extra = [make_ref()|L1],
Expand All @@ -316,7 +326,7 @@ prop_map() ->
subprop_map(Mod) ->
?FORALL(
{{S0, M0}, Fun},
{gen_set(Mod), function1(any())},
{gen_set(Mod), function1(ct_proper_ext:safe_any())},
is_equal(Mod:map(Fun, S0),
model_map(Fun, M0))
).
Expand All @@ -343,7 +353,9 @@ subprop_subtract(Mod) ->
{{S1, M1}, {S2, M2}},
?LET(
{L1, L2, B},
{list(), list(), list()},
{ct_proper_ext:safe_list(),
ct_proper_ext:safe_list(),
ct_proper_ext:safe_list()},
{gen_set(Mod, L1 ++ B), gen_set(Mod, L2 ++ B)}
),
is_equal(Mod:subtract(S1, S2),
Expand Down Expand Up @@ -374,7 +386,7 @@ subprop_union_1(Mod) ->
SMs,
?LET(
{Ls, A},
{list(list()), list()},
{list(ct_proper_ext:safe_list()), ct_proper_ext:safe_list()},
[gen_set(Mod, L ++ A) || L <- Ls]
),
begin
Expand All @@ -394,7 +406,9 @@ subprop_union_2(Mod) ->
{{S1, M1}, {S2, M2}},
?LET(
{L1, L2, B},
{list(), list(), list()},
{ct_proper_ext:safe_list(),
ct_proper_ext:safe_list(),
ct_proper_ext:safe_list()},
{gen_set(Mod, L1 ++ B), gen_set(Mod, L2 ++ B)}
),
is_equal(Mod:union(S1, S2),
Expand All @@ -409,12 +423,14 @@ subprop_operations(Mod) ->
?FORALL(
{SM0, Ops},
{gen_set(Mod),
list(oneof([{add_element, any()},
{del_element, any()},
list(oneof([{add_element, ct_proper_ext:safe_any()},
{del_element, ct_proper_ext:safe_any()},
{filter, function1(boolean())},
{filtermap, function1(oneof([true, false, {true, any()}]))},
{filtermap, function1(oneof([true,
false,
{true, ct_proper_ext:safe_any()}]))},
{intersection, gen_set(Mod)},
{map, function1(any())},
{map, function1(ct_proper_ext:safe_any())},
{subtract, gen_set(Mod)},
{union, gen_set(Mod)}]))},
begin
Expand Down Expand Up @@ -460,13 +476,13 @@ gen_version() ->
gen_set(sets) ->
?LET(
{L, V},
{list(), gen_version()},
{ct_proper_ext:safe_list(), gen_version()},
gen_set(sets, L, V)
);
gen_set(Mod) ->
?LET(
L,
list(),
ct_proper_ext:safe_list(),
gen_set(Mod, L, 0)
).

Expand All @@ -481,7 +497,7 @@ gen_set(Mod, List) when is_list(List) ->
gen_set(Mod, Version) when is_integer(Version) ->
?LET(
L,
list(),
ct_proper_ext:safe_list(),
gen_set(Mod, L, Version)
).

Expand Down

0 comments on commit 2b1799c

Please sign in to comment.