aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/sets_SUITE.erl
diff options
context:
space:
mode:
authorBjörn Gustavsson <[email protected]>2012-10-08 16:40:00 +0200
committerBjörn Gustavsson <[email protected]>2012-11-08 10:13:48 +0100
commitd07a3a935dc1278769cf1069721dbbbbe2b8f3cc (patch)
treee517f6aba18b21714db5a5450582ec6f711eaec4 /lib/stdlib/test/sets_SUITE.erl
parentc1cfd8368b68e9caa91cb2da889d83d65277ac53 (diff)
downloadotp-d07a3a935dc1278769cf1069721dbbbbe2b8f3cc.tar.gz
otp-d07a3a935dc1278769cf1069721dbbbbe2b8f3cc.tar.bz2
otp-d07a3a935dc1278769cf1069721dbbbbe2b8f3cc.zip
sets_SUITE: Eliminate use of parameterized modules
Since the support for parameterized modules will be removed in R16, we should not use them in test cases.
Diffstat (limited to 'lib/stdlib/test/sets_SUITE.erl')
-rw-r--r--lib/stdlib/test/sets_SUITE.erl342
1 files changed, 171 insertions, 171 deletions
diff --git a/lib/stdlib/test/sets_SUITE.erl b/lib/stdlib/test/sets_SUITE.erl
index f284276bd7..e2bcdd18ce 100644
--- a/lib/stdlib/test/sets_SUITE.erl
+++ b/lib/stdlib/test/sets_SUITE.erl
@@ -35,7 +35,7 @@
-import(lists, [foldl/3,reverse/1]).
init_per_testcase(_Case, Config) ->
- ?line Dog = ?t:timetrap(?t:minutes(5)),
+ Dog = ?t:timetrap(?t:minutes(5)),
[{watchdog,Dog}|Config].
end_per_testcase(_Case, Config) ->
@@ -70,65 +70,65 @@ create(Config) when is_list(Config) ->
test_all(fun create_1/1).
create_1(M) ->
- ?line S0 = M:empty(),
- ?line [] = M:to_list(S0),
- ?line 0 = M:size(S0),
- ?line true = M:is_empty(S0),
+ S0 = M(empty, []),
+ [] = M(to_list, S0),
+ 0 = M(size, S0),
+ true = M(is_empty, S0),
E = make_ref(),
- ?line One = M:singleton(E),
- ?line 1 = M:size(One),
- ?line false = M:is_empty(One),
- [E] = M:to_list(One),
+ One = M(singleton, E),
+ 1 = M(size, One),
+ false = M(is_empty, One),
+ [E] = M(to_list, One),
S0.
add_element(Config) when is_list(Config) ->
test_all([{0,132},{253,258},{510,514}], fun add_element_1/2).
add_element_1(List, M) ->
- ?line S = M:from_list(List),
- ?line SortedSet = lists:usort(List),
- ?line SortedSet = lists:sort(M:to_list(S)),
+ S = M(from_list, List),
+ SortedSet = lists:usort(List),
+ SortedSet = lists:sort(M(to_list, S)),
%% Make sure that we get the same result by inserting
%% elements one at the time.
- ?line S2 = foldl(fun(El, Set) -> M:add_element(El, Set) end,
- M:empty(), List),
- ?line true = M:equal(S, S2),
+ S2 = foldl(fun(El, Set) -> M(add_element, {El,Set}) end,
+ M(empty, []), List),
+ true = M(equal, {S,S2}),
%% Insert elements, randomly delete inserted elements,
%% and re-inserted all deleted elements at the end.
- ?line S3 = add_element_del(List, M, M:empty(), [], []),
- ?line true = M:equal(S2, S3),
- ?line true = M:equal(S, S3),
+ S3 = add_element_del(List, M, M(empty, []), [], []),
+ true = M(equal, {S2,S3}),
+ true = M(equal, {S,S3}),
S.
add_element_del([H|T], M, S, Del, []) ->
- add_element_del(T, M, M:add_element(H, S), Del, [H]);
+ add_element_del(T, M, M(add_element, {H,S}), Del, [H]);
add_element_del([H|T], M, S0, Del, Inserted) ->
- S1 = M:add_element(H, S0),
+ S1 = M(add_element, {H,S0}),
case random:uniform(3) of
1 ->
OldEl = lists:nth(random:uniform(length(Inserted)), Inserted),
- S = M:del_element(OldEl, S1),
+ S = M(del_element, {OldEl,S1}),
add_element_del(T, M, S, [OldEl|Del], [H|Inserted]);
_ ->
add_element_del(T, M, S1, Del, [H|Inserted])
end;
add_element_del([], M, S, Del, _) ->
- M:union(S, M:from_list(Del)).
+ M(union, {S,M(from_list, Del)}).
del_element(Config) when is_list(Config) ->
test_all([{0,132},{253,258},{510,514},{1022,1026}], fun del_element_1/2).
del_element_1(List, M) ->
- ?line S0 = M:from_list(List),
- ?line Empty = foldl(fun(El, Set) -> M:del_element(El, Set) end, S0, List),
- ?line Empty = M:empty(),
- ?line M:is_empty(Empty),
- ?line S1 = foldl(fun(El, Set) ->
- M:add_element(El, Set)
- end, S0, reverse(List)),
- ?line true = M:equal(S0, S1),
+ S0 = M(from_list, List),
+ Empty = foldl(fun(El, Set) -> M(del_element, {El,Set}) end, S0, List),
+ 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}),
S1.
subtract(Config) when is_list(Config) ->
@@ -138,23 +138,23 @@ subtract(Config) when is_list(Config) ->
test_all([{2,69},{126,130},{253,258},511,512,{1023,1030}], fun subtract_1/2).
subtract_empty(M) ->
- ?line Empty = M:empty(),
- ?line true = M:is_empty(M:subtract(Empty, Empty)),
- M:subtract(Empty, Empty).
+ Empty = M(empty, []),
+ true = M(is_empty, M(subtract, {Empty,Empty})),
+ M(subtract, {Empty,Empty}).
subtract_1(List, M) ->
- ?line S0 = M:from_list(List),
- ?line Empty = M:empty(),
+ S0 = M(from_list, List),
+ Empty = M(empty, []),
%% Trivial cases.
- ?line true = M:is_empty(M:subtract(Empty, S0)),
- ?line true = M:equal(S0, M:subtract(S0, Empty)),
+ true = M(is_empty, M(subtract, {Empty,S0})),
+ true = M(equal, {S0,M(subtract, {S0,Empty})}),
%% Not so trivial.
- ?line subtract_check(List, mutate_some(remove_some(List, 0.4)), M),
- ?line subtract_check(List, rnd_list(length(List) div 2 + 5), M),
- ?line subtract_check(List, rnd_list(length(List) div 7 + 9), M),
- ?line subtract_check(List, mutate_some(List), M).
+ subtract_check(List, mutate_some(remove_some(List, 0.4)), M),
+ subtract_check(List, rnd_list(length(List) div 2 + 5), M),
+ subtract_check(List, rnd_list(length(List) div 7 + 9), M),
+ subtract_check(List, mutate_some(List), M).
subtract_check(A, B, M) ->
one_subtract_check(B, A, M),
@@ -163,12 +163,12 @@ subtract_check(A, B, M) ->
one_subtract_check(A, B, M) ->
ASorted = lists:usort(A),
BSorted = lists:usort(B),
- ASet = M:from_list(A),
- BSet = M:from_list(B),
- DiffSet = M:subtract(ASet, BSet),
+ ASet = M(from_list, A),
+ BSet = M(from_list, B),
+ DiffSet = M(subtract, {ASet,BSet}),
Diff = ASorted -- BSorted,
- true = M:equal(DiffSet, M:from_list(Diff)),
- Diff = lists:sort(M:to_list(DiffSet)),
+ true = M(equal, {DiffSet,M(from_list, Diff)}),
+ Diff = lists:sort(M(to_list, DiffSet)),
DiffSet.
intersection(Config) when is_list(Config) ->
@@ -176,60 +176,60 @@ intersection(Config) when is_list(Config) ->
test_all([{1,65},{126,130},{253,259},{499,513},{1023,1025}], fun intersection_1/2).
intersection_1(List, M) ->
- ?line S0 = M:from_list(List),
+ S0 = M(from_list, List),
%% Intersection with self.
- ?line true = M:equal(S0, M:intersection(S0, S0)),
- ?line true = M:equal(S0, M:intersection([S0,S0])),
- ?line true = M:equal(S0, M:intersection([S0,S0,S0])),
- ?line true = M:equal(S0, M:intersection([S0])),
+ 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])}),
%% Intersection with empty.
- ?line Empty = M:empty(),
- ?line true = M:equal(Empty, M:intersection(S0, Empty)),
- ?line true = M:equal(Empty, M:intersection([S0,Empty,S0,Empty])),
+ Empty = M(empty, []),
+ true = M(equal, {Empty,M(intersection, {S0,Empty})}),
+ true = M(equal, {Empty,M(intersection, [S0,Empty,S0,Empty])}),
%% The intersection of no sets is undefined.
- ?line {'EXIT',_} = (catch M:intersection([])),
+ {'EXIT',_} = (catch M(intersection, [])),
%% Disjoint sets.
- ?line Disjoint = [{El} || El <- List],
- ?line DisjointSet = M:from_list(Disjoint),
- ?line M:is_empty(M:intersection(S0, DisjointSet)),
+ Disjoint = [{El} || El <- List],
+ DisjointSet = M(from_list, Disjoint),
+ true = M(is_empty, M(intersection, {S0,DisjointSet})),
%% Disjoint, different sizes.
- ?line M:is_empty(M:intersection(S0, M:from_list(remove_some(Disjoint, 0.3)))),
- ?line M:is_empty(M:intersection(S0, M:from_list(remove_some(Disjoint, 0.7)))),
- ?line M:is_empty(M:intersection(S0, M:from_list(remove_some(Disjoint, 0.9)))),
- ?line M:is_empty(M:intersection(M:from_list(remove_some(List, 0.3)), DisjointSet)),
- ?line M:is_empty(M:intersection(M:from_list(remove_some(List, 0.5)), DisjointSet)),
- ?line M:is_empty(M:intersection(M:from_list(remove_some(List, 0.9)), DisjointSet)),
+ [begin
+ SomeRemoved = M(from_list, remove_some(Disjoint, HowMuch)),
+ true = M(is_empty, M(intersection, {S0,SomeRemoved})),
+ MoreRemoved = M(from_list, remove_some(List, HowMuch)),
+ true = M(is_empty, M(intersection, {MoreRemoved,DisjointSet}))
+ end || HowMuch <- [0.3,0.5,0.7,0.9]],
%% Partial overlap (one or more elements in result set).
%% The sets have almost the same size. (Almost because a duplicated
%% element in the original list could be mutated and not mutated
%% at the same time.)
- ?line PartialOverlap = mutate_some(List, []),
- ?line IntersectionSet = check_intersection(List, PartialOverlap, M),
- ?line false = M:is_empty(IntersectionSet),
+ PartialOverlap = mutate_some(List, []),
+ IntersectionSet = check_intersection(List, PartialOverlap, M),
+ false = M(is_empty, IntersectionSet),
%% Partial overlap, different set sizes. (Intersection possibly empty.)
- ?line check_intersection(List, remove_some(PartialOverlap, 0.1), M),
- ?line check_intersection(List, remove_some(PartialOverlap, 0.3), M),
- ?line check_intersection(List, remove_some(PartialOverlap, 0.5), M),
- ?line check_intersection(List, remove_some(PartialOverlap, 0.7), M),
- ?line check_intersection(List, remove_some(PartialOverlap, 0.9), M),
+ check_intersection(List, remove_some(PartialOverlap, 0.1), M),
+ check_intersection(List, remove_some(PartialOverlap, 0.3), M),
+ check_intersection(List, remove_some(PartialOverlap, 0.5), M),
+ check_intersection(List, remove_some(PartialOverlap, 0.7), M),
+ check_intersection(List, remove_some(PartialOverlap, 0.9), M),
IntersectionSet.
check_intersection(Orig, Mutated, M) ->
- OrigSet = M:from_list(Orig),
- MutatedSet = M:from_list(Mutated),
+ OrigSet = M(from_list, Orig),
+ MutatedSet = M(from_list, Mutated),
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)),
- SortedIntersection = lists:sort(M:to_list(IntersectionSet)),
+ IntersectionSet = M(intersection, {OrigSet,MutatedSet}),
+ true = M(equal, {IntersectionSet,M(from_list, SortedIntersection)}),
+ SortedIntersection = lists:sort(M(to_list, IntersectionSet)),
IntersectionSet.
@@ -239,63 +239,63 @@ union(Config) when is_list(Config) ->
test_all([{1,71},{125,129},{254,259},{510,513},{1023,1025}], fun union_1/2).
union_1(List, M) ->
- ?line S = M:from_list(List),
+ S = M(from_list, List),
%% Union with self and empty.
- ?line Empty = M:empty(),
- ?line true = M:equal(S, M:union(S, S)),
- ?line true = M:equal(S, M:union([S,S])),
- ?line true = M:equal(S, M:union([S,S,Empty])),
- ?line true = M:equal(S, M:union([S,Empty,S])),
- ?line true = M:equal(S, M:union(S, Empty)),
- ?line true = M:equal(S, M:union([S])),
- ?line true = M:is_empty(M:union([])),
+ 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_empty, M(union, [])),
%% Partial overlap.
- ?line check_union(List, remove_some(mutate_some(List), 0.9), M),
- ?line check_union(List, remove_some(mutate_some(List), 0.7), M),
- ?line check_union(List, remove_some(mutate_some(List), 0.5), M),
- ?line check_union(List, remove_some(mutate_some(List), 0.3), M),
- ?line check_union(List, remove_some(mutate_some(List), 0.1), M),
-
- ?line check_union(List, mutate_some(remove_some(List, 0.9)), M),
- ?line check_union(List, mutate_some(remove_some(List, 0.7)), M),
- ?line check_union(List, mutate_some(remove_some(List, 0.5)), M),
- ?line check_union(List, mutate_some(remove_some(List, 0.3)), M),
- ?line check_union(List, mutate_some(remove_some(List, 0.1)), M).
+ check_union(List, remove_some(mutate_some(List), 0.9), M),
+ check_union(List, remove_some(mutate_some(List), 0.7), M),
+ check_union(List, remove_some(mutate_some(List), 0.5), M),
+ check_union(List, remove_some(mutate_some(List), 0.3), M),
+ check_union(List, remove_some(mutate_some(List), 0.1), M),
+
+ check_union(List, mutate_some(remove_some(List, 0.9)), M),
+ check_union(List, mutate_some(remove_some(List, 0.7)), M),
+ check_union(List, mutate_some(remove_some(List, 0.5)), M),
+ check_union(List, mutate_some(remove_some(List, 0.3)), M),
+ check_union(List, mutate_some(remove_some(List, 0.1)), M).
check_union(Orig, Other, M) ->
- OrigSet = M:from_list(Orig),
- OtherSet = M:from_list(Other),
+ OrigSet = M(from_list, Orig),
+ OtherSet = M(from_list, Other),
Union = Orig++Other,
SortedUnion = lists:usort(Union),
- UnionSet = M:union(OrigSet, OtherSet),
- SortedUnion = lists:sort(M:to_list(UnionSet)),
- M:equal(UnionSet, M:from_list(Union)),
+ UnionSet = M(union, {OrigSet,OtherSet}),
+ SortedUnion = lists:sort(M(to_list, UnionSet)),
+ M(equal, {UnionSet,M(from_list, Union)}),
UnionSet.
is_subset(Config) when is_list(Config) ->
test_all([{1,132},{253,270},{299,311}], fun is_subset_1/2).
is_subset_1(List, M) ->
- ?line S = M:from_list(List),
- ?line Empty = M:empty(),
+ S = M(from_list, List),
+ Empty = M(empty, []),
%% Subset of empty and self.
- ?line true = M:is_subset(Empty, Empty),
- ?line true = M:is_subset(Empty, S),
- ?line false = M:is_subset(S, Empty),
- ?line true = M:is_subset(S, S),
+ true = M(is_subset, {Empty,Empty}),
+ true = M(is_subset, {Empty,S}),
+ false = M(is_subset, {S,Empty}),
+ true = M(is_subset, {S,S}),
%% Other cases.
- Res = [?line false = M:is_subset(M:singleton(make_ref()), S),
- ?line true = M:is_subset(M:singleton(hd(List)), S),
- ?line true = check_subset(remove_some(List, 0.1), List, M),
- ?line true = check_subset(remove_some(List, 0.5), List, M),
- ?line true = check_subset(remove_some(List, 0.9), List, M),
- ?line check_subset(mutate_some(List), List, M),
- ?line check_subset(rnd_list(length(List) div 2 + 5), List, M),
- ?line subtract_check(List, rnd_list(length(List) div 7 + 9), M)
+ Res = [false = M(is_subset, {M(singleton, make_ref()),S}),
+ true = M(is_subset, {M(singleton, hd(List)),S}),
+ true = check_subset(remove_some(List, 0.1), List, M),
+ true = check_subset(remove_some(List, 0.5), List, M),
+ true = check_subset(remove_some(List, 0.9), List, M),
+ check_subset(mutate_some(List), List, M),
+ check_subset(rnd_list(length(List) div 2 + 5), List, M),
+ subtract_check(List, rnd_list(length(List) div 7 + 9), M)
],
res_to_set(Res, M, 0, []).
@@ -304,12 +304,12 @@ check_subset(X, Y, M) ->
check_one_subset(X, Y, M).
check_one_subset(X, Y, M) ->
- XSet = M:from_list(X),
- YSet = M:from_list(Y),
+ XSet = M(from_list, X),
+ YSet = M(from_list, Y),
SortedX = lists:usort(X),
SortedY = lists:usort(Y),
IsSubSet = length(SortedY--SortedX) =:= length(SortedY) - length(SortedX),
- IsSubSet = M:is_subset(XSet, YSet),
+ IsSubSet = M(is_subset, {XSet,YSet}),
IsSubSet.
%% Encode all test results as a set to return.
@@ -317,54 +317,54 @@ res_to_set([true|T], M, I, Acc) ->
res_to_set(T, M, I+1, [I|Acc]);
res_to_set([_|T], M, I, Acc) ->
res_to_set(T, M, I+1, Acc);
-res_to_set([], M, _, Acc) -> M:from_list(Acc).
+res_to_set([], M, _, Acc) -> M(from_list, Acc).
is_set(Config) when is_list(Config) ->
%% is_set/1 is tested in the other test cases when its argument
%% is a set. Here test some arguments that makes it return false.
- ?line false = gb_sets:is_set([a,b]),
- ?line false = gb_sets:is_set({a,very,bad,tuple}),
+ false = gb_sets:is_set([a,b]),
+ false = gb_sets:is_set({a,very,bad,tuple}),
- ?line false = sets:is_set([a,b]),
- ?line false = sets:is_set({a,very,bad,tuple}),
+ false = sets:is_set([a,b]),
+ false = sets:is_set({a,very,bad,tuple}),
- ?line false = ordsets:is_set([b,a]),
- ?line false = ordsets:is_set({bad,tuple}),
+ false = ordsets:is_set([b,a]),
+ false = ordsets:is_set({bad,tuple}),
%% Now test values that are known to be bad for all set representations.
test_all(fun is_set_1/1).
is_set_1(M) ->
- ?line false = M:is_set(self()),
- ?line false = M:is_set(blurf),
- ?line false = M:is_set(make_ref()),
- ?line false = M:is_set(<<1,2,3>>),
- ?line false = M:is_set(42),
- ?line false = M:is_set(math:pi()),
- ?line false = M:is_set({}),
- M:empty().
+ false = M(is_set, self()),
+ false = M(is_set, blurf),
+ false = M(is_set, make_ref()),
+ false = M(is_set, <<1,2,3>>),
+ false = M(is_set, 42),
+ false = M(is_set, math:pi()),
+ false = M(is_set, {}),
+ M(empty, []).
fold(Config) when is_list(Config) ->
test_all([{0,71},{125,129},{254,259},{510,513},{1023,1025},{9999,10001}],
fun fold_1/2).
fold_1(List, M) ->
- ?line S = M:from_list(List),
- ?line L = M:fold(fun(E, A) -> [E|A] end, [], S),
- ?line true = lists:sort(L) =:= lists:usort(List),
- M:empty().
+ S = M(from_list, List),
+ L = M(fold, {fun(E, A) -> [E|A] end,[],S}),
+ true = lists:sort(L) =:= lists:usort(List),
+ M(empty, []).
filter(Config) when is_list(Config) ->
test_all([{0,69},{126,130},{254,259},{510,513},{1023,1025},{7999,8000}],
fun filter_1/2).
filter_1(List, M) ->
- ?line S = M:from_list(List),
+ S = M(from_list, List),
IsNumber = fun(X) -> is_number(X) end,
- ?line M:equal(M:from_list(lists:filter(IsNumber, List)),
- M:filter(IsNumber, S)),
- ?line M:filter(fun(X) -> is_atom(X) end, S).
+ M(equal, {M(from_list, lists:filter(IsNumber, List)),
+ M(filter, {IsNumber,S})}),
+ M(filter, {fun(X) -> is_atom(X) end,S}).
%%%
%%% Test specifics for gb_sets.
@@ -375,26 +375,26 @@ take_smallest(Config) when is_list(Config) ->
fun take_smallest_1/2).
take_smallest_1(List, M) ->
- case M:module() of
+ case M(module, []) of
gb_sets -> take_smallest_2(List, M);
_ -> ok
end,
- M:empty().
+ M(empty, []).
take_smallest_2(List0, M) ->
- ?line List = lists:usort(List0),
- ?line S = M:from_list(List0),
+ List = lists:usort(List0),
+ S = M(from_list, List0),
take_smallest_3(S, List, M).
take_smallest_3(S0, List0, M) ->
- case M:is_empty(S0) of
+ case M(is_empty, S0) of
true -> ok;
false ->
- ?line Smallest = hd(List0),
- ?line Smallest = gb_sets:smallest(S0),
- ?line {Smallest,S} = gb_sets:take_smallest(S0),
- ?line List = tl(List0),
- ?line true = gb_sets:to_list(S) =:= List,
+ Smallest = hd(List0),
+ Smallest = gb_sets:smallest(S0),
+ {Smallest,S} = gb_sets:take_smallest(S0),
+ List = tl(List0),
+ true = gb_sets:to_list(S) =:= List,
take_smallest_3(S, List, M)
end.
@@ -403,26 +403,26 @@ take_largest(Config) when is_list(Config) ->
fun take_largest_1/2).
take_largest_1(List, M) ->
- case M:module() of
+ case M(module, []) of
gb_sets -> take_largest_2(List, M);
_ -> ok
end,
- M:empty().
+ M(empty, []).
take_largest_2(List0, M) ->
- ?line List = reverse(lists:usort(List0)),
- ?line S = M:from_list(List0),
+ List = reverse(lists:usort(List0)),
+ S = M(from_list, List0),
take_largest_3(S, List, M).
take_largest_3(S0, List0, M) ->
- case M:is_empty(S0) of
+ case M(is_empty, S0) of
true -> ok;
false ->
- ?line Largest = hd(List0),
- ?line Largest = gb_sets:largest(S0),
- ?line {Largest,S} = gb_sets:take_largest(S0),
- ?line List = tl(List0),
- ?line true = gb_sets:to_list(S) =:= reverse(List),
+ Largest = hd(List0),
+ Largest = gb_sets:largest(S0),
+ {Largest,S} = gb_sets:take_largest(S0),
+ List = tl(List0),
+ true = gb_sets:to_list(S) =:= reverse(List),
take_largest_3(S, List, M)
end.
@@ -441,23 +441,23 @@ sets_mods() ->
[Ordsets,Sets,Gb].
test_all(Tester) ->
- ?line Res = [begin
- random:seed(1, 2, 42),
- S = Tester(M),
- {M:size(S),lists:sort(M:to_list(S))}
- end || M <- sets_mods()],
- ?line all_same(Res).
+ Res = [begin
+ random:seed(1, 2, 42),
+ S = Tester(M),
+ {M(size, S),lists:sort(M(to_list, S))}
+ end || M <- sets_mods()],
+ all_same(Res).
test_all([{Low,High}|T], Tester) ->
test_all(lists:seq(Low, High)++T, Tester);
test_all([Sz|T], Tester) when is_integer(Sz) ->
List = rnd_list(Sz),
- ?line Res = [begin
+ Res = [begin
random:seed(19, 2, Sz),
S = Tester(List, M),
- {M:size(S),lists:sort(M:to_list(S))}
+ {M(size, S),lists:sort(M(to_list, S))}
end || M <- sets_mods()],
- ?line all_same(Res),
+ all_same(Res),
test_all(T, Tester);
test_all([], _) -> ok.