Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:26
erlang
2371-add-higher-lower-search-functions-in-gb_tr...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 2371-add-higher-lower-search-functions-in-gb_trees-and-gb.patch of Package erlang
From 1595acf0810451f3fdff4080bc77d71d59cafc2b Mon Sep 17 00:00:00 2001 From: Zeyu Zhang <zeyu@fb.com> Date: Wed, 11 Oct 2023 14:27:04 -0700 Subject: [PATCH] add higher/lower search functions in gb_trees and gb_sets --- lib/stdlib/doc/src/gb_sets.xml | 63 ++++++- lib/stdlib/doc/src/gb_trees.xml | 66 +++++++- lib/stdlib/src/gb_sets.erl | 141 +++++++++++++--- lib/stdlib/src/gb_trees.erl | 146 ++++++++++++---- .../test/gb_sets_property_test_SUITE.erl | 8 + .../test/property_test/gb_sets_prop.erl | 156 ++++++++++++++++-- 6 files changed, 500 insertions(+), 80 deletions(-) diff --git a/lib/stdlib/doc/src/gb_sets.xml b/lib/stdlib/doc/src/gb_sets.xml index 41443f7b04..7a725e33ac 100644 --- a/lib/stdlib/doc/src/gb_sets.xml +++ b/lib/stdlib/doc/src/gb_sets.xml @@ -303,10 +303,22 @@ <desc> <p>Returns an iterator that can be used for traversing the entries of <c><anno>Set</anno></c>; see - <seemfa marker="#next/1"><c>next/1</c></seemfa>. The implementation - of this is very efficient; traversing the whole set using - <c>next/1</c> is only slightly slower than getting the list of all - elements using <seemfa marker="#to_list/1"><c>to_list/1</c></seemfa> + <seemfa marker="#next/1"><c>next/1</c></seemfa>.</p> + <p>Equivalent to <c>iterator(<anno>Set</anno>, ordered)</c>.</p> + </desc> + </func> + + <func> + <name name="iterator" arity="2" since=""/> + <fsummary>Return an iterator for a set.</fsummary> + <desc> + <p>Returns an iterator that can be used for traversing the entries of + <c><anno>Set</anno></c> in either <c>ordered</c> or <c>reversed</c> + direction; see <seemfa marker="#next/1"><c>next/1</c></seemfa>. + The implementation of this is very efficient; traversing the whole + set using <c>next/1</c> is only slightly slower than getting the list + of all elements using + <seemfa marker="#to_list/1"><c>to_list/1</c></seemfa> and traversing that. The main advantage of the iterator approach is that it does not require the complete list of all elements to be built in @@ -324,8 +336,36 @@ <seemfa marker="#next/1"><c>next/1</c></seemfa>. The difference as compared to the iterator returned by <seemfa marker="#iterator/1"><c>iterator/1</c></seemfa> - is that the first element greater than - or equal to <c><anno>Element</anno></c> is returned.</p> + is that the iterator starts with the first element greater than + or equal to <c><anno>Element</anno></c>.</p> + <p>Equivalent to <c>iterator_from(<anno>Element</anno>, + <anno>Set</anno>, ordered)</c>.</p> + </desc> + </func> + + <func> + <name name="iterator_from" arity="3" since="OTP 18.0"/> + <fsummary>Return an iterator for a set starting from a specified element. + </fsummary> + <desc> + <p>Returns an iterator that can be used for traversing the + entries of <c><anno>Set</anno></c>; see + <seemfa marker="#next/1"><c>next/1</c></seemfa>. + The difference as compared to the iterator returned by + <seemfa marker="#iterator/2"><c>iterator/2</c></seemfa> + is that the iterator starts with the first element next to + or equal to <c><anno>Element</anno></c>.</p> + </desc> + </func> + + <func> + <name name="larger" arity="2" since=""/> + <fsummary>Return larger element.</fsummary> + <desc> + <p>Returns <c>{found, <anno>Element2</anno>}</c>, where + <c><anno>Element2</anno></c> is the least element strictly greater + than <c><anno>Element1</anno></c>.</p> + <p>Returns <c>none</c> if no such element exists.</p> </desc> </func> @@ -385,6 +425,17 @@ </desc> </func> + <func> + <name name="smaller" arity="2" since=""/> + <fsummary>Return smaller element.</fsummary> + <desc> + <p>Returns <c>{found, <anno>Element2</anno>}</c>, where + <c><anno>Element2</anno></c> is the greatest element strictly less + than <c><anno>Element1</anno></c>.</p> + <p>Returns <c>none</c> if no such element exists.</p> + </desc> + </func> + <func> <name name="smallest" arity="1" since=""/> <fsummary>Return smallest element.</fsummary> diff --git a/lib/stdlib/doc/src/gb_trees.xml b/lib/stdlib/doc/src/gb_trees.xml index c8944347a5..2e708f69c7 100644 --- a/lib/stdlib/doc/src/gb_trees.xml +++ b/lib/stdlib/doc/src/gb_trees.xml @@ -202,10 +202,21 @@ <desc> <p>Returns an iterator that can be used for traversing the entries of <c><anno>Tree</anno></c>; see - <seemfa marker="#next/1"><c>next/1</c></seemfa>. The implementation - of this is very efficient; traversing the whole tree using - <c>next/1</c> is only slightly slower than getting the list - of all elements using + <seemfa marker="#next/1"><c>next/1</c></seemfa>.</p> + <p>Equivalent to <c>iterator(<anno>Tree</anno>, ordered)</c>.</p> + </desc> + </func> + + <func> + <name name="iterator" arity="2" since=""/> + <fsummary>Return an iterator for a tree.</fsummary> + <desc> + <p>Returns an iterator that can be used for traversing the entries of + <c><anno>Tree</anno></c> in either <c>ordered</c> or <c>reversed</c> + direction; see <seemfa marker="#next/1"><c>next/1</c></seemfa>. + The implementation of this is very efficient; traversing the whole + tree using <c>next/1</c> is only slightly slower than getting the + list of all elements using <seemfa marker="#to_list/1"><c>to_list/1</c></seemfa> and traversing that. The main advantage of the iterator approach is that it does @@ -224,8 +235,25 @@ <seemfa marker="#next/1"><c>next/1</c></seemfa>. The difference as compared to the iterator returned by <seemfa marker="#iterator/1"><c>iterator/1</c></seemfa> - is that the first key greater than - or equal to <c><anno>Key</anno></c> is returned.</p> + is that the iterator starts with the first key greater than + or equal to <c><anno>Key</anno></c>.</p> + <p>Equivalent to <c>iterator_from(<anno>Key</anno>, <anno>Tree</anno>, + ordered)</c>.</p> + </desc> + </func> + + <func> + <name name="iterator_from" arity="3" since=""/> + <fsummary>Return an iterator for a tree starting from a specified key. + </fsummary> + <desc> + <p>Returns an iterator that can be used for traversing the entries of + <c><anno>Tree</anno></c> in either <c>ordered</c> or <c>reversed</c> + direction; see <seemfa marker="#next/1"><c>next/1</c></seemfa>. + The difference as compared to the iterator returned by + <seemfa marker="#iterator/2"><c>iterator/2</c></seemfa> + is that the iterator starts with the first key next to + or equal to <c><anno>Key</anno></c>.</p> </desc> </func> @@ -237,6 +265,18 @@ </desc> </func> + <func> + <name name="larger" arity="2" since=""/> + <fsummary>Return larger key and value.</fsummary> + <desc> + <p>Returns <c>{<anno>Key2</anno>, <anno>Value</anno>}</c>, where + <c><anno>Key2</anno></c> is the least key strictly greater than + <c><anno>Key1</anno></c>, <c><anno>Value</anno></c> is the value + associated with this key.</p> + <p>Returns <c>none</c> if no such pair exists.</p> + </desc> + </func> + <func> <name name="largest" arity="1" since=""/> <fsummary>Return largest key and value.</fsummary> @@ -277,7 +317,7 @@ <desc> <p>Returns <c>{<anno>Key</anno>, <anno>Value</anno>, <anno>Iter2</anno>}</c>, where <c><anno>Key</anno></c> is the - smallest key referred to by iterator <c><anno>Iter1</anno></c>, and + next key referred to by iterator <c><anno>Iter1</anno></c>, and <c><anno>Iter2</anno></c> is the new iterator to be used for traversing the remaining nodes, or the atom <c>none</c> if no nodes remain.</p> @@ -292,6 +332,18 @@ </desc> </func> + <func> + <name name="smaller" arity="2" since=""/> + <fsummary>Return smaller key and value.</fsummary> + <desc> + <p>Returns <c>{<anno>Key2</anno>, <anno>Value</anno>}</c>, where + <c><anno>Key2</anno></c> is the greatest key strictly less than + <c><anno>Key1</anno></c>, <c><anno>Value</anno></c> is the value + associated with this key.</p> + <p>Returns <c>none</c> if no such pair exists.</p> + </desc> + </func> + <func> <name name="smallest" arity="1" since=""/> <fsummary>Return smallest key and value.</fsummary> diff --git a/lib/stdlib/src/gb_sets.erl b/lib/stdlib/src/gb_sets.erl index f94996a669..c0d886ba83 100644 --- a/lib/stdlib/src/gb_sets.erl +++ b/lib/stdlib/src/gb_sets.erl @@ -123,17 +123,30 @@ %% set S, and S1 is the set S with element X deleted. Assumes that the %% set S is nonempty. %% +%% - smaller(X, S): returns {`found', X1}, where X1 is the greatest element +%% strictly less than X, or `none' if no such element exists. +%% +%% - larger(X, S): returns {`found', X1}, where X1 is the least element +%% strictly greater than K, or `none' if no such element exists. +%% %% - iterator(S): returns an iterator that can be used for traversing -%% the entries of set S; see `next'. The implementation of this is -%% very efficient; traversing the whole set using `next' is only -%% slightly slower than getting the list of all elements using -%% `to_list' and traversing that. The main advantage of the iterator +%% the entries of set S; see `next'. Equivalent to iterator(T, ordered). +%% +%% - iterator(S, Order): returns an iterator that can be used for traversing +%% the entries of set S in either ordered or reversed direction; see `next'. +%% The implementation of this is very efficient; traversing the whole set +%% using `next' is only slightly slower than getting the list of all elements +%% using `to_list' and traversing that. The main advantage of the iterator %% approach is that it does not require the complete list of all %% elements to be built in memory at one time. %% %% - iterator_from(X, S): returns an iterator that can be used for %% traversing the elements of set S greater than or equal to X; -%% see `next'. +%% see `next'. Equivalent to iterator_from(X, S, ordered). +%% +%% - iterator_from(X, S, Order): returns an iterator that can be used for +%% traversing the elements of set S in either ordered or reversed direction, +%% starting from the element equal to or closest to X; see `next'. %% %% - next(T): returns {X, T1} where X is the smallest element referred %% to by the iterator T, and T1 is the new iterator to be used for @@ -156,9 +169,9 @@ union/1, intersection/2, intersection/1, is_equal/2, is_disjoint/2, difference/2, is_subset/2, to_list/1, from_list/1, from_ordset/1, smallest/1, largest/1, - take_smallest/1, take_largest/1, iterator/1, - iterator_from/2, next/1, filter/2, fold/3, map/2, - filtermap/2, is_set/1]). + take_smallest/1, take_largest/1, smaller/2, larger/2, + iterator/1, iterator/2, iterator_from/2, iterator_from/3, + next/1, filter/2, fold/3, map/2, filtermap/2, is_set/1]). %% `sets' compatibility aliases: @@ -201,7 +214,7 @@ -type gb_set_node(Element) :: 'nil' | {Element, _, _}. -opaque set(Element) :: {non_neg_integer(), gb_set_node(Element)}. -type set() :: set(_). --opaque iter(Element) :: [gb_set_node(Element)]. +-opaque iter(Element) :: {ordered | reversed, [gb_set_node(Element)]}. -type iter() :: iter(_). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -495,6 +508,44 @@ largest_1({Key, _Smaller, nil}) -> largest_1({_Key, _Smaller, Larger}) -> largest_1(Larger). +-spec smaller(Element1, Set) -> none | {found, Element2} when + Element1 :: Element, + Element2 :: Element, + Set :: set(Element). +smaller(Key, {_, T}) -> + smaller_1(Key, T). + +smaller_1(_Key, nil) -> + none; +smaller_1(Key, {Key1, _Smaller, Larger}) when Key > Key1 -> + case smaller_1(Key, Larger) of + none -> + {found, Key1}; + Found -> + Found + end; +smaller_1(Key, {_Key, Smaller, _Larger}) -> + smaller_1(Key, Smaller). + +-spec larger(Element1, Set) -> none | {found, Element2} when + Element1 :: Element, + Element2 :: Element, + Set :: set(Element). +larger(Key, {_, T}) -> + larger_1(Key, T). + +larger_1(_Key, nil) -> + none; +larger_1(Key, {Key1, Smaller, _Larger}) when Key < Key1 -> + case larger_1(Key, Smaller) of + none -> + {found, Key1}; + Found -> + Found + end; +larger_1(Key, {_Key, _Smaller, Larger}) -> + larger_1(Key, Larger). + -spec to_list(Set) -> List when Set :: set(Element), List :: [Element]. @@ -512,42 +563,80 @@ to_list(nil, L) -> L. Set :: set(Element), Iter :: iter(Element). -iterator({_, T}) -> - iterator(T, []). +iterator(Set) -> + iterator(Set, ordered). + +-spec iterator(Set, Order) -> Iter when + Set :: set(Element), + Iter :: iter(Element), + Order :: ordered | reversed. + +iterator({_, T}, ordered) -> + {ordered, iterator_1(T, [])}; +iterator({_, T}, reversed) -> + {reversed, iterator_r(T, [])}. %% The iterator structure is really just a list corresponding to the %% call stack of an in-order traversal. This is quite fast. -iterator({_, nil, _} = T, As) -> +iterator_1({_, nil, _} = T, As) -> [T | As]; -iterator({_, L, _} = T, As) -> - iterator(L, [T | As]); -iterator(nil, As) -> +iterator_1({_, L, _} = T, As) -> + iterator_1(L, [T | As]); +iterator_1(nil, As) -> + As. + +iterator_r({_, _, nil} = T, As) -> + [T | As]; +iterator_r({_, _, R} = T, As) -> + iterator_r(R, [T | As]); +iterator_r(nil, As) -> As. -spec iterator_from(Element, Set) -> Iter when Set :: set(Element), Iter :: iter(Element). -iterator_from(S, {_, T}) -> - iterator_from(S, T, []). +iterator_from(Element, Set) -> + iterator_from(Element, Set, ordered). + +-spec iterator_from(Element, Set, Order) -> Iter when + Set :: set(Element), + Iter :: iter(Element), + Order :: ordered | reversed. + +iterator_from(S, {_, T}, ordered) -> + {ordered, iterator_from_1(S, T, [])}; +iterator_from(S, {_, T}, reversed) -> + {reversed, iterator_from_r(S, T, [])}. + +iterator_from_1(S, {K, _, T}, As) when K < S -> + iterator_from_1(S, T, As); +iterator_from_1(_, {_, nil, _} = T, As) -> + [T | As]; +iterator_from_1(S, {_, L, _} = T, As) -> + iterator_from_1(S, L, [T | As]); +iterator_from_1(_, nil, As) -> + As. -iterator_from(S, {K, _, T}, As) when K < S -> - iterator_from(S, T, As); -iterator_from(_, {_, nil, _} = T, As) -> +iterator_from_r(S, {K, T, _}, As) when K > S -> + iterator_from_r(S, T, As); +iterator_from_r(_, {_, _, nil} = T, As) -> [T | As]; -iterator_from(S, {_, L, _} = T, As) -> - iterator_from(S, L, [T | As]); -iterator_from(_, nil, As) -> +iterator_from_r(S, {_, _, R} = T, As) -> + iterator_from_r(S, R, [T | As]); +iterator_from_r(_, nil, As) -> As. -spec next(Iter1) -> {Element, Iter2} | 'none' when Iter1 :: iter(Element), Iter2 :: iter(Element). -next([{X, _, T} | As]) -> - {X, iterator(T, As)}; -next([]) -> +next({ordered, [{X, _, T} | As]}) -> + {X, {ordered, iterator_1(T, As)}}; +next({reversed, [{X, T, _} | As]}) -> + {X, {reversed, iterator_r(T, As)}}; +next({_, []}) -> none. diff --git a/lib/stdlib/src/gb_trees.erl b/lib/stdlib/src/gb_trees.erl index 54a5ab6690..6e489d86ff 100644 --- a/lib/stdlib/src/gb_trees.erl +++ b/lib/stdlib/src/gb_trees.erl @@ -95,19 +95,32 @@ %% in tree T, V is the value associated with X in T, and T1 is the %% tree T with key X deleted. Assumes that the tree T is nonempty. %% +%% - smaller(K, T): returns {Key, Value} pair, where Key is the +%% greatest key strictly less than K, or `none' if no such key exists. +%% +%% - larger(K, T): returns {Key, Value} pair, where Key is the +%% least key strictly greater than K, or `none' if no such key exists. +%% %% - iterator(T): returns an iterator that can be used for traversing -%% the entries of tree T; see `next'. The implementation of this is -%% very efficient; traversing the whole tree using `next' is only -%% slightly slower than getting the list of all elements using -%% `to_list' and traversing that. The main advantage of the iterator +%% the entries of tree T; see `next'. Equivalent to iterator(T, ordered). +%% +%% - iterator(T, Order): returns an iterator that can be used for traversing +%% the entries of tree T in either ordered or reversed direction; see `next'. +%% The implementation of this is very efficient; traversing the whole tree +%% using `next' is only slightly slower than getting the list of all elements +%% using `to_list' and traversing that. The main advantage of the iterator %% approach is that it does not require the complete list of all %% elements to be built in memory at one time. %% %% - iterator_from(K, T): returns an iterator that can be used for %% traversing the entries of tree T with key greater than or -%% equal to K; see `next'. +%% equal to K; see `next'. Equivalent to iterator_from(K, T, ordered). %% -%% - next(S): returns {X, V, S1} where X is the smallest key referred to +%% - iterator_from(K, T, Order): returns an iterator that can be used for +%% traversing the entries of tree T in either ordered or reversed direction, +%% starting from the key equal to or closest to K; see `next'. +%% +%% - next(S): returns {X, V, S1} where X is the next key referred to %% by the iterator S, and S1 is the new iterator to be used for %% traversing the remaining entries, or the atom `none' if no entries %% remain. @@ -122,8 +135,9 @@ update/3, enter/3, delete/2, delete_any/2, balance/1, is_defined/2, keys/1, values/1, to_list/1, from_orddict/1, smallest/1, largest/1, take/2, take_any/2, - take_smallest/1, take_largest/1, - iterator/1, iterator_from/2, next/1, map/2]). + take_smallest/1, take_largest/1, smaller/2, larger/2, + iterator/1, iterator/2, iterator_from/2, iterator_from/3, + next/1, map/2]). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -164,7 +178,7 @@ | {K, V, gb_tree_node(K, V), gb_tree_node(K, V)}. -opaque tree(Key, Value) :: {non_neg_integer(), gb_tree_node(Key, Value)}. -type tree() :: tree(_, _). --opaque iter(Key, Value) :: [gb_tree_node(Key, Value)]. +-opaque iter(Key, Value) :: {ordered | reversed, [gb_tree_node(Key, Value)]}. -type iter() :: iter(_, _). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -511,6 +525,46 @@ largest_1({_Key, _Value, _Smaller, Larger}) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +-spec smaller(Key1, Tree) -> none | {Key2, Value} when + Key1 :: Key, + Key2 :: Key, + Tree :: tree(Key, Value). +smaller(Key, {_, TreeNode}) -> + smaller_1(Key, TreeNode). + +smaller_1(_Key, nil) -> + none; +smaller_1(Key, {Key1, Value, _Smaller, Larger}) when Key > Key1 -> + case smaller_1(Key, Larger) of + none -> + {Key1, Value}; + Entry -> + Entry + end; +smaller_1(Key, {_Key, _Value, Smaller, _Larger}) -> + smaller_1(Key, Smaller). + +-spec larger(Key1, Tree) -> none | {Key2, Value} when + Key1 :: Key, + Key2 :: Key, + Tree :: tree(Key, Value). +larger(Key, {_, TreeNode}) -> + larger_1(Key, TreeNode). + +larger_1(_Key, nil) -> + none; +larger_1(Key, {Key1, Value, Smaller, _Larger}) when Key < Key1 -> + case larger_1(Key, Smaller) of + none -> + {Key1, Value}; + Entry -> + Entry + end; +larger_1(Key, {_Key, _Value, _Smaller, Larger}) -> + larger_1(Key, Larger). + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + -spec to_list(Tree) -> [{Key, Value}] when Tree :: tree(Key, Value). @@ -553,20 +607,34 @@ values(nil, L) -> L. Tree :: tree(Key, Value), Iter :: iter(Key, Value). -iterator({_, T}) -> - iterator_1(T). +iterator(Tree) -> + iterator(Tree, ordered). -iterator_1(T) -> - iterator(T, []). +-spec iterator(Tree, Order) -> Iter when + Tree :: tree(Key, Value), + Iter :: iter(Key, Value), + Order :: ordered | reversed. + +iterator({_, T}, ordered) -> + {ordered, iterator_1(T, [])}; +iterator({_, T}, reversed) -> + {reversed, iterator_r(T, [])}. %% The iterator structure is really just a list corresponding to %% the call stack of an in-order traversal. This is quite fast. -iterator({_, _, nil, _} = T, As) -> +iterator_1({_, _, nil, _} = T, As) -> [T | As]; -iterator({_, _, L, _} = T, As) -> - iterator(L, [T | As]); -iterator(nil, As) -> +iterator_1({_, _, L, _} = T, As) -> + iterator_1(L, [T | As]); +iterator_1(nil, As) -> + As. + +iterator_r({_, _, _, nil} = T, As) -> + [T | As]; +iterator_r({_, _, _, R} = T, As) -> + iterator_r(R, [T | As]); +iterator_r(nil, As) -> As. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -575,19 +643,35 @@ iterator(nil, As) -> Tree :: tree(Key, Value), Iter :: iter(Key, Value). -iterator_from(S, {_, T}) -> - iterator_1_from(S, T). +iterator_from(Key, Tree) -> + iterator_from(Key, Tree, ordered). -iterator_1_from(S, T) -> - iterator_from(S, T, []). +-spec iterator_from(Key, Tree, Order) -> Iter when + Tree :: tree(Key, Value), + Iter :: iter(Key, Value), + Order :: ordered | reversed. + +iterator_from(S, {_, T}, ordered) -> + {ordered, iterator_from_1(S, T, [])}; +iterator_from(S, {_, T}, reversed) -> + {reversed, iterator_from_r(S, T, [])}. + +iterator_from_1(S, {K, _, _, T}, As) when K < S -> + iterator_from_1(S, T, As); +iterator_from_1(_, {_, _, nil, _} = T, As) -> + [T | As]; +iterator_from_1(S, {_, _, L, _} = T, As) -> + iterator_from_1(S, L, [T | As]); +iterator_from_1(_, nil, As) -> + As. -iterator_from(S, {K, _, _, T}, As) when K < S -> - iterator_from(S, T, As); -iterator_from(_, {_, _, nil, _} = T, As) -> +iterator_from_r(S, {K, _, T, _}, As) when K > S -> + iterator_from_r(S, T, As); +iterator_from_r(_, {_, _, _, nil} = T, As) -> [T | As]; -iterator_from(S, {_, _, L, _} = T, As) -> - iterator_from(S, L, [T | As]); -iterator_from(_, nil, As) -> +iterator_from_r(S, {_, _, _, R} = T, As) -> + iterator_from_r(S, R, [T | As]); +iterator_from_r(_, nil, As) -> As. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -596,9 +680,11 @@ iterator_from(_, nil, As) -> Iter1 :: iter(Key, Value), Iter2 :: iter(Key, Value). -next([{X, V, _, T} | As]) -> - {X, V, iterator(T, As)}; -next([]) -> +next({ordered, [{X, V, _, T} | As]}) -> + {X, V, {ordered, iterator_1(T, As)}}; +next({reversed, [{X, V, T, _} | As]}) -> + {X, V, {reversed, iterator_r(T, As)}}; +next({_, []}) -> none. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% diff --git a/lib/stdlib/test/gb_sets_property_test_SUITE.erl b/lib/stdlib/test/gb_sets_property_test_SUITE.erl index 4ba8809506..d8137efd5f 100644 --- a/lib/stdlib/test/gb_sets_property_test_SUITE.erl +++ b/lib/stdlib/test/gb_sets_property_test_SUITE.erl @@ -33,8 +33,10 @@ all() -> [ insert_case, is_member_case, iterator_case, iterator_from_case, + larger_case, largest_case, singleton_case, + smaller_case, smallest_case, take_largest_case, take_smallest_case @@ -76,12 +78,18 @@ iterator_case(Config) -> iterator_from_case(Config) -> do_proptest(prop_iterator_from, Config). +larger_case(Config) -> + do_proptest(prop_larger, Config). + largest_case(Config) -> do_proptest(prop_largest, Config). singleton_case(Config) -> do_proptest(prop_singleton, Config). +smaller_case(Config) -> + do_proptest(prop_smaller, Config). + smallest_case(Config) -> do_proptest(prop_smallest, Config). diff --git a/lib/stdlib/test/property_test/gb_sets_prop.erl b/lib/stdlib/test/property_test/gb_sets_prop.erl index a4097904d9..7854357367 100644 --- a/lib/stdlib/test/property_test/gb_sets_prop.erl +++ b/lib/stdlib/test/property_test/gb_sets_prop.erl @@ -59,6 +59,31 @@ prop_balance() -> gb_sets:is_equal(S, gb_sets:balance(S)) ). +%% --- ceiling/2 ------------------------------------------------------- +prop_ceiling() -> + ?FORALL( + {S, O, L}, + ?LET( + {L1, L2}, + {ct_proper_ext:safe_list(), + non_empty(ct_proper_ext:safe_list())}, + {gb_sets:from_list(L1), lists:usort(L1), L1 ++ L2} + ), + lists:all( + fun(E) -> + gb_sets:ceiling(E, S) =:= do_ceiling(E, O) + end, + L + ) + ). + +do_ceiling(_, []) -> + none; +do_ceiling(E, [X | _]) when X >= E -> + {found, X}; +do_ceiling(E, [X | R]) when X < E -> + do_ceiling(E, R). + %% --- delete/2 ------------------------------------------------------- prop_delete() -> ?FORALL( @@ -118,6 +143,31 @@ prop_difference() -> gb_sets:difference(S1, S2) =:= gb_sets:subtract(S1, S2) ). +%% --- floor/2 ------------------------------------------------------- +prop_floor() -> + ?FORALL( + {S, O, L}, + ?LET( + {L1, L2}, + {ct_proper_ext:safe_list(), + non_empty(ct_proper_ext:safe_list())}, + {gb_sets:from_list(L1), lists:reverse(lists:usort(L1)), L1 ++ L2} + ), + lists:all( + fun(E) -> + gb_sets:floor(E, S) =:= do_floor(E, O) + end, + L + ) + ). + +do_floor(_, []) -> + none; +do_floor(E, [X | _]) when X =< E -> + {found, X}; +do_floor(E, [X | R]) when X > E -> + do_floor(E, R). + %% --- from_ordset/1 -------------------------------------------------- prop_from_ordset() -> ?FORALL( @@ -182,17 +232,29 @@ prop_iterator() -> {gb_sets:from_list(L1), L1} end ), - do_iterate(gb_sets:iterator(S), L) + do_iterate(gb_sets:iterator(S), L, ordered) + ), + ?FORALL( + {S, L}, + ?LET( + L, + ct_proper_ext:safe_list(), + begin + L1 = lists:usort(L), + {gb_sets:from_list(L1), lists:reverse(L1)} + end + ), + do_iterate(gb_sets:iterator(S, reversed), L, reversed) ). -do_iterate(none, L) -> +do_iterate(none, L, _) -> L =:= []; -do_iterate(I, []) -> +do_iterate(I, [], _) -> none =:= gb_sets:next(I); -do_iterate(I0, L0) -> +do_iterate(I0, L0, Order) -> {E, I1} = gb_sets:next(I0), lists:member(E, L0) andalso - do_iterate_from(E, I1, lists:delete(E, L0)). + do_iterate_from(E, I1, lists:delete(E, L0), Order). %% --- iterator_from/2 ------------------------------------------------ %% @@ -213,18 +275,65 @@ prop_iterator_from() -> {gb_sets:from_list(L1), L2, F} end ), - do_iterate_from(From, gb_sets:iterator_from(From, S), L) + do_iterate_from(From, gb_sets:iterator_from(From, S), L, ordered) + ), + ?FORALL( + {S, L, From}, + ?LET( + {L, E}, + {ct_proper_ext:safe_list(), ct_proper_ext:safe_any()}, + begin + L1 = lists:usort(L), + L2 = lists:dropwhile(fun(X) -> X > E end, lists:reverse(L1)), + F = case L2 of + [] -> E; + _ -> oneof([E, hd(L2)]) + end, + {gb_sets:from_list(L1), L2, F} + end + ), + do_iterate_from(From, gb_sets:iterator_from(From, S, reversed), L, reversed) ). -do_iterate_from(_Min, none, L) -> +do_iterate_from(_From, none, L, _) -> L =:= []; -do_iterate_from(_Min, I, []) -> +do_iterate_from(_From, I, [], _) -> none =:= gb_sets:next(I); -do_iterate_from(Min, I0, L0) -> +do_iterate_from(From, I0, L0, ordered) -> {E, I1} = gb_sets:next(I0), lists:member(E, L0) andalso - Min =< E andalso - do_iterate_from(E, I1, lists:delete(E, L0)). + From =< E andalso + do_iterate_from(E, I1, lists:delete(E, L0), ordered); +do_iterate_from(From, I0, L0, reversed) -> + {E, I1} = gb_sets:next(I0), + lists:member(E, L0) andalso + From >= E andalso + do_iterate_from(E, I1, lists:delete(E, L0), reversed). + +%% --- larger/2 ------------------------------------------------------- +prop_larger() -> + ?FORALL( + {S, O, L}, + ?LET( + {L1, L2}, + {ct_proper_ext:safe_list(), + non_empty(ct_proper_ext:safe_list())}, + {gb_sets:from_list(L1), lists:usort(L1), L1 ++ L2} + ), + lists:all( + fun(E) -> + gb_sets:larger(E, S) =:= do_larger(E, O) + end, + L + ) + ). + +do_larger(_, []) -> + none; +do_larger(E, [X | _]) when X > E -> + {found, X}; +do_larger(E, [X | R]) when X =< E -> + do_larger(E, R). %% --- largest/1 ------------------------------------------------------ prop_largest() -> @@ -249,6 +358,31 @@ prop_singleton() -> [E] =:= gb_sets:to_list(gb_sets:singleton(E)) ). +%% --- smaller/2 ------------------------------------------------------- +prop_smaller() -> + ?FORALL( + {S, O, L}, + ?LET( + {L1, L2}, + {ct_proper_ext:safe_list(), + non_empty(ct_proper_ext:safe_list())}, + {gb_sets:from_list(L1), lists:reverse(lists:usort(L1)), L1 ++ L2} + ), + lists:all( + fun(E) -> + gb_sets:smaller(E, S) =:= do_smaller(E, O) + end, + L + ) + ). + +do_smaller(_, []) -> + none; +do_smaller(E, [X | _]) when X < E -> + {found, X}; +do_smaller(E, [X | R]) when X >= E -> + do_smaller(E, R). + %% --- smallest/1 ----------------------------------------------------- prop_smallest() -> ?FORALL( -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor