File 5541-Property-based-tests-for-the-lists-module.patch of Package erlang
From 87d80d23950dc8ef7249bdd58c84214096e9ddac Mon Sep 17 00:00:00 2001
From: Maria Scott <maria-12648430@hnc-agency.org>
Date: Tue, 5 Jul 2022 15:10:30 +0200
Subject: [PATCH] Property-based tests for the lists module
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit
Co-authored-by: Jan Uhlig <juhlig@hnc-agency.org>
Co-authored-by: Björn Gustavsson <bgustavsson@gmail.com>
---
lib/stdlib/test/Makefile | 1 +
lib/stdlib/test/lists_property_test_SUITE.erl | 391 ++++
lib/stdlib/test/property_test/lists_prop.erl | 1807 +++++++++++++++++
3 files changed, 2199 insertions(+)
create mode 100644 lib/stdlib/test/lists_property_test_SUITE.erl
create mode 100644 lib/stdlib/test/property_test/lists_prop.erl
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index b8e4d89996..9ccd48bcc7 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -49,6 +49,7 @@ MODULES= \
io_SUITE \
io_proto_SUITE \
lists_SUITE \
+ lists_property_test_SUITE \
log_mf_h_SUITE \
math_SUITE \
ms_transform_SUITE \
diff --git a/lib/stdlib/test/lists_property_test_SUITE.erl b/lib/stdlib/test/lists_property_test_SUITE.erl
new file mode 100644
index 0000000000..fee088a396
--- /dev/null
+++ b/lib/stdlib/test/lists_property_test_SUITE.erl
@@ -0,0 +1,391 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2021. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(lists_property_test_SUITE).
+
+-include_lib("common_test/include/ct.hrl").
+-compile(export_all).
+
+all() ->
+ [
+ all_true_case, all_false_case,
+ any_true_case, any_false_case,
+ append_1_case,
+ append_2_case,
+ concat_case,
+ delete_case, delete_absent_case,
+ droplast_case,
+ dropwhile_case,
+ duplicate_case,
+ enumerate_1_case,
+ enumerate_2_case,
+ filter_case,
+ filtermap_case,
+ flatlength_case,
+ flatmap_case,
+ flatten_1_case,
+ flatten_2_case,
+ foldl_case,
+ foldr_case,
+ foreach_case,
+ join_case,
+ keydelete_case, keydelete_absent_case,
+ keyfind_case, keyfind_absent_case,
+ keymap_case,
+ keymember_case, keymember_absent_case,
+ keymerge_case,
+ keyreplace_case, keyreplace_absent_case,
+ keysearch_case, keysearch_absent_case,
+ keysort_case,
+ keystore_case, keystore_absent_case,
+ keytake_case, keytake_absent_case,
+ last_case,
+ map_case,
+ mapfoldl_case,
+ mapfoldr_case,
+ max_case,
+ member_case, member_absent_case,
+ merge_1_case,
+ merge_2_case,
+ merge_3_case,
+ merge3_case,
+ min_case,
+ nth_case, nth_outofrange_case,
+ nthtail_case, nthtail_outofrange_case,
+ partition_case,
+ prefix_case,
+ reverse_1_case,
+ reverse_2_case,
+ search_case, search_absent_case,
+ seq2_case,
+ seq3_case,
+ sort_1_case,
+ sort_2_case,
+ split_case, split_outofrange_case,
+ splitwith_case,
+ sublist_2_case,
+ sublist_3_case,
+ subtract_case,
+ suffix_case,
+ sum_case,
+ takewhile_case,
+ ukeymerge_case,
+ ukeysort_case,
+ umerge_1_case,
+ umerge_2_case,
+ umerge_3_case,
+ umerge3_case,
+ uniq_1_case,
+ uniq_2_case,
+ unzip_case,
+ unzip3_case,
+ usort_1_case,
+ usort_2_case,
+ zip_case,
+ zip3_case,
+ zipwith_case,
+ zipwith3_case
+ ].
+
+init_per_suite(Config) ->
+ ct_property_test:init_per_suite(Config).
+
+end_per_suite(Config) ->
+ persistent_term:erase({lists_prop, random_atoms}),
+ Config.
+
+do_proptest(Prop, Config) ->
+ ct_property_test:quickcheck(lists_prop:Prop(), Config).
+
+all_true_case(Config) ->
+ do_proptest(prop_all_true, Config).
+
+all_false_case(Config) ->
+ do_proptest(prop_all_false, Config).
+
+any_true_case(Config) ->
+ do_proptest(prop_any_true, Config).
+
+any_false_case(Config) ->
+ do_proptest(prop_any_false, Config).
+
+append_1_case(Config) ->
+ do_proptest(prop_append_1, Config).
+
+append_2_case(Config) ->
+ do_proptest(prop_append_2, Config).
+
+concat_case(Config) ->
+ do_proptest(prop_concat, Config).
+
+delete_case(Config) ->
+ do_proptest(prop_delete, Config).
+
+delete_absent_case(Config) ->
+ do_proptest(prop_delete_absent, Config).
+
+droplast_case(Config) ->
+ do_proptest(prop_droplast, Config).
+
+dropwhile_case(Config) ->
+ do_proptest(prop_dropwhile, Config).
+
+duplicate_case(Config) ->
+ do_proptest(prop_duplicate, Config).
+
+enumerate_1_case(Config) ->
+ do_proptest(prop_enumerate_1, Config).
+
+enumerate_2_case(Config) ->
+ do_proptest(prop_enumerate_2, Config).
+
+filter_case(Config) ->
+ do_proptest(prop_filter, Config).
+
+filtermap_case(Config) ->
+ do_proptest(prop_filtermap, Config).
+
+flatlength_case(Config) ->
+ do_proptest(prop_flatlength, Config).
+
+flatmap_case(Config) ->
+ do_proptest(prop_flatmap, Config).
+
+flatten_1_case(Config) ->
+ do_proptest(prop_flatten_1, Config).
+
+flatten_2_case(Config) ->
+ do_proptest(prop_flatten_2, Config).
+
+foldl_case(Config) ->
+ do_proptest(prop_foldl, Config).
+
+foldr_case(Config) ->
+ do_proptest(prop_foldr, Config).
+
+foreach_case(Config) ->
+ do_proptest(prop_foreach, Config).
+
+join_case(Config) ->
+ do_proptest(prop_join, Config).
+
+keydelete_case(Config) ->
+ do_proptest(prop_keydelete, Config).
+
+keydelete_absent_case(Config) ->
+ do_proptest(prop_keydelete_absent, Config).
+
+keyfind_case(Config) ->
+ do_proptest(prop_keyfind, Config).
+
+keyfind_absent_case(Config) ->
+ do_proptest(prop_keyfind_absent, Config).
+
+keymap_case(Config) ->
+ do_proptest(prop_keymap, Config).
+
+keymember_case(Config) ->
+ do_proptest(prop_keymember, Config).
+
+keymember_absent_case(Config) ->
+ do_proptest(prop_keymember_absent, Config).
+
+keymerge_case(Config) ->
+ do_proptest(prop_keymerge, Config).
+
+keyreplace_case(Config) ->
+ do_proptest(prop_keyreplace, Config).
+
+keyreplace_absent_case(Config) ->
+ do_proptest(prop_keyreplace_absent, Config).
+
+keysearch_case(Config) ->
+ do_proptest(prop_keysearch, Config).
+
+keysearch_absent_case(Config) ->
+ do_proptest(prop_keysearch_absent, Config).
+
+keysort_case(Config) ->
+ do_proptest(prop_keysort, Config).
+
+keystore_case(Config) ->
+ do_proptest(prop_keystore, Config).
+
+keystore_absent_case(Config) ->
+ do_proptest(prop_keystore_absent, Config).
+
+keytake_case(Config) ->
+ do_proptest(prop_keytake, Config).
+
+keytake_absent_case(Config) ->
+ do_proptest(prop_keytake_absent, Config).
+
+last_case(Config) ->
+ do_proptest(prop_last, Config).
+
+map_case(Config) ->
+ do_proptest(prop_map, Config).
+
+mapfoldl_case(Config) ->
+ do_proptest(prop_mapfoldl, Config).
+
+mapfoldr_case(Config) ->
+ do_proptest(prop_mapfoldr, Config).
+
+max_case(Config) ->
+ do_proptest(prop_max, Config).
+
+member_case(Config) ->
+ do_proptest(prop_member, Config).
+
+member_absent_case(Config) ->
+ do_proptest(prop_member_absent, Config).
+
+merge_1_case(Config) ->
+ do_proptest(prop_merge_1, Config).
+
+merge_2_case(Config) ->
+ do_proptest(prop_merge_2, Config).
+
+merge_3_case(Config) ->
+ do_proptest(prop_merge_3, Config).
+
+merge3_case(Config) ->
+ do_proptest(prop_merge3, Config).
+
+min_case(Config) ->
+ do_proptest(prop_min, Config).
+
+nth_case(Config) ->
+ do_proptest(prop_nth, Config).
+
+nth_outofrange_case(Config) ->
+ do_proptest(prop_nth_outofrange, Config).
+
+nthtail_case(Config) ->
+ do_proptest(prop_nthtail, Config).
+
+nthtail_outofrange_case(Config) ->
+ do_proptest(prop_nthtail_outofrange, Config).
+
+partition_case(Config) ->
+ do_proptest(prop_partition, Config).
+
+prefix_case(Config) ->
+ do_proptest(prop_prefix, Config).
+
+reverse_1_case(Config) ->
+ do_proptest(prop_reverse_1, Config).
+
+reverse_2_case(Config) ->
+ do_proptest(prop_reverse_2, Config).
+
+search_case(Config) ->
+ do_proptest(prop_search, Config).
+
+search_absent_case(Config) ->
+ do_proptest(prop_search_absent, Config).
+
+seq2_case(Config) ->
+ do_proptest(prop_seq2, Config).
+
+seq3_case(Config) ->
+ do_proptest(prop_seq3, Config).
+
+sort_1_case(Config) ->
+ do_proptest(prop_sort_1, Config).
+
+sort_2_case(Config) ->
+ do_proptest(prop_sort_2, Config).
+
+split_case(Config) ->
+ do_proptest(prop_split, Config).
+
+split_outofrange_case(Config) ->
+ do_proptest(prop_split_outofrange, Config).
+
+splitwith_case(Config) ->
+ do_proptest(prop_splitwith, Config).
+
+sublist_2_case(Config) ->
+ do_proptest(prop_sublist_2, Config).
+
+sublist_3_case(Config) ->
+ do_proptest(prop_sublist_3, Config).
+
+subtract_case(Config) ->
+ do_proptest(prop_subtract, Config).
+
+suffix_case(Config) ->
+ do_proptest(prop_suffix, Config).
+
+sum_case(Config) ->
+ do_proptest(prop_sum, Config).
+
+takewhile_case(Config) ->
+ do_proptest(prop_takewhile, Config).
+
+ukeymerge_case(Config) ->
+ do_proptest(prop_ukeymerge, Config).
+
+ukeysort_case(Config) ->
+ do_proptest(prop_ukeysort, Config).
+
+umerge_1_case(Config) ->
+ do_proptest(prop_umerge_1, Config).
+
+umerge_2_case(Config) ->
+ do_proptest(prop_umerge_2, Config).
+
+umerge_3_case(Config) ->
+ do_proptest(prop_umerge_3, Config).
+
+umerge3_case(Config) ->
+ do_proptest(prop_umerge3, Config).
+
+uniq_1_case(Config) ->
+ do_proptest(prop_uniq_1, Config).
+
+uniq_2_case(Config) ->
+ do_proptest(prop_uniq_2, Config).
+
+unzip_case(Config) ->
+ do_proptest(prop_unzip, Config).
+
+unzip3_case(Config) ->
+ do_proptest(prop_unzip3, Config).
+
+usort_1_case(Config) ->
+ do_proptest(prop_usort_1, Config).
+
+usort_2_case(Config) ->
+ do_proptest(prop_usort_2, Config).
+
+zip_case(Config) ->
+ do_proptest(prop_zip, Config).
+
+zip3_case(Config) ->
+ do_proptest(prop_zip3, Config).
+
+zipwith_case(Config) ->
+ do_proptest(prop_zipwith, Config).
+
+zipwith3_case(Config) ->
+ do_proptest(prop_zipwith3, Config).
+
diff --git a/lib/stdlib/test/property_test/lists_prop.erl b/lib/stdlib/test/property_test/lists_prop.erl
new file mode 100644
index 0000000000..6df00335c6
--- /dev/null
+++ b/lib/stdlib/test/property_test/lists_prop.erl
@@ -0,0 +1,1807 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2021. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(lists_prop).
+
+-compile([export_all, nowarn_export_all]).
+
+-proptest(eqc).
+-proptest([triq, proper]).
+
+-ifndef(EQC).
+-ifndef(PROPER).
+-ifndef(TRIQ).
+-define(EQC, true).
+-endif.
+-endif.
+-endif.
+
+-ifdef(EQC).
+-include_lib("eqc/include/eqc.hrl").
+-define(MOD_eqc,eqc).
+
+-else.
+-ifdef(PROPER).
+-include_lib("proper/include/proper.hrl").
+-define(MOD_eqc,proper).
+
+-else.
+-ifdef(TRIQ).
+-define(MOD_eqc,triq).
+-include_lib("triq/include/triq.hrl").
+
+-endif.
+-endif.
+-endif.
+
+-define(RANDOM_ATOMS, 1000).
+
+%%%%%%%%%%%%%%%%%%
+%%% Properties %%%
+%%%%%%%%%%%%%%%%%%
+
+%% all/2
+prop_all_true() ->
+ ?FORALL(
+ InList,
+ gen_list(),
+ lists:all(fun(_) -> true end, InList)
+ ).
+
+prop_all_false() ->
+ ?FORALL(
+ {InList, Elem},
+ ?LET(
+ {F, R, E},
+ {gen_list(), gen_list(), make_ref()},
+ {F ++ [E|R], E}
+ ),
+ not lists:all(fun(T) -> T =/= Elem end, InList)
+ ).
+
+%% any/2
+prop_any_true() ->
+ ?FORALL(
+ {InList, Elem},
+ ?LET(
+ {F, R, E},
+ {gen_list(), gen_list(), make_ref()},
+ {F ++ [E|R], E}
+ ),
+ lists:any(fun(T) -> T =:= Elem end, InList)
+ ).
+
+prop_any_false() ->
+ ?FORALL(
+ InList,
+ gen_list(),
+ not lists:any(fun(_) -> false end, InList)
+ ).
+
+%% append/1
+prop_append_1() ->
+ ?FORALL(
+ InLists,
+ list(gen_list()),
+ check_appended(InLists, lists:append(InLists))
+ ).
+
+%% append/2
+prop_append_2() ->
+ ?FORALL(
+ {InList1, InList2},
+ {gen_list(), gen_list()},
+ lists:append(InList1, InList2) =:= InList1 ++ InList2
+ ).
+
+%% concat/1
+prop_concat() ->
+ ?FORALL(
+ {InList, ExpString},
+ gen_list_fold(
+ oneof([gen_atom(), number(), string()]),
+ fun
+ (A, Acc) when is_atom(A) -> Acc ++ atom_to_list(A);
+ (I, Acc) when is_integer(I) -> Acc ++ integer_to_list(I);
+ (F, Acc) when is_float(F) -> Acc ++ float_to_list(F);
+ (L, Acc) when is_list(L) -> Acc ++ L
+ end,
+ []
+ ),
+ lists:concat(InList) =:= ExpString
+ ).
+
+%% delete/2
+prop_delete() ->
+ ?FORALL(
+ {InList, DelElem},
+ ?LET(
+ {F, R, E},
+ {gen_list(), gen_list(), gen_any()},
+ {F ++ [E|R], E}
+ ),
+ begin
+ DeletedList = lists:delete(DelElem, InList),
+ length(DeletedList) =:= length(InList) - 1 andalso
+ check_deleted(DelElem, InList, DeletedList)
+ end
+ ).
+
+prop_delete_absent() ->
+ ?FORALL(
+ InList,
+ gen_list(),
+ lists:delete(make_ref(), InList) =:= InList
+ ).
+
+%% droplast/1
+prop_droplast() ->
+ ?FORALL(
+ InList,
+ gen_list(),
+ try
+ lists:droplast(InList) =:= lists:reverse(tl(lists:reverse(InList)))
+ catch
+ error:_ ->
+ InList =:= []
+ end
+ ).
+
+%% dropwhile/2
+prop_dropwhile() ->
+ ?FORALL(
+ {Pred, InList, ExpList},
+ ?LET(
+ Fn,
+ function1(boolean()),
+ ?LET(
+ {L, {_, DL}},
+ gen_list_fold(
+ gen_any(),
+ fun(E, {Drop, Acc}) ->
+ case Drop andalso Fn(E) of
+ true -> {true, Acc};
+ false -> {false, Acc ++ [E]}
+ end
+ end,
+ {true, []}
+ ),
+ {Fn, L, DL}
+ )
+ ),
+ lists:dropwhile(Pred, InList) =:= ExpList
+ ).
+
+%% duplicate/2
+prop_duplicate() ->
+ ?FORALL(
+ {N, Term, ExpList},
+ ?LET(
+ T,
+ gen_any(),
+ ?LET(L, list(T), {length(L), T, L})
+ ),
+ lists:duplicate(N, Term) =:= ExpList
+ ).
+
+%% enumerate/1
+prop_enumerate_1() ->
+ ?FORALL(
+ {InList, ExpList},
+ ?LET(
+ {L, {_, EL}},
+ gen_list_fold(
+ gen_any(),
+ fun(T, {I, Acc}) ->
+ {I + 1, Acc ++ [{I, T}]}
+ end,
+ {1, []}
+ ),
+ {L, EL}
+ ),
+ lists:enumerate(InList) =:= ExpList
+ ).
+
+%% enumerate/2
+prop_enumerate_2() ->
+ ?FORALL(
+ {StartIndex, InList, ExpList},
+ ?LET(
+ N,
+ integer(),
+ ?LET(
+ {L, {_, EL}},
+ gen_list_fold(
+ gen_any(),
+ fun(T, {I, Acc}) ->
+ {I + 1, Acc ++ [{I, T}]}
+ end,
+ {N, []}
+ ),
+ {N, L, EL}
+ )
+ ),
+ lists:enumerate(StartIndex, InList) =:= ExpList
+ ).
+
+%% filter/2
+prop_filter() ->
+ ?FORALL(
+ {Pred, InList, ExpList},
+ ?LET(
+ P,
+ function1(boolean()),
+ ?LET(
+ {L, F},
+ gen_list_fold(
+ gen_any(),
+ fun(T, Acc) ->
+ case P(T) of
+ true -> Acc ++ [T];
+ false -> Acc
+ end
+ end,
+ []
+ ),
+ {P, L, F}
+ )
+ ),
+ lists:filter(Pred, InList) =:= ExpList
+ ).
+
+%% filtermap/2
+prop_filtermap() ->
+ ?FORALL(
+ {FilterMapFn, InList, ExpList},
+ ?LET(
+ Fn,
+ function1(oneof([true, false, {true, gen_any()}])),
+ ?LET(
+ {L, FM},
+ gen_list_fold(
+ gen_any(),
+ fun(T, Acc) ->
+ case Fn(T) of
+ false -> Acc;
+ true -> Acc ++ [T];
+ {true, T1} -> Acc ++ [T1]
+ end
+ end,
+ []
+ ),
+ {Fn, L, FM}
+ )
+ ),
+ lists:filtermap(FilterMapFn, InList) =:= ExpList
+ ).
+
+%% flatlength/1
+prop_flatlength() ->
+ ?FORALL(
+ {DeepList, Len},
+ gen_list_deepfold(fun(_, _, Cnt) -> Cnt + 1 end, 0),
+ lists:flatlength(DeepList) =:= Len
+ ).
+
+%% flatmap/2
+prop_flatmap() ->
+ ?FORALL(
+ {MapFn, InList, ExpList},
+ ?LET(
+ Fn,
+ function1(gen_list()),
+ ?LET(
+ {L, FlatMapped},
+ gen_list_fold(
+ gen_any(),
+ fun(T, Acc) ->
+ Acc ++ Fn(T)
+ end,
+ []
+ ),
+ {Fn, L, FlatMapped}
+ )
+ ),
+ lists:flatmap(MapFn, InList) =:= ExpList
+ ).
+
+%% flatten/1
+prop_flatten_1() ->
+ ?FORALL(
+ {DeepList, FlatList},
+ gen_list_deepfold(fun(_, E, Acc) -> Acc ++ [E] end, []),
+ lists:flatten(DeepList) =:= FlatList
+ ).
+
+%% flatten/2
+prop_flatten_2() ->
+ ?FORALL(
+ {{DeepList, FlatList}, Tail},
+ {gen_list_deepfold(fun(_, E, Acc) -> Acc ++ [E] end, []), gen_list()},
+ lists:flatten(DeepList, Tail) =:= FlatList ++ Tail
+ ).
+
+%% foldl/3
+prop_foldl() ->
+ ?FORALL(
+ {FoldFn, InList, Acc0, Exp},
+ ?LET(
+ {Fn, Acc0},
+ {function2(gen_any()), gen_any()},
+ ?LET(
+ {L, V},
+ gen_list_fold(gen_any(), Fn, Acc0),
+ {Fn, L, Acc0, V}
+ )
+ ),
+ lists:foldl(FoldFn, Acc0, InList) =:= Exp
+ ).
+
+%% foldr/3
+prop_foldr() ->
+ ?FORALL(
+ {FoldFn, InList, Acc0, Exp},
+ ?LET(
+ {Fn, Acc0},
+ {function2(gen_any()), gen_any()},
+ ?LET(
+ {L, V},
+ gen_list_fold(gen_any(), Fn, Acc0),
+ {Fn, lists:reverse(L), Acc0, V}
+ )
+ ),
+ lists:foldr(FoldFn, Acc0, InList) =:= Exp
+ ).
+
+%% foreach/2
+prop_foreach() ->
+ ?FORALL(
+ InList,
+ gen_list(),
+ begin
+ Tag = make_ref(),
+ lists:foreach(fun(E) -> self() ! {Tag, E} end, InList),
+ [receive {Tag, T} -> T after 100 -> error(timeout) end || _ <- InList] =:= InList
+ end
+ ).
+
+%% join/2
+prop_join() ->
+ ?FORALL(
+ {Sep, InList},
+ {gen_any(), gen_list()},
+ check_joined(Sep, InList, lists:join(Sep, InList))
+ ).
+
+%% keydelete/3
+prop_keydelete() ->
+ ?FORALL(
+ {Key, N, InList},
+ ?LET(
+ {K, N},
+ {gen_any(), range(1, 5)},
+ ?LET(
+ {F, R, E},
+ {gen_list(), gen_list(), gen_keytuple(K, N, N + 3)},
+ {K, N, F ++ [E|R]}
+ )
+ ),
+ begin
+ DeletedL = lists:keydelete(Key, N, InList),
+ length(DeletedL) =:= length(InList) - 1 andalso
+ check_keydeleted(Key, N, InList, DeletedL)
+ end
+ ).
+
+prop_keydelete_absent() ->
+ ?FORALL(
+ {N, InList},
+ {pos_integer(), gen_list()},
+ lists:keydelete(make_ref(), N, InList) =:= InList
+ ).
+
+%% keyfind/3
+prop_keyfind() ->
+ ?FORALL(
+ {Key, N, InList},
+ ?LET(
+ {K, N},
+ {gen_any(), range(1, 5)},
+ ?LET(
+ {F, R, E},
+ {gen_list(), gen_list(), gen_keytuple(K, N, N + 3)},
+ {K, N, F ++ [E|R]}
+ )
+ ),
+ begin
+ Found = lists:keyfind(Key, N, InList),
+ is_tuple(Found) andalso
+ tuple_size(Found) >= N andalso
+ element(N, Found) == Key
+ end
+ ).
+
+prop_keyfind_absent() ->
+ ?FORALL(
+ {N, InList},
+ {pos_integer(), gen_list()},
+ not lists:keyfind(make_ref(), N, InList)
+ ).
+
+%% keymap/3
+prop_keymap() ->
+ ?FORALL(
+ {MapFn, N, InList, ExpList},
+ ?LET(
+ Fn,
+ function([gen_any()], gen_any()),
+ ?LET(
+ N,
+ range(1, 5),
+ ?LET(
+ {L, M},
+ gen_list_fold(
+ gen_tuple(N, N + 3),
+ fun(T, Acc) ->
+ Acc ++ [setelement(N, T, Fn(element(N, T)))]
+ end,
+ []
+ ),
+ {Fn, N, L, M}
+ )
+ )
+ ),
+ lists:keymap(MapFn, N, InList) =:= ExpList
+ ).
+
+%% keymember/3
+prop_keymember() ->
+ ?FORALL(
+ {Key, N, InList},
+ ?LET(
+ {K, N},
+ {gen_any(), range(1, 5)},
+ ?LET(
+ {F, R, E},
+ {gen_list(), gen_list(), gen_keytuple(K, N, N + 3)},
+ {K, N, F ++ [E|R]}
+ )
+ ),
+ lists:keymember(Key, N, InList)
+ ).
+
+prop_keymember_absent() ->
+ ?FORALL(
+ {N, InList},
+ {pos_integer(), gen_list()},
+ not lists:keymember(make_ref(), N, InList)
+ ).
+
+%% keymerge/3
+prop_keymerge() ->
+ ?FORALL(
+ {N, InList1, InList2},
+ ?LET(
+ N,
+ range(1, 5),
+ ?LET(
+ {L1, L2},
+ {list(gen_tuple(N, N+3)), list(gen_tuple(N, N+3))},
+ {N, lists:sort(L1), lists:sort(L2)}
+ )
+ ),
+ check_merged(
+ fun (E1, E2) -> element(N, E1) =< element(N, E2) end,
+ [InList1, InList2],
+ lists:keymerge(N, InList1, InList2)
+ )
+ ).
+
+%% keyreplace/4
+prop_keyreplace() ->
+ ?FORALL(
+ {Key, N, InList, Replacement},
+ ?LET(
+ {K, N},
+ {gen_any(), range(1, 5)},
+ ?LET(
+ {F, R, E0, E1},
+ {gen_list(), gen_list(), gen_keytuple(K, N, N + 3), gen_tuple()},
+ {K, N, F ++ [E0|R], E1}
+ )
+ ),
+ check_keyreplaced(Key, N, Replacement, InList, lists:keyreplace(Key, N, InList, Replacement))
+ ).
+
+prop_keyreplace_absent() ->
+ ?FORALL(
+ {N, InList, Replacement},
+ {pos_integer(), gen_list(), gen_tuple()},
+ lists:keyreplace(make_ref(), N, InList, Replacement) =:= InList
+ ).
+
+%% keysearch/3
+prop_keysearch() ->
+ ?FORALL(
+ {Key, N, InList},
+ ?LET(
+ {K, N},
+ {gen_any(), range(1, 5)},
+ ?LET(
+ {F, R, E},
+ {gen_list(), gen_list(), gen_keytuple(K, N, N + 3)},
+ {K, N, F ++ [E|R]}
+ )
+ ),
+ begin
+ {value, Found} = lists:keysearch(Key, N, InList),
+ is_tuple(Found) andalso
+ tuple_size(Found) >= N andalso
+ element(N, Found) == Key
+ end
+ ).
+
+prop_keysearch_absent() ->
+ ?FORALL(
+ {N, InList},
+ {pos_integer(), gen_list()},
+ not lists:keysearch(make_ref(), N, InList)
+ ).
+
+%% keysort/2
+prop_keysort() ->
+ ?FORALL(
+ {N, InList},
+ ?LET(
+ N,
+ range(1, 5),
+ {N, list(gen_tuple(N, N + 3))}
+ ),
+ begin
+ Sorted = lists:keysort(N, InList),
+ length(Sorted) =:= length(InList) andalso
+ check_sorted(fun(E1, E2) -> element(N, E1) =< element(N, E2) end, InList, Sorted)
+ end
+ ).
+
+%% keystore/4
+prop_keystore() ->
+ ?FORALL(
+ {Key, N, InList, ToStore},
+ ?LET(
+ {K, N},
+ {gen_any(), range(1, 5)},
+ ?LET(
+ {F, R, E0, E1},
+ {gen_list(), gen_list(), gen_keytuple(K, N, N + 3), gen_tuple()},
+ {K, N, F ++ [E0|R], E1}
+ )
+ ),
+ check_keyreplaced(Key, N, ToStore, InList, lists:keystore(Key, N, InList, ToStore))
+ ).
+
+prop_keystore_absent() ->
+ ?FORALL(
+ {N, InList, ToStore},
+ {pos_integer(), gen_list(), gen_tuple()},
+ lists:keystore(make_ref(), N, InList, ToStore) =:= InList ++ [ToStore]
+ ).
+
+%% keytake/3
+prop_keytake() ->
+ ?FORALL(
+ {Key, N, InList, ExpList, ExpElem},
+ ?LET(
+ {K, N},
+ {make_ref(), range(1, 5)},
+ ?LET(
+ {F, R, E},
+ {gen_list(), gen_list(), gen_keytuple(K, N, N + 3)},
+ {K, N, F ++ [E|R], F ++ R, E}
+ )
+ ),
+ lists:keytake(Key, N, InList) =:= {value, ExpElem, ExpList}
+ ).
+
+prop_keytake_absent() ->
+ ?FORALL(
+ {N, InList},
+ {pos_integer(), gen_list()},
+ lists:keytake(make_ref(), N, InList) =:= false
+ ).
+
+%% last/1
+prop_last() ->
+ ?FORALL(
+ InList,
+ gen_list(),
+ try
+ lists:last(InList) =:= hd(lists:reverse(InList))
+ catch
+ error:_ ->
+ InList =:= []
+ end
+ ).
+
+%% map/2
+prop_map() ->
+ ?FORALL(
+ {MapFn, InList, ExpList},
+ ?LET(
+ Fn,
+ function1(gen_any()),
+ ?LET(
+ {L, M},
+ gen_list_fold(
+ gen_any(),
+ fun(T, Acc) ->
+ Acc ++ [Fn(T)]
+ end,
+ []
+ ),
+ {Fn, L, M}
+ )
+ ),
+ lists:map(MapFn, InList) =:= ExpList
+ ).
+
+%% mapfoldl/3
+prop_mapfoldl() ->
+ ?FORALL(
+ {MapFoldFn, InList, Acc0, Exp},
+ ?LET(
+ {MapFn, FoldFn, Acc0},
+ {function1(gen_any()), function2(gen_any()), gen_any()},
+ ?LET(
+ {L, MV},
+ gen_list_fold(
+ gen_any(),
+ fun(T, {AccM, AccF}) ->
+ {AccM ++ [MapFn(T)], FoldFn(T, AccF)}
+ end,
+ {[], Acc0}
+ ),
+ {fun(T, Acc) -> {MapFn(T), FoldFn(T, Acc)} end, L, Acc0, MV}
+ )
+ ),
+ lists:mapfoldl(MapFoldFn, Acc0, InList) =:= Exp
+ ).
+
+%% mapfoldr/3
+prop_mapfoldr() ->
+ ?FORALL(
+ {MapFoldFn, InList, Acc0, Exp},
+ ?LET(
+ {MapFn, FoldFn, Acc0},
+ {function1(gen_any()), function2(gen_any()), gen_any()},
+ ?LET(
+ {L, MV},
+ gen_list_fold(
+ gen_any(),
+ fun(T, {AccM, AccF}) ->
+ {[MapFn(T)|AccM], FoldFn(T, AccF)}
+ end,
+ {[], Acc0}
+ ),
+ {fun(T, Acc) -> {MapFn(T), FoldFn(T, Acc)} end, lists:reverse(L), Acc0, MV}
+ )
+ ),
+ lists:mapfoldr(MapFoldFn, Acc0, InList) =:= Exp
+ ).
+
+%% max/1
+prop_max() ->
+ ?FORALL(
+ {InList, ExpMax},
+ gen_list_fold(gen_any(), fun erlang:max/2),
+ try
+ lists:max(InList) == ExpMax
+ catch
+ error:_ ->
+ InList =:= []
+ end
+ ).
+
+%% member/2
+prop_member() ->
+ ?FORALL(
+ {InList, Member},
+ ?LET(
+ {F, R, E},
+ {gen_list(), gen_list(), gen_any()},
+ {F ++ [E|R], E}
+ ),
+ lists:member(Member, InList)
+ ).
+
+prop_member_absent() ->
+ ?FORALL(
+ InList,
+ gen_list(),
+ not lists:member(make_ref(), InList)
+ ).
+
+%% merge/1
+prop_merge_1() ->
+ ?FORALL(
+ InLists,
+ list(?LET(L, gen_list(), lists:sort(L))),
+ check_merged(fun erlang:'=<'/2, InLists, lists:merge(InLists))
+ ).
+
+%% merge/2
+prop_merge_2() ->
+ ?FORALL(
+ {InList1, InList2},
+ ?LET(
+ {L1, L2},
+ {gen_list(), gen_list()},
+ {lists:sort(L1), lists:sort(L2)}
+ ),
+ check_merged(fun erlang:'=<'/2, [InList1, InList2], lists:merge(InList1, InList2))
+ ).
+
+%% merge/3
+prop_merge_3() ->
+ ?FORALL(
+ {SortFn, InList1, InList2},
+ ?LET(
+ {Fn, L1, L2},
+ {gen_ordering_fun(), gen_list(), gen_list()},
+ {Fn, lists:sort(Fn, L1), lists:sort(Fn, L2)}
+ ),
+ check_merged(SortFn, [InList1, InList2], lists:merge(SortFn, InList1, InList2))
+ ).
+
+%% merge3/3
+prop_merge3() ->
+ ?FORALL(
+ {InList1, InList2, InList3},
+ ?LET(
+ {L1, L2, L3},
+ {gen_list(), gen_list(), gen_list()},
+ {lists:sort(L1), lists:sort(L2), lists:sort(L3)}
+ ),
+ check_merged(fun erlang:'=<'/2, [InList1, InList2, InList3], lists:merge3(InList1, InList2, InList3))
+ ).
+
+%% min/1
+prop_min() ->
+ ?FORALL(
+ {InList, ExpMin},
+ gen_list_fold(gen_any(), fun erlang:min/2),
+ try
+ lists:min(InList) == ExpMin
+ catch
+ error:_ ->
+ InList =:= []
+ end
+ ).
+
+%% nth/2
+prop_nth() ->
+ ?FORALL(
+ {InList, N, ExpElem},
+ ?LET(
+ {F, R, E},
+ {gen_list(), gen_list(), gen_any()},
+ {F ++ [E|R], length(F)+1, E}
+ ),
+ lists:nth(N, InList) =:= ExpElem
+ ).
+
+prop_nth_outofrange() ->
+ ?FORALL(
+ {N, InList},
+ ?LET(
+ {L, Offset},
+ {gen_list(), pos_integer()},
+ {length(L) + Offset, L}
+ ),
+ try
+ lists:nth(N, InList)
+ of
+ _ ->
+ false
+ catch
+ error:_ ->
+ true
+ end
+ ).
+
+%% nthtail/2
+prop_nthtail() ->
+ ?FORALL(
+ {InList, N, ExpTail},
+ ?LET(
+ {F, R},
+ {gen_list(), gen_list()},
+ {F ++ R, length(F), R}
+ ),
+ lists:nthtail(N, InList) =:= ExpTail
+ ).
+
+prop_nthtail_outofrange() ->
+ ?FORALL(
+ {N, InList},
+ ?LET(
+ {L, Offset},
+ {gen_list(), pos_integer()},
+ {length(L) + Offset, L}
+ ),
+ try
+ lists:nthtail(N, InList)
+ of
+ _ ->
+ false
+ catch
+ error:_ ->
+ true
+ end
+ ).
+
+%% partition/2
+prop_partition() ->
+ ?FORALL(
+ {Pred, InList},
+ {function1(boolean()), gen_list()},
+ begin
+ {Group1, Group2} = lists:partition(Pred, InList),
+ check_partitioned(Pred, InList, Group1, Group2)
+ end
+ ).
+
+%% prefix/2
+prop_prefix() ->
+ ?FORALL(
+ {InList, Prefix},
+ ?LET(
+ {F, R},
+ {gen_list(), gen_list()},
+ {F ++ R, F}
+ ),
+ lists:prefix(Prefix, InList) andalso
+ not lists:prefix([make_ref()|Prefix], InList) andalso
+ not lists:prefix(Prefix ++ [make_ref()], InList) andalso
+ (not lists:prefix(Prefix, [make_ref()|InList]) orelse Prefix =:= [])
+ ).
+
+%% reverse/1
+prop_reverse_1() ->
+ ?FORALL(
+ InList,
+ gen_list(),
+ check_reversed(InList, lists:reverse(InList)) andalso
+ lists:reverse(lists:reverse(InList)) =:= InList
+ ).
+
+%% reverse/2
+prop_reverse_2() ->
+ ?FORALL(
+ {InList, InTail},
+ {gen_list(), gen_list()},
+ check_reversed(InList, lists:reverse(InList, InTail), InTail)
+ ).
+
+%% search/2
+prop_search() ->
+ ?FORALL(
+ {Pred, InList, ExpElem},
+ ?LET(
+ {F, R, E},
+ {gen_list(), gen_list(), make_ref()},
+ {fun(T) -> T =:= E end, F ++ [E|R], E}
+ ),
+ lists:search(Pred, InList) =:= {value, ExpElem}
+ ).
+
+prop_search_absent() ->
+ ?FORALL(
+ InList,
+ gen_list(),
+ lists:search(fun(_) -> false end, InList) =:= false
+ ).
+
+%% seq/2
+prop_seq2() ->
+ ?FORALL(
+ {From, To},
+ {integer(), integer()},
+ try
+ lists:seq(From, To)
+ of
+ Seq ->
+ To >= From - 1 andalso
+ check_seq(Seq, From, To, 1)
+ catch
+ error:_ ->
+ To < From - 1
+ end
+ ).
+
+%% seq/3
+prop_seq3() ->
+ ?FORALL(
+ {From, To, Step},
+ {integer(), integer(), integer()},
+ try
+ lists:seq(From, To, Step)
+ of
+ Seq when Step > 0 ->
+ To >= From - Step andalso
+ check_seq(Seq, From, To, Step);
+ Seq when Step < 0 ->
+ To =< From - Step andalso
+ check_seq(Seq, From, To, Step);
+ Seq when Step =:= 0 ->
+ From =:= To andalso
+ check_seq(Seq, From, To, Step)
+ catch
+ error:_ when Step > 0 ->
+ To < From - Step;
+ error:_ when Step < 0 ->
+ To > From - Step;
+ error:_ when Step =:= 0 ->
+ From =/= To
+ end
+ ).
+
+%% sort/1
+prop_sort_1() ->
+ ?FORALL(
+ InList,
+ gen_list(),
+ begin
+ Sorted = lists:sort(InList),
+ length(Sorted) =:= length(InList) andalso
+ check_sorted(InList, Sorted)
+ end
+ ).
+
+%% sort/2
+prop_sort_2() ->
+ ?FORALL(
+ {SortFn, InList},
+ {gen_ordering_fun(), gen_list()},
+ begin
+ Sorted = lists:sort(SortFn, InList),
+ length(Sorted) =:= length(InList) andalso
+ check_sorted(SortFn, InList, Sorted)
+ end
+ ).
+
+%% split/2
+prop_split() ->
+ ?FORALL(
+ {N, InList, ExpList1, ExpList2},
+ ?LET(
+ {F, R},
+ {gen_list(), gen_list()},
+ {length(F), F ++ R, F, R}
+ ),
+ lists:split(N, InList) =:= {ExpList1, ExpList2}
+ ).
+
+prop_split_outofrange() ->
+ ?FORALL(
+ {N, InList},
+ ?LET(
+ {L, Offset},
+ {gen_list(), pos_integer()},
+ {length(L) + Offset, L}
+ ),
+ try
+ lists:split(N, InList)
+ of
+ _ ->
+ false
+ catch
+ error:_ ->
+ true
+ end
+ ).
+
+%% splitwith/2
+prop_splitwith() ->
+ ?FORALL(
+ {Pred, InList},
+ {function1(boolean()), gen_list()},
+ begin
+ {Part1, Part2} = lists:splitwith(Pred, InList),
+ check_splitwithed(Pred, InList, Part1, Part2)
+ end
+ ).
+
+%% sublist/2
+prop_sublist_2() ->
+ ?FORALL(
+ {Len, InList, ExpList},
+ ?LET(
+ {F, R},
+ {gen_list(), gen_list()},
+ {length(F), F ++ R, F}
+ ),
+ lists:sublist(InList, Len) =:= ExpList
+ ).
+
+%% sublist/3
+prop_sublist_3() ->
+ ?FORALL(
+ {Start, Len, InList, ExpList},
+ ?LET(
+ {F, M, R},
+ {gen_list(), gen_list(), gen_list()},
+ {length(F)+1, length(M), F ++ M ++ R, M}
+ ),
+ lists:sublist(InList, Start, Len) =:= ExpList
+ ).
+
+%% subtract/2
+prop_subtract() ->
+ ?FORALL(
+ {InList, SubtractList},
+ ?LET(
+ {L, B, S},
+ {gen_list(), gen_list(), gen_list()},
+ {L ++ B, S ++ B}
+ ),
+ lists:subtract(InList, SubtractList) =:= InList -- SubtractList
+ ).
+
+%% suffix/2
+prop_suffix() ->
+ ?FORALL(
+ {InList, Suffix},
+ ?LET(
+ {F, R},
+ {gen_list(), gen_list()},
+ {F ++ R, R}
+ ),
+ lists:suffix(Suffix, InList) andalso
+ not lists:suffix([make_ref()|Suffix], InList) andalso
+ not lists:suffix(Suffix ++ [make_ref()], InList) andalso
+ (not lists:suffix(Suffix, InList ++ [make_ref()]) orelse Suffix =:= [])
+ ).
+
+%% sum/1
+prop_sum() ->
+ ?FORALL(
+ {InList, ExpSum},
+ gen_list_fold(number(), fun erlang:'+'/2, 0),
+ lists:sum(InList) =:= ExpSum
+ ).
+
+%% takewhile/2
+prop_takewhile() ->
+ ?FORALL(
+ {Pred, InList, ExpList},
+ ?LET(
+ Fn,
+ function1(boolean()),
+ ?LET(
+ {L, {_, TL}},
+ gen_list_fold(
+ gen_any(),
+ fun(E, {Take, Acc}) ->
+ case Take andalso Fn(E) of
+ true -> {true, Acc ++ [E]};
+ false -> {false, Acc}
+ end
+ end,
+ {true, []}
+ ),
+ {Fn, L, TL}
+ )
+ ),
+ lists:takewhile(Pred, InList) =:= ExpList
+ ).
+
+%% ukeymerge/3
+prop_ukeymerge() ->
+ ?FORALL(
+ {N, InList1, InList2},
+ ?LET(
+ N,
+ range(1, 5),
+ ?LET(
+ {L1, L2},
+ {list(gen_tuple(N, N+3)), list(gen_tuple(N, N+3))},
+ {N, lists:ukeysort(N, L1), lists:ukeysort(N, L2)}
+ )
+ ),
+ check_umerged(
+ fun(E1, E2) -> element(N, E1) =< element(N, E2) end,
+ [InList1, InList2],
+ lists:ukeymerge(N, InList1, InList2)
+ )
+ ).
+
+%% ukeysort/2
+prop_ukeysort() ->
+ ?FORALL(
+ {N, InList},
+ ?LET(
+ N,
+ range(1, 5),
+ {N, list(gen_tuple(N, N + 3))}
+ ),
+ begin
+ Sorted = lists:ukeysort(N, InList),
+ length(Sorted) =< length(InList) andalso
+ check_usorted(fun(E1, E2) -> element(N, E1) =< element(N, E2) end, InList, Sorted)
+ end
+ ).
+
+%% umerge/1
+prop_umerge_1() ->
+ ?FORALL(
+ InLists,
+ list(?LET(L, gen_list(), lists:usort(L))),
+ check_umerged(InLists, lists:umerge(InLists))
+ ).
+
+%% umerge/2
+prop_umerge_2() ->
+ ?FORALL(
+ {InList1, InList2},
+ ?LET(
+ {L1, L2},
+ {gen_list(), gen_list()},
+ {lists:usort(L1), lists:usort(L2)}
+ ),
+ check_umerged([InList1, InList2], lists:umerge(InList1, InList2))
+ ).
+
+%% umerge/3
+prop_umerge_3() ->
+ ?FORALL(
+ {SortFn, InList1, InList2},
+ ?LET(
+ {Fn, L1, L2},
+ {gen_ordering_fun(), gen_list(), gen_list()},
+ {Fn, lists:usort(Fn, L1), lists:usort(Fn, L2)}
+ ),
+ check_umerged(SortFn, [InList1, InList2], lists:umerge(SortFn, InList1, InList2))
+ ).
+
+%% umerge3/3
+prop_umerge3() ->
+ ?FORALL(
+ {InList1, InList2, InList3},
+ ?LET(
+ {L1, L2, L3},
+ {gen_list(), gen_list(), gen_list()},
+ {lists:usort(L1), lists:usort(L2), lists:usort(L3)}
+ ),
+ check_umerged([InList1, InList2, InList3], lists:umerge3(InList1, InList2, InList3))
+ ).
+
+%% uniq/1
+prop_uniq_1() ->
+ ?FORALL(
+ InList,
+ ?LET(
+ {L, M},
+ {gen_list(), gen_list()},
+ ?LET(
+ S,
+ vector(length(L) + 2 * length(M), integer()),
+ [E || {_, E} <- lists:sort(lists:zip(S, L ++ M ++ M))]
+ )
+ ),
+ check_uniqed(InList, lists:uniq(InList))
+ ).
+
+%% uniq/2
+prop_uniq_2() ->
+ ?FORALL(
+ {UniqFn, InList},
+ {function1(oneof([a, b, c])), gen_list()},
+ check_uniqed(UniqFn, InList, lists:uniq(UniqFn, InList))
+ ).
+
+%% unzip/1
+prop_unzip() ->
+ ?FORALL(
+ {InList, {ExpList1, ExpList2}},
+ gen_list_fold(
+ {gen_any(), gen_any()},
+ fun({T1, T2}, {L1, L2}) ->
+ {L1 ++ [T1], L2 ++ [T2]}
+ end,
+ {[], []}
+ ),
+ lists:unzip(InList) =:= {ExpList1, ExpList2}
+ ).
+
+%% unzip3/1
+prop_unzip3() ->
+ ?FORALL(
+ {InList, {ExpList1, ExpList2, ExpList3}},
+ gen_list_fold(
+ {gen_any(), gen_any(), gen_any()},
+ fun({T1, T2, T3}, {L1, L2, L3}) ->
+ {L1 ++ [T1], L2 ++ [T2], L3 ++ [T3]}
+ end,
+ {[], [], []}
+ ),
+ lists:unzip3(InList) =:= {ExpList1, ExpList2, ExpList3}
+ ).
+
+%% usort/1
+prop_usort_1() ->
+ ?FORALL(
+ InList,
+ gen_list(),
+ begin
+ Sorted = lists:usort(InList),
+ length(Sorted) =< length(InList) andalso
+ check_usorted(InList, Sorted)
+ end
+ ).
+
+%% usort/2
+prop_usort_2() ->
+ ?FORALL(
+ {SortFn, InList},
+ {gen_ordering_fun(), gen_list()},
+ begin
+ Sorted = lists:usort(SortFn, InList),
+ length(Sorted) =< length(InList) andalso
+ check_usorted(SortFn, InList, Sorted)
+ end
+ ).
+
+%% zip/2
+prop_zip() ->
+ ?FORALL(
+ {ExpList, {InList1, InList2}},
+ gen_list_fold(
+ {gen_any(), gen_any()},
+ fun({T1, T2}, {L1, L2}) ->
+ {L1 ++ [T1], L2 ++ [T2]}
+ end,
+ {[], []}
+ ),
+ lists:zip(InList1, InList2) =:= ExpList
+ ).
+
+%% zip3/3
+prop_zip3() ->
+ ?FORALL(
+ {ExpList, {InList1, InList2, InList3}},
+ gen_list_fold(
+ {gen_any(), gen_any(), gen_any()},
+ fun({T1, T2, T3}, {L1, L2, L3}) ->
+ {L1 ++ [T1], L2 ++ [T2], L3 ++ [T3]}
+ end,
+ {[], [], []}
+ ),
+ lists:zip3(InList1, InList2, InList3) =:= ExpList
+ ).
+
+%% zipwith/3
+prop_zipwith() ->
+ ?FORALL(
+ {ZipFn, InList1, InList2, ExpList},
+ ?LET(
+ Fn,
+ function2(gen_any()),
+ ?LET(
+ {_, {L1, L2, Z}},
+ gen_list_fold(
+ {gen_any(), gen_any()},
+ fun({T1, T2}, {L1, L2, Z}) ->
+ {L1 ++ [T1], L2 ++ [T2], Z ++ [Fn(T1, T2)]}
+ end,
+ {[], [], []}
+ ),
+ {Fn, L1, L2, Z}
+ )
+ ),
+ lists:zipwith(ZipFn, InList1, InList2) =:= ExpList
+ ).
+
+%% zipwith3/4
+prop_zipwith3() ->
+ ?FORALL(
+ {ZipFn, InList1, InList2, InList3, ExpList},
+ ?LET(
+ Fn,
+ function3(gen_any()),
+ ?LET(
+ {_, {L1, L2, L3, Z}},
+ gen_list_fold(
+ {gen_any(), gen_any(), gen_any()},
+ fun({T1, T2, T3}, {L1, L2, L3, Z}) ->
+ {L1 ++ [T1], L2 ++ [T2], L3 ++ [T3], Z ++ [Fn(T1, T2, T3)]}
+ end,
+ {[], [], [], []}
+ ),
+ {Fn, L1, L2, L3, Z}
+ )
+ ),
+ lists:zipwith3(ZipFn, InList1, InList2, InList3) =:= ExpList
+ ).
+
+%%%%%%%%%%%%%%%%%%
+%%% Generators %%%
+%%%%%%%%%%%%%%%%%%
+
+%% Generator for lists of the given type, folding the given function
+%% over values on the top level as they are generated. The first generated
+%% value serves as the initial accumulator.
+gen_list_fold(Gen, FoldFn) ->
+ ?SIZED(
+ Size,
+ ?LET(
+ T,
+ Gen,
+ if
+ Size =< 1 ->
+ {[], T};
+ true ->
+ gen_list_fold(max(0, Size - 1), Gen, [T], FoldFn, T)
+ end
+ )
+ ).
+
+%% Generator for lists of the given type, folding the given function
+%% over values on the top level as they are generated.
+gen_list_fold(Gen, FoldFn, Acc0) ->
+ ?SIZED(
+ Size,
+ gen_list_fold(max(0, Size - 1), Gen, [], FoldFn, Acc0)
+ ).
+
+gen_list_fold(0, _Gen, L, _FoldFn, Acc) ->
+ {L, Acc};
+gen_list_fold(N, Gen, L, FoldFn, Acc) ->
+ ?LET(
+ E,
+ Gen,
+ gen_list_fold(N - 1, Gen, L ++ [E], FoldFn, FoldFn(E, Acc))
+ ).
+
+%% Generator for key tuples of the given size,
+%% with the given key in the given (ie, last) position.
+gen_keytuple(Key, Size) ->
+ gen_keytuple(Key, Size, Size).
+
+%% Generator for key tuples of the given minimum and maximum
+%% sizes, with the given key in the given minimum position.
+gen_keytuple(Key, MinSize, MaxSize) ->
+ ?LET(
+ Tuple,
+ gen_tuple(MinSize, MaxSize),
+ setelement(MinSize, Tuple, Key)
+ ).
+
+%% Generator for tuples of random size.
+gen_tuple() ->
+ ?LET(
+ N,
+ non_neg_integer(),
+ gen_tuple(N)
+ ).
+
+%% Generator for tuples of the given size.
+gen_tuple(Size) ->
+ ?LET(
+ V,
+ vector(Size, gen_any()),
+ list_to_tuple(V)
+ ).
+
+%% Generator for tuples of the given minimum and
+%% maximum sizes.
+gen_tuple(MinSize, MaxSize) ->
+ ?LET(
+ N,
+ range(MinSize, MaxSize),
+ ?LET(
+ V,
+ vector(N, gen_any()),
+ list_to_tuple(V)
+ )
+ ).
+
+%% Generator for lists of anything.
+gen_list() ->
+ list(gen_any()).
+
+%% Generator for lists of anything, folding the given function
+%% over values on all levels of list-nesting as they are generated.
+gen_list_deepfold(FoldFn, Acc0) ->
+ ?SIZED(
+ Size,
+ ?LET(
+ {_, L, Acc},
+ gen_list_deepfold(max(0, Size - 1), 0, [], FoldFn, Acc0),
+ {L, Acc}
+ )
+ ).
+
+gen_list_deepfold(N, _Level, L, _FoldFn, Acc) when N =< 0 ->
+ {N, lists:reverse(L), Acc};
+gen_list_deepfold(N, Level, L, FoldFn, Acc) ->
+ ?LET(
+ X,
+ frequency([
+ {4, {term, gen_any_simple()}},
+ {1, deeplist},
+ {1, tuple},
+ {2, stop}
+ ]),
+ case X of
+ deeplist ->
+ ?LET(
+ {N1, L1, Acc1},
+ gen_list_deepfold(N, Level + 1, [], FoldFn, Acc),
+ gen_list_deepfold(N1, Level, [L1|L], FoldFn, Acc1)
+ );
+ tuple ->
+ ?LET(
+ {N1, L1, _},
+ gen_list_deepfold(N, Level + 1, [], fun(_, _, _) -> undefined end, undefined),
+ begin
+ E = list_to_tuple(L1),
+ gen_list_deepfold(N1, Level, [E|L], FoldFn, FoldFn(Level, E, Acc))
+ end
+ );
+ stop ->
+ {N, lists:reverse(L), Acc};
+ {term, E} ->
+ gen_list_deepfold(N - 1, Level, [E|L], FoldFn, FoldFn(Level, E, Acc))
+ end
+ ).
+
+%% Generator for simple and composite (lists and tuples) types.
+gen_any() ->
+ frequency(
+ [
+ {4, gen_any_simple()},
+ {1, ?LET({L, _}, gen_list_deepfold(fun(_, _, Acc) -> Acc end, undefined), L)},
+ {1, ?LET({L, _}, gen_list_deepfold(fun(_, _, Acc) -> Acc end, undefined), list_to_tuple(L))}
+ ]
+ ).
+
+%% Generator for simple types:
+%% - atoms
+%% - integers
+%% - floats
+%% - bitstrings
+gen_any_simple() ->
+ oneof([gen_atom(), integer(), float(), bitstring()]).
+
+%% Generator for interesting atoms:
+%% - well-known atoms like `ok', `undefined', `infinity'...
+%% - randomly generated "weird" atoms
+gen_atom() ->
+ oneof(
+ [
+ oneof([ok, error, true, false, undefined, infinity]),
+ oneof(['', '"', '\'', '(', ')', '()', '[', '[', '[]', '{', '}', '{}']),
+ gen_random_atom()
+ ]
+ ).
+
+%% Generator for a limited set of random atoms. The number of
+%% atoms that will be generated is set in `?RANDOM_ATOMS'.
+gen_random_atom() ->
+ ?LAZY(
+ ?LET(
+ N,
+ range(1, ?RANDOM_ATOMS),
+ try
+ persistent_term:get({?MODULE, random_atoms})
+ of
+ Atoms ->
+ maps:get(N, Atoms)
+ catch
+ error:badarg ->
+ ?LET(
+ AtomsList,
+ vector(?RANDOM_ATOMS, ?SIZED(Size, resize(Size * 100, atom()))),
+ begin
+ Fn = fun
+ F(_, [], Acc) ->
+ Acc;
+ F(Index, [A|As], Acc) ->
+ F(Index + 1, As, Acc#{Index => A})
+ end,
+ Atoms = Fn(1, AtomsList, #{}),
+ persistent_term:put({?MODULE, random_atoms}, Atoms),
+ maps:get(N, Atoms)
+ end
+ )
+ end
+ )
+ ).
+
+%% Generator for ordering functions, to be used for sorting and merging.
+%% The generated ordering functions are designed to fulfill the requirements given
+%% at the top of the `lists' documentation, namely to be antisymmetric, transitive,
+%% and total. Further, the chances that two terms compare equal, less or greater
+%% are equal.
+gen_ordering_fun() ->
+ ?LET(
+ F,
+ function1(range(1, 3)),
+ fun(T1, T2) ->
+ F(T1) =< F(T2)
+ end
+ ).
+
+%%%%%%%%%%%%%%%
+%%% Helpers %%%
+%%%%%%%%%%%%%%%
+
+%% --------------------------------------------------------------------
+check_appended([], []) ->
+ true;
+check_appended([[]|Ls], AL) ->
+ check_appended(Ls, AL);
+check_appended([L], AL) ->
+ L =:= AL;
+check_appended([[E1|L]|Ls], [E2|AL]) ->
+ E1 =:= E2 andalso
+ check_appended([L|Ls], AL);
+check_appended(_Ls, _AL) ->
+ false.
+
+%% --------------------------------------------------------------------
+check_deleted(E, [E|L], DL) ->
+ L =:= DL;
+check_deleted(E, [_|L], [_|DL]) ->
+ check_deleted(E, L, DL);
+check_deleted(_E, [], []) ->
+ true;
+check_deleted(_E, _L, _DL) ->
+ false.
+
+%% --------------------------------------------------------------------
+check_joined(Sep, [E|L], [E, Sep|JL]) ->
+ check_joined(Sep, L, JL);
+check_joined(_Sep, [E], [E]) ->
+ true;
+check_joined(_Sep, [], []) ->
+ true;
+check_joined(_Sep, _L, _JL) ->
+ false.
+
+%% --------------------------------------------------------------------
+check_keydeleted(K, N, [E|L], KDL) when element(N, E) == K ->
+ L =:= KDL;
+check_keydeleted(K, N, [_|L], [_|KDL]) ->
+ check_keydeleted(K, N, L, KDL);
+check_keydeleted(_K, _N, _L, _KDL) ->
+ false.
+
+%% --------------------------------------------------------------------
+check_keyreplaced(K, N, R, [E1|L], [E2|KRL]) when element(N, E1) == K ->
+ E2 =:= R andalso L =:= KRL;
+check_keyreplaced(K, N, R, [_|L], [_|KRL]) ->
+ check_keyreplaced(K, N, R, L, KRL);
+check_keyreplaced(_K, _N, _R, _L, _KRL) ->
+ false.
+
+%% --------------------------------------------------------------------
+check_merged(Ls, ML) ->
+ check_merged(fun erlang:'=<'/2, Ls, ML).
+
+check_merged(Fn, [[]|Ls], ML) ->
+ check_merged(Fn, Ls, ML);
+check_merged(_Fn, [], ML) ->
+ ML =:= [];
+check_merged(_Fn, [L], ML) ->
+ ML =:= L;
+check_merged(Fn, Ls, [E|ML]) ->
+ case find_in_heads(Fn, E, Ls) of
+ {true, Ls1} ->
+ check_merged(Fn, Ls1, ML);
+ false ->
+ false
+ end;
+check_merged(_Fn, _Ls, _ML) ->
+ false.
+
+find_in_heads(Fn, E, Ls) ->
+ find_in_heads(Fn, E, Ls, []).
+
+find_in_heads(Fn, E, [[]|Ls], Seen) ->
+ find_in_heads(Fn, E, Ls, Seen);
+find_in_heads(Fn, E, [[E1|LRest]=L|Ls], Seen) ->
+ case Fn(E, E1) andalso Fn(E1, E) of
+ true ->
+ {true, lists:reverse(Seen, [LRest|Ls])};
+ false ->
+ find_in_heads(Fn, E, Ls, [L|Seen])
+ end;
+find_in_heads(_Fn, _E, _Ls, _Seen) ->
+ false.
+
+%% --------------------------------------------------------------------
+check_partitioned(Pred, [E|L], P1, P2) ->
+ case {Pred(E), P1, P2} of
+ {true, [E|Rest], _} ->
+ check_partitioned(Pred, L, Rest, P2);
+ {false, _, [E|Rest]} ->
+ check_partitioned(Pred, L, P1, Rest);
+ _ ->
+ false
+ end;
+check_partitioned(_Pred, [], [], []) ->
+ true;
+check_partitioned(_Pred, _L, _P1, _P2) ->
+ false.
+
+%% --------------------------------------------------------------------
+check_reversed(L1, L2) ->
+ check_reversed(L1, L2, []).
+
+check_reversed(L1, L2, Tail) ->
+ check_reversed1(L1, L2) =:= Tail.
+
+check_reversed1([], L2) ->
+ L2;
+check_reversed1([E|L1], L2) ->
+ case check_reversed1(L1, L2) of
+ [E|L2Rest] -> L2Rest;
+ _ -> false
+ end.
+
+%% --------------------------------------------------------------------
+check_seq([F|Seq], F, T, S) ->
+ check_seq(Seq, F + S, T, S);
+check_seq([], F, T, S) when S >= 0 ->
+ F >= T;
+check_seq([], F, T, S) when S < 0 ->
+ F =< T;
+check_seq(_Seq, _F, _T, _S) ->
+ false.
+
+%% --------------------------------------------------------------------
+check_sorted(L, Sorted) ->
+ check_sorted(fun erlang:'=<'/2, L, Sorted).
+
+check_sorted(SortFun, L, Sorted) ->
+ ExpElems = count_elems(L),
+ check_sorted(SortFun, Sorted, ExpElems, #{}).
+
+check_sorted(_SortFun, [], ExpElems, FoundElems) ->
+ ExpElems =:= FoundElems;
+check_sorted(SortFun, [E], ExpElems, FoundElems) ->
+ maps:is_key(E, ExpElems) andalso
+ check_sorted(SortFun, [], ExpElems, maps:update_with(E, fun(Cnt) -> Cnt + 1 end, 1, FoundElems));
+check_sorted(SortFun, [E1|[E2|_]=L], ExpElems, FoundElems) ->
+ SortFun(E1, E2) andalso
+ maps:is_key(E1, ExpElems) andalso
+ check_sorted(SortFun, L, ExpElems, maps:update_with(E1, fun(Cnt) -> Cnt + 1 end, 1, FoundElems));
+check_sorted(_SortFun, _L, _ExpElems, _FoundElems) ->
+ false.
+
+count_elems(L) ->
+ count_elems(L, #{}).
+
+count_elems([E|Es], Acc) ->
+ count_elems(Es, maps:update_with(E, fun(Cnt) -> Cnt + 1 end, 1, Acc));
+count_elems([], Acc) ->
+ Acc.
+
+%% --------------------------------------------------------------------
+check_splitwithed(Pred, [E|L], [E|P1], P2) ->
+ Pred(E) andalso
+ check_splitwithed(Pred, L, P1, P2);
+check_splitwithed(Pred, [E|_]=L, [], P2) ->
+ not Pred(E) andalso L =:= P2;
+check_splitwithed(_Pred, [], [], []) ->
+ true;
+check_splitwithed(_Pred, _L, _P1, _P2) ->
+ false.
+
+%% --------------------------------------------------------------------
+check_umerged(Ls, ML) ->
+ check_umerged(fun erlang:'=<'/2, Ls, ML).
+
+check_umerged(Fn, [[]|Ls], ML) ->
+ check_umerged(Fn, Ls, ML);
+check_umerged(_Fn, [L], ML) ->
+ ML =:= L;
+check_umerged(_Fn, [], ML) ->
+ ML =:= [];
+check_umerged(Fn, Ls, [E|ML]) ->
+ case find_and_remove_from_heads(Fn, E, Ls) of
+ {true, Ls1} ->
+ check_umerged(Fn, Ls1, ML);
+ false ->
+ false
+ end;
+check_umerged(_Fn, _Ls, _ML) ->
+ false.
+
+find_and_remove_from_heads(Fn, E, Ls) ->
+ find_and_remove_from_heads(false, Fn, E, Ls, []).
+
+find_and_remove_from_heads(Found, Fn, E, [[]|Ls], Seen) ->
+ find_and_remove_from_heads(Found, Fn, E, Ls, Seen);
+find_and_remove_from_heads(false, _Fn, _E, [], _Seen) ->
+ false;
+find_and_remove_from_heads(true, _Fn, _E, [], Seen) ->
+ {true, lists:reverse(Seen)};
+find_and_remove_from_heads(Found, Fn, E, [[E1|LRest]=L|Ls], Seen) ->
+ case Fn(E, E1) andalso Fn(E1, E) of
+ true ->
+ find_and_remove_from_heads(true, Fn, E, Ls, [LRest|Seen]);
+ false ->
+ find_and_remove_from_heads(Found, Fn, E, Ls, [L|Seen])
+ end.
+
+%% --------------------------------------------------------------------
+check_uniqed(L, UL) ->
+ check_uniqed(fun(X) -> X end, L, UL).
+
+check_uniqed(Fn, L, UL) ->
+ check_uniqed1(Fn, L, UL, sets:new([{version, 2}])).
+
+check_uniqed1(Fn, [E|L], [], Seen) ->
+ sets:is_element(Fn(E), Seen) andalso
+ check_uniqed1(Fn, L, [], Seen);
+check_uniqed1(Fn, [E1|L], [E2|URest]=U, Seen) ->
+ X1 = Fn(E1),
+ X2 = Fn(E2),
+ case sets:is_element(X1, Seen) of
+ true ->
+ X1 =/= X2 andalso
+ check_uniqed1(Fn, L, U, Seen);
+ false ->
+ X1 =:= X2 andalso
+ check_uniqed1(Fn, L, URest, sets:add_element(X1, Seen))
+ end;
+check_uniqed1(_Fn, [], [], _Seen) ->
+ true;
+check_uniqed1(_Fn, _L, _UL, _Seen) ->
+ false.
+
+%% --------------------------------------------------------------------
+check_usorted(L, Sorted) ->
+ check_usorted(fun erlang:'=<'/2, L, Sorted).
+
+check_usorted(SortFun, L, Sorted) ->
+ ExpElems = ucount_elems(SortFun, L),
+ check_sorted(SortFun, Sorted, ExpElems, #{}).
+
+ucount_elems(SortFun, L) ->
+ ucount_elems(SortFun, L, #{}).
+
+ucount_elems(SortFun, [E|Es], Acc) ->
+ K = ufind_key(SortFun, E, maps:keys(Acc)),
+ ucount_elems(SortFun, Es, maps:put(K, 1, Acc));
+ucount_elems(_SortFun, [], Acc) ->
+ Acc.
+
+ufind_key(SortFun, E, [K|Keys]) ->
+ case SortFun(E, K) andalso SortFun(K, E) of
+ true ->
+ K;
+ false ->
+ ufind_key(SortFun, E, Keys)
+ end;
+ufind_key(_SortFun, E, []) ->
+ E.
--
2.35.3