Skip to content

Commit 9565c19

Browse files
committed
Use ct_proper_ext generators in queue property tests
1 parent fb8bf23 commit 9565c19

File tree

1 file changed

+22
-50
lines changed

1 file changed

+22
-50
lines changed

lib/stdlib/test/property_test/queue_prop.erl

Lines changed: 22 additions & 50 deletions
Original file line numberDiff line numberDiff line change
@@ -19,36 +19,7 @@
1919
%%
2020
-module(queue_prop).
2121

22-
-compile(export_all).
23-
24-
-proptest(eqc).
25-
-proptest([triq, proper]).
26-
27-
-ifndef(EQC).
28-
-ifndef(PROPER).
29-
-ifndef(TRIQ).
30-
-define(EQC, true).
31-
-endif.
32-
-endif.
33-
-endif.
34-
35-
-ifdef(EQC).
36-
-include_lib("eqc/include/eqc.hrl").
37-
-define(MOD_eqc,eqc).
38-
39-
-else.
40-
-ifdef(PROPER).
41-
-include_lib("proper/include/proper.hrl").
42-
-define(MOD_eqc,proper).
43-
44-
-else.
45-
-ifdef(TRIQ).
46-
-define(MOD_eqc,triq).
47-
-include_lib("triq/include/triq.hrl").
48-
49-
-endif.
50-
-endif.
51-
-endif.
22+
-include_lib("common_test/include/ct_property_test.hrl").
5223

5324
%%%%%%%%%%%%%%%%%%
5425
%%% Properties %%%
@@ -72,7 +43,7 @@ prop_is_queue() ->
7243
prop_list_conversion() ->
7344
?FORALL(
7445
List,
75-
list(),
46+
ct_proper_ext:safe_list(),
7647
begin
7748
Queue = queue:from_list(List),
7849
queue:is_queue(Queue) andalso
@@ -83,7 +54,7 @@ prop_list_conversion() ->
8354
prop_from_list_invalid() ->
8455
?FORALL(
8556
NonList,
86-
?SUCHTHAT(T, term(), not is_list(T)),
57+
?SUCHTHAT(T, ct_proper_ext:safe_any(), not is_list(T)),
8758
expect_badarg(fun queue:from_list/1, [NonList])
8859
).
8960

@@ -93,7 +64,8 @@ prop_to_list_invalid() ->
9364
prop_all() ->
9465
?FORALL(
9566
{L, Q},
96-
oneof([list_queue(atom()), list_queue(term())]),
67+
oneof([list_queue(ct_proper_ext:safe_atom()),
68+
list_queue(ct_proper_ext:safe_any())]),
9769
begin
9870
lists:all(fun is_atom/1, L) =:= queue:all(fun is_atom/1, Q)
9971
end
@@ -129,7 +101,7 @@ prop_daeh_invalid() ->
129101
prop_delete() ->
130102
?FORALL(
131103
{X, {L, Q}},
132-
{term(), list_queue()},
104+
{ct_proper_ext:safe_any(), list_queue()},
133105
begin
134106
R1 = if
135107
L =:= [] ->
@@ -150,7 +122,7 @@ prop_delete_invalid() ->
150122
prop_delete_r() ->
151123
?FORALL(
152124
{X, {L, Q}},
153-
{term(), list_queue()},
125+
{ct_proper_ext:safe_any(), list_queue()},
154126
begin
155127
R1 = if
156128
L =:= [] ->
@@ -327,7 +299,7 @@ prop_head_invalid() ->
327299
prop_in() ->
328300
?FORALL(
329301
L,
330-
list(),
302+
ct_proper_ext:safe_list(),
331303
begin
332304
Q = lists:foldl(
333305
fun(I, Acc) ->
@@ -410,7 +382,7 @@ prop_liat_invalid() ->
410382
prop_member() ->
411383
?FORALL(
412384
{X, {L, Q}},
413-
{term(), list_queue()},
385+
{ct_proper_ext:safe_any(), list_queue()},
414386
begin
415387
% all members of L are members of Q
416388
lists:all(
@@ -526,7 +498,7 @@ prop_reverse_invalid() ->
526498
prop_snoc() ->
527499
?FORALL(
528500
L,
529-
list(),
501+
ct_proper_ext:safe_list(),
530502
begin
531503
Q = lists:foldl(
532504
fun(I, Acc) ->
@@ -542,7 +514,7 @@ prop_snoc() ->
542514
prop_snoc_invalid() ->
543515
?FORALL(
544516
{I, NonQueue},
545-
{term(), non_queue()},
517+
{ct_proper_ext:safe_any(), non_queue()},
546518
expect_badarg(fun queue:snoc/2, [NonQueue, I])
547519
).
548520

@@ -568,7 +540,7 @@ prop_split_invalid() ->
568540
{non_queue(), 0},
569541
?SUCHTHAT(
570542
{Q1, N1},
571-
{queue(), term()},
543+
{queue(), ct_proper_ext:safe_any()},
572544
not(is_integer(N1) andalso N1>=0 andalso N1=<queue:len(Q1))
573545
)
574546
]
@@ -588,23 +560,23 @@ prop_ops() ->
588560
{Ops, {L, Q}},
589561
{
590562
list(
591-
oneof([{cons, term()},
563+
oneof([{cons, ct_proper_ext:safe_any()},
592564
daeh,
593565
drop,
594566
drop_r,
595567
get,
596568
get_r,
597569
head,
598-
{in, term()},
599-
{in_r, term()},
570+
{in, ct_proper_ext:safe_any()},
571+
{in_r, ct_proper_ext:safe_any()},
600572
init,
601573
liat,
602574
last,
603575
out,
604576
out_r,
605577
peek,
606578
peek_r,
607-
{snoc, term()},
579+
{snoc, ct_proper_ext:safe_any()},
608580
tail])
609581
),
610582
list_queue()
@@ -785,7 +757,7 @@ common_drop_tail(Fn) ->
785757
common_in_r_cons(Fn) ->
786758
?FORALL(
787759
L,
788-
list(),
760+
ct_proper_ext:safe_list(),
789761
begin
790762
Q = lists:foldl(
791763
fun(I, Acc) ->
@@ -815,7 +787,7 @@ common_invalid_pred(Fn) ->
815787
common_invalid_term(Fn) ->
816788
?FORALL(
817789
{I, NonQueue},
818-
{term(), non_queue()},
790+
{ct_proper_ext:safe_any(), non_queue()},
819791
expect_badarg(Fn, [I, NonQueue])
820792
).
821793

@@ -824,7 +796,7 @@ common_invalid_term(Fn) ->
824796
%%%%%%%%%%%%%%%%%%
825797

826798
list_queue() ->
827-
list_queue(term()).
799+
list_queue(ct_proper_ext:safe_any()).
828800

829801
list_queue(Type) ->
830802
?LET(
@@ -841,7 +813,7 @@ list_queue(Type) ->
841813
).
842814

843815
queue() ->
844-
queue(term()).
816+
queue(ct_proper_ext:safe_any()).
845817

846818
queue(Type) ->
847819
?LET(List, list(Type), queue:from_list(List)).
@@ -857,7 +829,7 @@ queue(Type) ->
857829
non_queue() ->
858830
?SUCHTHAT(
859831
T,
860-
term(),
832+
ct_proper_ext:safe_any(),
861833
not(
862834
is_tuple(T) andalso
863835
tuple_size(T) =:= 2 andalso
@@ -869,7 +841,7 @@ non_queue() ->
869841
non_fun(Arity) ->
870842
?SUCHTHAT(
871843
T,
872-
term(),
844+
ct_proper_ext:safe_any(),
873845
not is_function(T, Arity)
874846
).
875847

0 commit comments

Comments
 (0)