Skip to content

Commit

Permalink
Remove calls to PropEr-internal functions
Browse files Browse the repository at this point in the history
  • Loading branch information
Maria-12648430 committed Jun 14, 2023
1 parent 795b7f4 commit d98facc
Showing 1 changed file with 50 additions and 26 deletions.
76 changes: 50 additions & 26 deletions lib/common_test/src/ct_property_test_proper_ext.erl
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,16 @@
-export([safe_list/0]).
-export([safe_tuple/0]).

-spec safe_list() -> proper_types:type().
safe_list() ->
proper_types:list(safe_any()).


-spec safe_tuple() -> proper_types:type().
safe_tuple() ->
proper_types:tuple(safe_any()).


-spec safe_atom() -> proper_types:type().
safe_atom() ->
proper_types:oneof([proper_types:oneof(['', true, false, ok,
Expand All @@ -41,16 +51,12 @@ safe_atom() ->

-spec existing_atom() -> proper_types:type().
existing_atom() ->
proper_types:bind(proper_types:non_neg_integer(),
fun(N) ->
get_existing_atom(N)
end,
false).
proper_types:lazy(fun() ->
N = erlang:system_info(atom_count),
get_existing_atom(rand_int0(N - 1), N)
end).

-define(ATOM_TERM_BIN(Index), <<131, 75, Index:24>>).
get_existing_atom(Index) ->
get_existing_atom(Index, erlang:system_info(atom_count)).

get_existing_atom(Index, Max) ->
Index1 = Index rem Max,
case binary_to_term(?ATOM_TERM_BIN(Index1)) of
Expand All @@ -73,44 +79,62 @@ safe_any(0) ->
proper_types:integer(),
proper_types:float()]);
safe_any(Size) ->
{_, Choice} = proper_arith:freq_choose([{3, simple},
{1, binary},
{4, list},
{4, tuple}]),
NumElements = proper_arith:rand_int(0, Size),
case {Choice, NumElements} of
{simple, _NumEls} ->
case pick_type(Size) of
simple ->
safe_any(0);
{binary, _NumEls} ->
binary ->
proper_types:resize(Size, proper_types:bitstring());
{list, 0} ->
[];
{list, 1} ->
[proper_types:lazy(fun() -> safe_any(Size-1) end)];
[proper_types:lazy(fun() -> safe_any(Size - 1) end)];
{list, NumEls} ->
ElSizes = proper_arith:distribute(Size-1, NumEls),
ElSizes = distribute(Size - 1, NumEls),
proper_types:fixed_list([proper_types:lazy(fun() ->
safe_any(S)
end)
|| S <- ElSizes]);
{tuple, 0} ->
{};
{tuple, 1} ->
{proper_types:lazy(fun() -> safe_any(Size-1) end)};
{proper_types:lazy(fun() -> safe_any(Size - 1) end)};
{tuple, NumEls} ->
ElSizes = proper_arith:distribute(Size-1, NumEls),
ElSizes = distribute(Size - 1, NumEls),
proper_types:tuple([proper_types:lazy(fun() ->
safe_any(S) end)
|| S <- ElSizes])
end.

pick_type(Size) ->
case rand:uniform(100) of
X when X =< 33 ->
%% 33% tuples
{tuple, rand_int0(Size)};
X when X =< 66 ->
%% 33% lists
{list, rand_int0(Size)};
X when X =< 75 ->
%% 9% binaries
binary;
_ ->
%% 25% simple types
simple
end.

-spec safe_list() -> proper_types:type().
safe_list() ->
proper_types:list(safe_any()).
distribute(Slots, Credits) ->
[X || {_, X} <- lists:sort(distribute_1(Slots, Credits))].

distribute_1(0, 0) ->
[];
distribute_1(1, Credits) ->
[{rand:uniform(1000), Credits}];
distribute_1(Slots, 0) ->
[{rand:uniform(1000), 0} || _ <- lists:seq(1, Slots)];
distribute_1(Slots, Credits) ->
N = rand_int0(Credits),
[{rand:uniform(1000), N}|distribute_1(Slots - 1, Credits - N)].

-spec safe_tuple() -> proper_types:type().
safe_tuple() ->
proper_types:tuple(safe_any()).

%% random non-neg integer
rand_int0(Max) ->
rand:uniform(Max + 1) - 1.

0 comments on commit d98facc

Please sign in to comment.