File 1461-Polish-documentation-for-the-sets-modules.patch of Package erlang
From 06425ab743443ccad392d2272a389289163cd36b Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 18 Feb 2025 11:43:59 +0100
Subject: [PATCH] Polish documentation for the sets modules
Ensure that the first sentence describing each function makes sense
by itself when shown in the Summary part of the documentation.
Add examples for all functions.
While at it, also remove comments for documented functions, and
remove out-commented code, and do some other minor clean ups.
---
lib/stdlib/src/gb_sets.erl | 729 ++++++++++++++++++++++++---------
lib/stdlib/src/ordsets.erl | 381 +++++++++++++----
lib/stdlib/src/sets.erl | 480 +++++++++++++++++-----
lib/stdlib/test/sets_SUITE.erl | 13 +-
4 files changed, 1225 insertions(+), 378 deletions(-)
diff --git a/lib/stdlib/src/gb_sets.erl b/lib/stdlib/src/gb_sets.erl
index a66c56cfcf..e64da908d2 100644
--- a/lib/stdlib/src/gb_sets.erl
+++ b/lib/stdlib/src/gb_sets.erl
@@ -20,147 +20,6 @@
%% ordered lists, for larger sets, but depends on the application. See
%% notes below for details.
%% ---------------------------------------------------------------------
-%% Notes:
-%%
-%% The complexity on set operations is bounded by either O(|S|) or O(|T|
-%% * log(|S|)), where S is the largest given set, depending on which is
-%% fastest for any particular function call. For operating on sets of
-%% almost equal size, this implementation is about 3 times slower than
-%% using ordered-list sets directly. For sets of very different sizes,
-%% however, this solution can be arbitrarily much faster; in practical
-%% cases, often between 10 and 100 times. This implementation is
-%% particularly suited for ackumulating elements a few at a time,
-%% building up a large set (more than 100-200 elements), and repeatedly
-%% testing for membership in the current set.
-%%
-%% As with normal tree structures, lookup (membership testing),
-%% insertion and deletion have logarithmic complexity.
-%%
-%% Operations:
-%%
-%% - empty(): returns empty set.
-%%
-%% Alias: new(), for compatibility with `sets'.
-%%
-%% - is_empty(S): returns 'true' if S is an empty set, and 'false'
-%% otherwise.
-%%
-%% - size(S): returns the number of nodes in the set as an integer.
-%% Returns 0 (zero) if the set is empty.
-%%
-%% - singleton(X): returns a set containing only the element X.
-%%
-%% - is_member(X, S): returns `true' if element X is a member of set S,
-%% and `false' otherwise.
-%%
-%% Alias: is_element(), for compatibility with `sets'.
-%%
-%% - insert(X, S): inserts element X into set S; returns the new set.
-%% *Assumes that the element is not present in S.*
-%%
-%% - add(X, S): adds element X to set S; returns the new set. If X is
-%% already an element in S, nothing is changed.
-%%
-%% Alias: add_element(), for compatibility with `sets'.
-%%
-%% - delete(X, S): removes element X from set S; returns new set.
-%% Assumes that the element exists in the set.
-%%
-%% - delete_any(X, S): removes key X from set S if the key is present
-%% in the set, otherwise does nothing; returns new set.
-%%
-%% Alias: del_element(), for compatibility with `sets'.
-%%
-%% - balance(S): rebalances the tree representation of S. Note that this
-%% is rarely necessary, but may be motivated when a large number of
-%% elements have been deleted from the tree without further
-%% insertions. Rebalancing could then be forced in order to minimise
-%% lookup times, since deletion only does not rebalance the tree.
-%%
-%% - union(S1, S2): returns a new set that contains each element that is
-%% in either S1 or S2 or both, and no other elements.
-%%
-%% - union(Ss): returns a new set that contains each element that is in
-%% at least one of the sets in the list Ss, and no other elements.
-%%
-%% - intersection(S1, S2): returns a new set that contains each element
-%% that is in both S1 and S2, and no other elements.
-%%
-%% - intersection(Ss): returns a new set that contains each element that
-%% is in all of the sets in the list Ss, and no other elements.
-%%
-%% - is_disjoint(S1, S2): returns `true' if none of the elements in S1
-%% occurs in S2.
-%%
-%% - difference(S1, S2): returns a new set that contains each element in
-%% S1 that is not also in S2, and no other elements.
-%%
-%% Alias: subtract(), for compatibility with `sets'.
-%%
-%% - is_subset(S1, S2): returns `true' if each element in S1 is also a
-%% member of S2, and `false' otherwise.
-%%
-%% - to_list(S): returns an ordered list of all elements in set S. The
-%% list never contains duplicates.
-%%
-%% - from_list(List): creates a set containing all elements in List,
-%% where List may be unordered and contain duplicates.
-%%
-%% - from_ordset(L): turns an ordered-set list L into a set. The list
-%% must not contain duplicates.
-%%
-%% - smallest(S): returns the smallest element in set S. Assumes that
-%% the set S is nonempty.
-%%
-%% - largest(S): returns the largest element in set S. Assumes that the
-%% set S is nonempty.
-%%
-%% - take_smallest(S): returns {X, S1}, where X is the smallest element
-%% in set S, and S1 is the set S with element X deleted. Assumes that
-%% the set S is nonempty.
-%%
-%% - take_largest(S): returns {X, S1}, where X is the largest element in
-%% 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'. 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'. 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
-%% traversing the remaining elements, or the atom `none' if no
-%% elements remain.
-%%
-%% - filter(P, S): Filters set S using predicate function P. Included
-%% for compatibility with `sets'.
-%%
-%% - fold(F, A, S): Folds function F over set S with A as the initial
-%% ackumulator. Included for compatibility with `sets'.
-%%
-%% - is_set(S): returns 'true' if S appears to be a set, and 'false'
-%% otherwise. Not recommended; included for compatibility with `sets'.
-module(gb_sets).
-moduledoc """
@@ -237,13 +96,13 @@ in the Standard Library.
%% Behaviour is logarithmic (as it should be).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% Some macros.
+%% Some macros.
-define(p, 2). % It seems that p = 2 is optimal for sorted keys
-define(pow(A, _), A * A). % correct with exponent as defined above.
--define(div2(X), X bsr 1).
+-define(div2(X), X bsr 1).
-define(mul2(X), X bsl 1).
@@ -262,20 +121,49 @@ in the Standard Library.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
--doc "Returns a new empty set.".
+-doc """
+Returns a new empty set.
+
+## Examples
+
+```erlang
+1> gb_sets:to_list(gb_sets:empty()).
+[]
+```
+""".
-spec empty() -> Set when
Set :: set(none()).
empty() ->
{0, nil}.
--doc "Returns a new empty set.".
+-doc """
+Returns a new empty set.
+
+## Examples
+
+```erlang
+1> gb_sets:to_list(gb_sets:new()).
+[]
+```
+""".
-spec new() -> Set when
Set :: set(none()).
new() -> empty().
--doc "Returns `true` if `Set` is an empty set, otherwise `false`.".
+-doc """
+Returns `true` if `Set` is an empty set; otherwise, returns `false`.
+
+## Examples
+
+```erlang
+1> gb_sets:is_empty(gb_sets:new()).
+true
+2> gb_sets:is_empty(gb_sets:singleton(1)).
+false
+```
+""".
-spec is_empty(Set) -> boolean() when
Set :: set().
@@ -284,7 +172,18 @@ is_empty({0, nil}) ->
is_empty(_) ->
false.
--doc "Returns the number of elements in `Set`.".
+-doc """
+Returns the number of elements in `Set`.
+
+## Examples
+
+```erlang
+1> gb_sets:size(gb_sets:new()).
+0
+2> gb_sets:size(gb_sets:from_list([4,5,6])).
+3
+```
+""".
-spec size(Set) -> non_neg_integer() when
Set :: set().
@@ -292,8 +191,19 @@ size({Size, _}) ->
Size.
-doc """
-Returns `true` if `Set1` and `Set2` are equal, that is when every element of one
-set is also a member of the respective other set, otherwise `false`.
+Returns `true` if `Set1` and `Set2` are equal, that is, if every element
+of one set is also a member of the other set; otherwise, returns `false`.
+
+## Examples
+
+```erlang
+1> Empty = gb_sets:new().
+2> S = gb_sets:from_list([a,b]).
+3> gb_sets:is_equal(S, S)
+true
+4> gb_sets:is_equal(S, Empty)
+false
+```
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec is_equal(Set1, Set2) -> boolean() when
@@ -322,7 +232,17 @@ is_equal_1({Key1, Smaller, Bigger}, Keys0) ->
throw(not_equal)
end.
--doc "Returns a set containing only element `Element`.".
+-doc """
+Returns a set containing only element `Element`.
+
+## Examples
+
+```erlang
+1> S = gb_sets:singleton(42).
+2> gb_sets:to_list(S).
+[42]
+```
+""".
-spec singleton(Element) -> set(Element).
singleton(Key) ->
@@ -335,7 +255,20 @@ singleton(Key) ->
is_element(Key, S) ->
is_member(Key, S).
--doc "Returns `true` if `Element` is an member of `Set`, otherwise `false`.".
+-doc """
+Returns `true` if `Element` is an element of `Set`; otherwise, returns
+`false`.
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_list([a,b,c]).
+2> gb_sets:is_member(42, S).
+false
+3> gb_sets:is_member(b, S).
+true
+```
+""".
-spec is_member(Element, Set) -> boolean() when
Set :: set(Element).
@@ -352,8 +285,23 @@ is_member_1(_, nil) ->
false.
-doc """
-Returns a new set formed from `Set1` with `Element` inserted. Assumes that
-`Element` is not present in `Set1`.
+Returns a new set formed from `Set1` with `Element` inserted,
+assuming `Element` is not already present.
+
+Use `add/2` for inserting into a set where `Element` is potentially
+already present.
+
+## Examples
+
+```erlang
+1> S0 = gb_sets:new().
+2> S1 = gb_sets:insert(7, S0).
+3> gb_sets:to_list(S1).
+[7]
+4> S2 = gb_sets:insert(42, S1).
+5> gb_sets:to_list(S2).
+[7,42]
+```
""".
-spec insert(Element, Set1) -> Set2 when
Set1 :: set(Element),
@@ -363,7 +311,7 @@ insert(Key, {S, T}) when is_integer(S), S >= 0 ->
S1 = S + 1,
{S1, insert_1(Key, T, ?pow(S1, ?p))}.
-insert_1(Key, {Key1, Smaller, Bigger}, S) when Key < Key1 ->
+insert_1(Key, {Key1, Smaller, Bigger}, S) when Key < Key1 ->
case insert_1(Key, Smaller, ?div2(S)) of
{T1, H1, S1} when is_integer(H1), is_integer(S1) ->
T = {Key1, T1, Bigger},
@@ -380,7 +328,7 @@ insert_1(Key, {Key1, Smaller, Bigger}, S) when Key < Key1 ->
T1 ->
{Key1, T1, Bigger}
end;
-insert_1(Key, {Key1, Smaller, Bigger}, S) when Key > Key1 ->
+insert_1(Key, {Key1, Smaller, Bigger}, S) when Key > Key1 ->
case insert_1(Key, Bigger, ?div2(S)) of
{T1, H1, S1} when is_integer(H1), is_integer(S1) ->
T = {Key1, Smaller, T1},
@@ -416,10 +364,21 @@ count(nil) ->
-doc """
Rebalances the tree representation of `Set1`.
-Notice that this is rarely necessary, but can be motivated when a large number of
-elements have been deleted from the tree without further insertions. Rebalancing
- can then be forced to minimise lookup times, as deletion does not rebalance the
-tree.
+This is rarely necessary, but can be motivated when a large number of
+elements have been deleted from the tree without further
+insertions. Forcing rebalancing can minimize lookup times, as deletion
+does not rebalance the tree.
+
+## Examples
+
+```erlang
+1> S0 = gb_sets:from_ordset(lists:seq(1, 100)).
+2> Delete = fun(E, Set) -> gb_sets:delete(E, Set) end.
+3> S1 = lists:foldl(Delete, S0, lists:seq(1, 50)).
+4> gb_sets:size(S1).
+50
+5> S2 = gb_sets:balance(S1).
+```
""".
-spec balance(Set1) -> Set2 when
Set1 :: set(Element),
@@ -449,8 +408,22 @@ balance_list_1(L, 0) ->
{nil, L}.
-doc """
-Returns a new set formed from `Set1` with `Element` inserted. If `Element` is
-already an element in `Set1`, nothing is changed.
+Returns a new set formed from `Set1` with `Element` inserted.
+
+If `Element` is already an element in `Set1`, nothing is changed.
+
+## Examples
+
+```erlang
+1> S0 = gb_sets:new().
+2> S1 = gb_sets:add_element(7, S0).
+3> gb_sets:to_list(S1).
+[7]
+4> S2 = gb_sets:add_element(42, S1).
+5> S2 = gb_sets:add_element(42, S1).
+6> gb_sets:to_list(S2).
+[7,42]
+```
""".
-spec add_element(Element, Set1) -> Set2 when
Set1 :: set(Element),
@@ -475,6 +448,14 @@ add(X, S) ->
-doc """
Returns a set of the elements in `List`, where `List` can be unordered and
contain duplicates.
+
+## Examples
+
+```erlang
+1> Unordered = [x,y,a,x,y,b,b,z]
+2> gb_sets:to_list(gb_sets:from_list(Unordered)).
+[a,b,x,y,z]
+```
""".
-spec from_list(List) -> Set when
List :: [Element],
@@ -484,8 +465,18 @@ from_list(L) ->
from_ordset(ordsets:from_list(L)).
-doc """
-Turns an ordered-set list `List` into a set. The list must not contain
+Turns an ordered list without duplicates `List` into a set.
+
+See `from_list/1` for a function that accepts unordered lists with
duplicates.
+
+## Examples
+
+```erlang
+1> Ordset = [1,2,3].
+2> gb_sets:to_list(gb_sets:from_ordset(Ordset)).
+[1,2,3]
+```
""".
-spec from_ordset(List) -> Set when
List :: [Element],
@@ -504,8 +495,18 @@ del_element(Key, S) ->
delete_any(Key, S).
-doc """
-Returns a new set formed from `Set1` with `Element` removed. If `Element` is not
-an element in `Set1`, nothing is changed.
+Returns a new set formed from `Set1` with `Element` removed.
+
+If `Element` is not an element in `Set1`, nothing is changed.
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_list([a,b]).
+2> gb_sets:to_list(gb_sets:delete_any(b, S)).
+[a]
+3> S = gb_sets:delete_any(x, S).
+```
""".
-spec delete_any(Element, Set1) -> Set2 when
Set1 :: set(Element),
@@ -520,8 +521,19 @@ delete_any(Key, S) ->
end.
-doc """
-Returns a new set formed from `Set1` with `Element` removed. Assumes that
+Returns a new set formed from `Set1` with `Element` removed, assuming
`Element` is present in `Set1`.
+
+Use `delete_any/2` when deleting from a set where `Element` is potentially
+missing.
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_list([a,b]).
+2> gb_sets:to_list(gb_sets:delete(b, S)).
+[a]
+```
""".
-spec delete(Element, Set1) -> Set2 when
Set1 :: set(Element),
@@ -548,8 +560,21 @@ merge(Smaller, Larger) ->
{Key, Smaller, Larger1}.
-doc """
-Returns `{Element, Set2}`, where `Element` is the smallest element in `Set1`,
-and `Set2` is this set with `Element` deleted. Assumes that `Set1` is not empty.
+Returns `{Element, Set2}`, where `Element` is the smallest element in
+`Set1`, and `Set2` is this set with `Element` deleted.
+
+Assumes that `Set1` is not empty.
+
+## Examples
+
+```erlang
+1> S0 = gb_sets:from_list([a,b,c]).
+2> {Smallest,S1} = gb_sets:take_smallest(S0).
+3> Smallest.
+a
+4> gb_sets:to_list(S1).
+[b,c]
+```
""".
-spec take_smallest(Set1) -> {Element, Set2} when
Set1 :: set(Element),
@@ -565,7 +590,19 @@ take_smallest1({Key, Smaller, Larger}) ->
{Key1, Smaller1} = take_smallest1(Smaller),
{Key1, {Key, Smaller1, Larger}}.
--doc "Returns the smallest element in `Set`. Assumes that `Set` is not empty.".
+-doc """
+Returns the smallest element in `Set`.
+
+Assumes that `Set` is not empty.
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_list([a,b,c]).
+2> gb_sets:smallest(S).
+a
+```
+""".
-spec smallest(Set) -> Element when
Set :: set(Element).
@@ -578,8 +615,21 @@ smallest_1({_Key, Smaller, _Larger}) ->
smallest_1(Smaller).
-doc """
-Returns `{Element, Set2}`, where `Element` is the largest element in `Set1`, and
-`Set2` is this set with `Element` deleted. Assumes that `Set1` is not empty.
+Returns `{Element, Set2}`, where `Element` is the largest element in
+`Set1`, and `Set2` is this set with `Element` deleted.
+
+Assumes that `Set1` is not empty.
+
+## Examples
+
+```erlang
+1> S0 = gb_sets:from_list([a,b,c]).
+2> {Largest,S1} = gb_sets:take_largest(S0).
+3> Largest.
+c
+4> gb_sets:to_list(S1).
+[a,b]
+```
""".
-spec take_largest(Set1) -> {Element, Set2} when
Set1 :: set(Element),
@@ -595,7 +645,19 @@ take_largest1({Key, Smaller, Larger}) ->
{Key1, Larger1} = take_largest1(Larger),
{Key1, {Key, Smaller, Larger1}}.
--doc "Returns the largest element in `Set`. Assumes that `Set` is not empty.".
+-doc """
+Returns the largest element in `Set`.
+
+Assumes that `Set` is not empty.
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_list([a,b,c]).
+2> gb_sets:largest(S).
+c
+```
+""".
-spec largest(Set) -> Element when
Set :: set(Element).
@@ -612,6 +674,18 @@ Returns `{found, Element2}`, where `Element2` is the greatest element strictly
less than `Element1`.
Returns `none` if no such element exists.
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_list([a,b,c]).
+2> gb_sets:smaller(b, S).
+{found,a}
+3> gb_sets:smaller(z, S).
+{found,c}
+4> gb_sets:smaller(a, S).
+none
+```
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec smaller(Element1, Set) -> none | {found, Element2} when
@@ -638,6 +712,20 @@ Returns `{found, Element2}`, where `Element2` is the least element strictly
greater than `Element1`.
Returns `none` if no such element exists.
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_list([10,20,30]).
+2> gb_sets:larger(1, S).
+{found,10}
+3> gb_sets:larger(10, S).
+{found,20}
+4> gb_sets:larger(19, S).
+{found,20}
+5> gb_sets:larger(30, S).
+none
+```
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec larger(Element1, Set) -> none | {found, Element2} when
@@ -659,7 +747,14 @@ larger_1(Key, {Key1, Smaller, _Larger}) when Key < Key1 ->
larger_1(Key, {_Key, _Smaller, Larger}) ->
larger_1(Key, Larger).
--doc "Returns the elements of `Set` as a list.".
+-doc """
+Returns the elements of `Set` as an ordered list.
+
+```erlang
+1> gb_sets:to_list(gb_sets:from_list([4,3,5,1,2])).
+[1,2,3,4,5]
+```
+""".
-spec to_list(Set) -> List when
Set :: set(Element),
List :: [Element].
@@ -690,11 +785,21 @@ iterator(Set) ->
Returns an iterator that can be used for traversing the entries of `Set` in
either `ordered` or `reversed` direction; see `next/1`.
-The implementation of this is very efficient; traversing the whole set using
-[`next/1`](`next/1`) is only slightly slower than getting the list of all
- elements using `to_list/1` 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.
+The implementation is very efficient; traversing the whole set using
+[`next/1`](`next/1`) is only slightly slower than getting the list of
+all elements using `to_list/1` and traversing that. The main advantage
+of the iterator approach is that it avoids building the complete list
+of all elements to be built in memory at once.
+
+```erlang
+1> S = gb_sets:from_ordset([1,2,3,4,5]).
+2> Iter0 = gb_sets:iterator(S, ordered).
+3> element(1, gb_sets:next(Iter0)).
+1
+4> Iter1 = gb_sets:iterator(S, reversed).
+5> element(1, gb_sets:next(Iter1)).
+5
+```
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec iterator(Set, Order) -> Iter when
@@ -726,11 +831,22 @@ iterator_r(nil, As) ->
-doc """
Returns an iterator that can be used for traversing the entries of `Set`; see
-`next/1`. The difference as compared to the iterator returned by `iterator/1` is
-that the iterator starts with the first element greater than or equal to
+`next/1`.
+
+Unlike the iterator returned by `iterator/1` or `iterator/2`, this
+iterator starts with the first element greater than or equal to
`Element`.
Equivalent to [`iterator_from(Element, Set, ordered)`](`iterator_from/3`).
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_ordset([10,20,30,40,50]).
+2> Iter = gb_sets:iterator_from(17, S).
+3> element(1, gb_sets:next(Iter)).
+20
+```
""".
-doc(#{since => <<"OTP 18.0">>}).
-spec iterator_from(Element, Set) -> Iter when
@@ -742,8 +858,20 @@ iterator_from(Element, Set) ->
-doc """
Returns an iterator that can be used for traversing the entries of `Set`; see
-`next/1`. The difference as compared to the iterator returned by `iterator/2` is
-that the iterator starts with the first element next to or equal to `Element`.
+`next/1`.
+
+Unlike the iterator returned by `iterator/1` or `iterator/2`, this
+iterator starts with the first element greater than or equal to
+`Element`.
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_ordset([10,20,30,40,50]).
+2> Iter = gb_sets:iterator_from(17, S, reversed).
+3> element(1, gb_sets:next(Iter)).
+10
+```
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec iterator_from(Element, Set, Order) -> Iter when
@@ -775,9 +903,20 @@ iterator_from_r(_, nil, As) ->
As.
-doc """
-Returns `{Element, Iter2}`, where `Element` is the smallest element referred to
+Returns `{Element, Iter2}`, where `Element` is the first element referred to
by iterator `Iter1`, and `Iter2` is the new iterator to be used for traversing
the remaining elements, or the atom `none` if no elements remain.
+
+```erlang
+1> S = gb_sets:from_ordset([1,2,3,4,5]).
+2> Iter0 = gb_sets:iterator(S).
+3> {Element0, Iter1} = gb_sets:next(Iter0).
+4> Element0.
+1
+5> {Element1, Iter2} = gb_sets:next(Iter1).
+6> Element1.
+2
+```
""".
-spec next(Iter1) -> {Element, Iter2} | 'none' when
Iter1 :: iter(Element),
@@ -813,7 +952,22 @@ next({_, []}) ->
%% traversing the elements can be devised, but they all have higher
%% overhead.
--doc "Returns the merged (union) set of `Set1` and `Set2`.".
+-doc """
+Returns the union of `Set1` and `Set2`.
+
+The union of two sets is a new set that contains all the elements from
+both sets, without duplicates.
+
+## Examples
+
+```erlang
+1> S0 = gb_sets:from_list([a,b,c,d]).
+2> S1 = gb_sets:from_list([c,d,e,f]).
+3> Union = gb_sets:union(S0, S1).
+4> gb_sets:to_list(Union).
+[a,b,c,d,e,f]
+```
+""".
-spec union(Set1, Set2) -> Set3 when
Set1 :: set(Element),
Set2 :: set(Element),
@@ -919,7 +1073,24 @@ balance_revlist_1([Key | L], 1) ->
balance_revlist_1(L, 0) ->
{nil, L}.
--doc "Returns the merged (union) set of the list of sets.".
+-doc """
+Returns the union of a list of sets.
+
+The union of multiple sets is a new set that contains all the elements from
+all sets, without duplicates.
+
+## Examples
+
+```erlang
+1> S0 = gb_sets:from_list([a,b,c,d]).
+2> S1 = gb_sets:from_list([d,e,f]).
+3> S2 = gb_sets:from_list([q,r])
+4> Sets = [S0, S1, S2].
+5> Union = gb_sets:union(Sets).
+6> gb_sets:to_list(Union).
+[a,b,c,d,e,f,q,r]
+```
+""".
-spec union(SetList) -> Set when
SetList :: [set(Element),...],
Set :: set(Element).
@@ -935,7 +1106,24 @@ union_list(S, []) -> S.
%% The rest is modelled on the above.
--doc "Returns the intersection of `Set1` and `Set2`.".
+-doc """
+Returns the intersection of `Set1` and `Set2`.
+
+The intersection of two sets is a new set that contains only the
+elements that are present in both sets.
+
+## Examples
+
+```erlang
+1> S0 = gb_sets:from_list([a,b,c,d]).
+2> S1 = gb_sets:from_list([c,d,e,f]).
+3> S2 = gb_sets:from_list([q,r]).
+4> gb_sets:to_list(gb_sets:intersection(S0, S1)).
+[c,d]
+5> gb_sets:to_list(gb_sets:intersection(S1, S2)).
+[]
+```
+""".
-spec intersection(Set1, Set2) -> Set3 when
Set1 :: set(Element),
Set2 :: set(Element),
@@ -987,7 +1175,25 @@ intersection_2([], _, As, S) ->
intersection_2(_, [], As, S) ->
{S, balance_revlist(As, S)}.
--doc "Returns the intersection of the non-empty list of sets.".
+-doc """
+Returns the intersection of the non-empty list of sets.
+
+The intersection of multiple sets is a new set that contains only the
+elements that are present in all sets.
+
+## Examples
+
+```erlang
+1> S0 = gb_sets:from_list([a,b,c,d]).
+2> S1 = gb_sets:from_list([d,e,f]).
+3> S2 = gb_sets:from_list([q,r])
+4> Sets = [S0, S1, S2].
+5> gb_sets:to_list(gb_sets:intersection([S0, S1, S2])).
+[]
+6> gb_sets:to_list(gb_sets:intersection([S0, S1])).
+[d]
+```
+""".
-spec intersection(SetList) -> Set when
SetList :: [set(Element),...],
Set :: set(Element).
@@ -1000,8 +1206,25 @@ intersection_list(S, [S1 | Ss]) ->
intersection_list(S, []) -> S.
-doc """
-Returns `true` if `Set1` and `Set2` are disjoint (have no elements in common),
-otherwise `false`.
+Returns `true` if `Set1` and `Set2` are disjoint; otherwise, returns
+`false`.
+
+Two sets are disjoint if they have no elements in common.
+
+This function is equivalent to `gb_sets:intersection(Set1, Set2) =:= []`,
+but faster.
+
+## Examples
+
+```erlang
+1> S0 = gb_sets:from_list([a,b,c,d]).
+2> S1 = gb_sets:from_list([d,e,f]).
+3> S2 = gb_sets:from_list([q,r])
+4> gb_sets:is_disjoint(S0, S1).
+false
+5> gb_sets:is_disjoint(S1, S2).
+true
+```
""".
-spec is_disjoint(Set1, Set2) -> boolean() when
Set1 :: set(Element),
@@ -1033,7 +1256,20 @@ is_disjoint_1(_, nil) ->
%% the sets. Therefore, we always build a new tree, and thus we need to
%% traverse the whole element list of the left operand.
--doc "Returns only the elements of `Set1` that are not also elements of `Set2`.".
+-doc """
+Returns the elements of `Set1` that are not elements in `Set2`.
+
+## Examples
+
+```erlang
+1> S0 = gb_sets:from_list([a,b,c,d]).
+2> S1 = gb_sets:from_list([c,d,e,f]).
+3> gb_sets:to_list(gb_sets:subtract(S0, S1)).
+[a,b]
+4> gb_sets:to_list(gb_sets:subtract(S1, S0)).
+[e,f]
+```
+""".
-spec subtract(Set1, Set2) -> Set3 when
Set1 :: set(Element),
Set2 :: set(Element),
@@ -1096,8 +1332,21 @@ difference_2(Xs, [], As, S) ->
%% without the construction of a new set.
-doc """
-Returns `true` when every element of `Set1` is also a member of `Set2`,
-otherwise `false`.
+Returns `true` when every element of `Set1` is also a member of `Set2`;
+otherwise, returns `false`.
+
+## Examples
+
+```erlang
+1> S0 = gb_sets:from_list([a,b,c,d]).
+2> S1 = gb_sets:from_list([c,d]).
+3> gb_sets:is_subset(S1, S0).
+true
+4> gb_sets:is_subset(S0, S1).
+false
+5> gb_sets:is_subset(S0, S0).
+true
+```
""".
-spec is_subset(Set1, Set2) -> boolean() when
Set1 :: set(Element),
@@ -1144,10 +1393,28 @@ is_subset_2(_, []) ->
%% For compatibility with `sets':
-doc """
-Returns `true` if `Term` appears to be a set, otherwise `false`. This function
-will return `true` for any term that coincides with the representation of a
-`gb_set`, while not really being a `gb_set`, thus it might return false positive
-results. See also note on [data types](`e:system:data_types.md#no_user_types`).
+Returns `true` if `Term` appears to be a set; otherwise, returns `false`.
+
+> #### Note {: .info }
+>
+> This function will return `true` for any term that coincides with the
+> representation of a `gb_set`, while not really being a `gb_set`, thus
+> it might return false positive results. See also note on [data
+> types](`e:system:data_types.md#no_user_types`).
+>
+> Furthermore, since gb_sets are opaque, calling this function on terms
+> that are not gb_sets could result in `m:dialyzer` warnings.
+
+## Examples
+
+```erlang
+1> gb_sets:is_set(gb_sets:new()).
+true
+2> gb_sets:is_set(gb_sets:singleton(42)).
+true
+3> gb_sets:is_set(0).
+false
+```
""".
-spec is_set(Term) -> boolean() when
Term :: term().
@@ -1156,7 +1423,19 @@ is_set({0, nil}) -> true;
is_set({N, {_, _, _}}) when is_integer(N), N >= 0 -> true;
is_set(_) -> false.
--doc "Filters elements in `Set1` using predicate function `Pred`.".
+-doc """
+Filters elements in `Set1` using predicate function `Pred`.
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_list([1,2,3,4,5,6,7]).
+2> IsEven = fun(N) -> N rem 2 =:= 0 end.
+3> Filtered = gb_sets:filter(IsEven, S).
+4> gb_sets:to_list(Filtered).
+[2,4,6]
+```
+""".
-spec filter(Pred, Set1) -> Set2 when
Pred :: fun((Element) -> boolean()),
Set1 :: set(Element),
@@ -1165,7 +1444,19 @@ is_set(_) -> false.
filter(F, S) when is_function(F, 1) ->
from_ordset([X || X <- to_list(S), F(X)]).
--doc "Maps elements in `Set1` using mapping function `Fun`.".
+-doc """
+Maps elements in `Set1` with mapping function `Fun`.
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_list([1,2,3,4,5,6,7]).
+2> F = fun(N) -> N div 2 end.
+3> Mapped = gb_sets:map(F, S).
+4> gb_sets:to_list(Mapped).
+[0,1,2,3]
+```
+""".
-doc(#{since => <<"OTP 27.0">>}).
-spec map(Fun, Set1) -> Set2 when
Fun :: fun((Element1) -> Element2),
@@ -1179,7 +1470,36 @@ map_1({Key, Small, Big}, F, L) ->
map_1(Small, F, [F(Key) | map_1(Big, F, L)]);
map_1(nil, _F, L) -> L.
--doc "Filters and maps elements in `Set1` using function `Fun`.".
+-doc """
+Calls `Fun(Elem)` for each `Elem` of `Set1` to update or remove
+elements from `Set1`.
+
+`Fun/1` must return either a Boolean or a tuple `{true, Value}`. The
+function returns the set of elements for which `Fun` returns a new
+value, with `true` being equivalent to `{true, Elem}`.
+
+`gb_sets:filtermap/2` behaves as if it were defined as follows:
+
+```erlang
+filtermap(Fun, Set1) ->
+ gb_sets:from_list(lists:filtermap(Fun, Set1)).
+```
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_list([2,4,5,6,8,9])
+2> F = fun(X) ->
+ case X rem 2 of
+ 0 -> {true, X div 2};
+ 1 -> false
+ end
+ end.
+3> Set = gb_sets:filtermap(F, S).
+4> gb_sets:to_list(Set).
+[1,2,3,4]
+```
+""".
-doc(#{since => <<"OTP 27.0">>}).
-spec filtermap(Fun, Set1) -> Set2 when
Fun :: fun((Element1) -> boolean() | {true, Element2}),
@@ -1201,8 +1521,17 @@ filtermap_1({Key, Small, Big}, F, L) ->
filtermap_1(nil, _F, L) -> L.
-doc """
-Folds `Function` over every element in `Set` returning the final value of the
-accumulator.
+Folds `Function` over every element in `Set` and returns the final value of
+the accumulator.
+
+## Examples
+
+```erlang
+1> S = gb_sets:from_list([1,2,3,4]).
+2> Plus = fun erlang:'+'/2.
+3> gb_sets:fold(Plus, 0, S).
+10
+```
""".
-spec fold(Function, Acc0, Set) -> Acc1 when
Function :: fun((Element, AccIn) -> AccOut),
diff --git a/lib/stdlib/src/ordsets.erl b/lib/stdlib/src/ordsets.erl
index 6ec419cf7c..bc2256ea16 100644
--- a/lib/stdlib/src/ordsets.erl
+++ b/lib/stdlib/src/ordsets.erl
@@ -52,21 +52,41 @@ sets in the Standard Library.
-doc "As returned by `new/0`.".
-type ordset(T) :: [T].
-%% new() -> Set.
-%% Return a new empty ordered set.
+-doc """
+Returns a new empty ordered set.
+
+## Examples
--doc "Returns a new empty ordered set.".
+```erlang
+1> ordsets:new()
+[]
+```
+""".
-spec new() -> [].
new() -> [].
-%% is_set(Term) -> boolean().
-%% Return 'true' if Set is an ordered set of elements, else 'false'.
-
-doc """
-Returns `true` if `Ordset` is an ordered set of elements, otherwise `false`.
-This function will return `true` for any ordered list, even when not constructed
-by the functions in this module.
+Returns `true` if `Ordset` is an ordered set of elements; otherwise,
+returns `false`.
+
+> #### Note {: .info }
+>
+> This function returns true for any ordered list, even if it was not
+> constructed using the functions in this module.
+
+## Examples
+
+```erlang
+1> ordsets:is_set(ordsets:from_list([a,x,13,{p,q}])).
+true
+2> ordsets:is_set([a,b,c]).
+true
+3> ordsets:is_set([z,a]).
+false
+4> ordsets:is_set({a,b}).
+false
+```
""".
-spec is_set(Ordset) -> boolean() when
Ordset :: term().
@@ -80,30 +100,55 @@ is_set([E2|Es], E1) when E1 < E2 ->
is_set([_|_], _) -> false;
is_set([], _) -> true.
-%% size(OrdSet) -> int().
-%% Return the number of elements in OrdSet.
+-doc """
+Returns the number of elements in `Ordset`.
+
+## Examples
--doc "Returns the number of elements in `Ordset`.".
+```erlang
+1> ordsets:size(ordsets:new()).
+0
+2> ordsets:size(ordsets:from_list([4,5,6])).
+3
+```
+""".
-spec size(Ordset) -> non_neg_integer() when
Ordset :: ordset(_).
size(S) -> length(S).
-%% is_empty(OrdSet) -> boolean().
-%% Return 'true' if OrdSet is an empty set, otherwise 'false'.
--doc "Returns `true` if `Ordset` is an empty set, otherwise `false`.".
+-doc """
+Returns `true` if `Ordset` is an empty set; otherwise, returns `false`.
+
+## Examples
+
+```erlang
+1> ordsets:is_empty(ordsets:new()).
+true
+2> ordsets:is_empty(ordsets:from_list([1])).
+false
+```
+""".
-doc(#{since => <<"OTP 21.0">>}).
-spec is_empty(Ordset) -> boolean() when
Ordset :: ordset(_).
-is_empty(S) -> S=:=[].
+is_empty(S) -> S =:= [].
-%% is_equal(OrdSet1, OrdSet2) -> boolean().
-%% Return 'true' if OrdSet1 and OrdSet2 contain the same elements,
-%% otherwise 'false'.
-doc """
-Returns `true` if `Ordset1` and `Ordset2` are equal, that is when every element
-of one set is also a member of the respective other set, otherwise `false`.
+Returns `true` if `Ordset1` and `Ordset2` are equal, that is, if every element
+of one set is also a member of the other set; otherwise, returns `false`.
+
+## Examples
+
+```erlang
+1> Empty = ordsets:new().
+2> S = ordsets:from_list([a,b]).
+3> ordsets:is_equal(S, S)
+true
+4> ordsets:is_equal(S, Empty)
+false
+```
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec is_equal(Ordset1, Ordset2) -> boolean() when
@@ -113,20 +158,33 @@ of one set is also a member of the respective other set, otherwise `false`.
is_equal(S1, S2) when is_list(S1), is_list(S2) ->
S1 == S2.
-%% to_list(OrdSet) -> [Elem].
-%% Return the elements in OrdSet as a list.
+-doc """
+Returns the elements of `Ordset` as a list.
+
+## Examples
--doc "Returns the elements of `Ordset` as a list.".
+```erlang
+1> S = ordsets:from_list([a,b]).
+2> ordsets:to_list(S).
+[a,b]
+```
+""".
-spec to_list(Ordset) -> List when
Ordset :: ordset(T),
List :: [T].
to_list(S) -> S.
-%% from_list([Elem]) -> Set.
-%% Build an ordered set from the elements in List.
+-doc """
+Returns an ordered set of the elements in `List`.
+
+## Examples
--doc "Returns an ordered set of the elements in `List`.".
+```erlang
+1> ordsets:from_list([a,b,a,b,b,c]).
+[a,b,c]
+```
+""".
-spec from_list(List) -> Ordset when
List :: [T],
Ordset :: ordset(T).
@@ -134,10 +192,19 @@ to_list(S) -> S.
from_list(L) ->
lists:usort(L).
-%% is_element(Element, OrdSet) -> boolean().
-%% Return 'true' if Element is an element of OrdSet, else 'false'.
+-doc """
+Returns `true` if `Element` is an element of `Ordset`; otherwise, returns `false`.
+
+## Examples
--doc "Returns `true` if `Element` is an element of `Ordset`, otherwise `false`.".
+```erlang
+1> S = ordsets:from_list([a,b,c]).
+2> ordsets:is_element(42, S).
+false
+3> ordsets:is_element(b, S).
+true
+```
+""".
-spec is_element(Element, Ordset) -> boolean() when
Element :: term(),
Ordset :: ordset(_).
@@ -147,26 +214,45 @@ is_element(E, [H|_]) when E < H -> false;
is_element(_E, [_H|_]) -> true; %E == H
is_element(_, []) -> false.
-%% add_element(Element, OrdSet) -> OrdSet.
-%% Return OrdSet with Element inserted in it.
-
--doc "Returns a new ordered set formed from `Ordset1` with `Element` inserted.".
+-doc """
+Returns a new ordered set formed from `Ordset1` with `Element` inserted.
+
+## Examples
+
+```erlang
+1> S0 = ordsets:new().
+[]
+2> S1 = ordsets:add_element(7, S0).
+[7]
+3> S2 = ordsets:add_element(42, S1).
+[7,42]
+4> ordsets:add_element(42, S2).
+[7,42]
+```
+""".
-spec add_element(Element, Ordset1) -> Ordset2 when
Element :: E,
Ordset1 :: ordset(T),
Ordset2 :: ordset(T | E).
-%-spec add_element(E, ordset(T)) -> [T | E,...].
-
add_element(E, [H|Es]) when E > H -> [H|add_element(E, Es)];
add_element(E, [H|_]=Set) when E < H -> [E|Set];
add_element(_E, [_H|_]=Set) -> Set; %E == H
add_element(E, []) -> [E].
-%% del_element(Element, OrdSet) -> OrdSet.
-%% Return OrdSet but with Element removed.
+-doc """
+Returns a copy of `Ordset1` with `Element` removed.
+
+## Examples
--doc "Returns `Ordset1`, but with `Element` removed.".
+```erlang
+1> S = ordsets:from_list([a,b,c]).
+2> ordsets:del_element(c, S).
+[a,b]
+3> ordsets:del_element(x, S).
+[a,b,c]
+```
+""".
-spec del_element(Element, Ordset1) -> Ordset2 when
Element :: term(),
Ordset1 :: ordset(T),
@@ -177,10 +263,21 @@ del_element(E, [H|_]=Set) when E < H -> Set;
del_element(_E, [_H|Es]) -> Es; %E == H
del_element(_, []) -> [].
-%% union(OrdSet1, OrdSet2) -> OrdSet
-%% Return the union of OrdSet1 and OrdSet2.
+-doc """
+Returns the union of `Ordset1` and `Ordset2`.
--doc "Returns the merged (union) set of `Ordset1` and `Ordset2`.".
+The union of two sets is a new set that contains all the elements from
+both sets, without duplicates.
+
+## Examples
+
+```erlang
+1> S0 = ordsets:from_list([a,b,c,d]).
+2> S1 = ordsets:from_list([c,d,e,f]).
+3> ordsets:union(S0, S1).
+[a,b,c,d,e,f]
+```
+""".
-spec union(Ordset1, Ordset2) -> Ordset3 when
Ordset1 :: ordset(T1),
Ordset2 :: ordset(T2),
@@ -195,10 +292,23 @@ union([E1|Es1], [_E2|Es2]) -> %E1 == E2
union([], Es2) -> Es2;
union(Es1, []) -> Es1.
-%% union([OrdSet]) -> OrdSet
-%% Return the union of the list of ordered sets.
+-doc """
+Returns the union of a list of sets.
+
+The union of multiple sets is a new set that contains all the elements from
+all sets, without duplicates.
--doc "Returns the merged (union) set of the list of sets.".
+## Examples
+
+```erlang
+1> S0 = ordsets:from_list([a,b,c,d]).
+2> S1 = ordsets:from_list([d,e,f]).
+3> S2 = ordsets:from_list([q,r])
+4> Sets = [S0, S1, S2].
+5> ordsets:union(Sets).
+[a,b,c,d,e,f,q,r]
+```
+""".
-spec union(OrdsetList) -> Ordset when
OrdsetList :: [ordset(T)],
Ordset :: ordset(T).
@@ -206,10 +316,24 @@ union(Es1, []) -> Es1.
union(OrdsetList) ->
lists:umerge(OrdsetList).
-%% intersection(OrdSet1, OrdSet2) -> OrdSet.
-%% Return the intersection of OrdSet1 and OrdSet2.
-
--doc "Returns the intersection of `Ordset1` and `Ordset2`.".
+-doc """
+Returns the intersection of `Ordset1` and `Ordset2`.
+
+The intersection of two sets is a new set that contains only the
+elements that are present in both sets.
+
+## Examples
+
+```erlang
+1> S0 = ordsets:from_list([a,b,c,d]).
+2> S1 = ordsets:from_list([c,d,e,f]).
+3> S2 = ordsets:from_list([q,r]).
+4> ordsets:intersection(S0, S1).
+[c,d]
+5> ordsets:intersection(S1, S2).
+[]
+```
+""".
-spec intersection(Ordset1, Ordset2) -> Ordset3 when
Ordset1 :: ordset(_),
Ordset2 :: ordset(_),
@@ -226,10 +350,25 @@ intersection([], _) ->
intersection(_, []) ->
[].
-%% intersection([OrdSet]) -> OrdSet.
-%% Return the intersection of the list of ordered sets.
-
--doc "Returns the intersection of the non-empty list of sets.".
+-doc """
+Returns the intersection of the non-empty list of sets.
+
+The intersection of multiple sets is a new set that contains only the
+elements that are present in all sets.
+
+## Examples
+
+```erlang
+1> S0 = ordsets:from_list([a,b,c,d]).
+2> S1 = ordsets:from_list([d,e,f]).
+3> S2 = ordsets:from_list([q,r])
+4> Sets = [S0, S1, S2].
+5> ordsets:intersection([S0, S1, S2]).
+[]
+6> ordsets:intersection([S0, S1]).
+[d]
+```
+""".
-spec intersection(OrdsetList) -> Ordset when
OrdsetList :: [ordset(_),...],
Ordset :: ordset(_).
@@ -242,12 +381,26 @@ intersection1(S1, [S2|Ss]) ->
intersection1(intersection(S1, S2), Ss);
intersection1(S1, []) -> S1.
-%% is_disjoint(OrdSet1, OrdSet2) -> boolean().
-%% Check whether OrdSet1 and OrdSet2 are disjoint.
-
-doc """
-Returns `true` if `Ordset1` and `Ordset2` are disjoint (have no elements in
-common), otherwise `false`.
+Returns `true` if `Ordset1` and `Ordset2` are disjoint; otherwise,
+returns `false`.
+
+Two sets are disjoint if they have no elements in common.
+
+This function is equivalent to `ordsets:intersection(Ordset1, Ordset2)
+=:= []`, but faster.
+
+## Examples
+
+```erlang
+1> S0 = ordsets:from_list([a,b,c,d]).
+2> S1 = ordsets:from_list([d,e,f]).
+3> S2 = ordsets:from_list([q,r])
+4> ordsets:is_disjoint(S0, S1).
+false
+5> ordsets:is_disjoint(S1, S2).
+true
+```
""".
-spec is_disjoint(Ordset1, Ordset2) -> boolean() when
Ordset1 :: ordset(_),
@@ -264,11 +417,20 @@ is_disjoint([], _) ->
is_disjoint(_, []) ->
true.
-%% subtract(OrdSet1, OrdSet2) -> OrdSet.
-%% Return all and only the elements of OrdSet1 which are not also in
-%% OrdSet2.
-
--doc "Returns only the elements of `Ordset1` that are not also elements of `Ordset2`.".
+-doc """
+Returns the elements of `Ordset1` that are not elements in `Ordset2`.
+
+## Examples
+
+```erlang
+1> S0 = ordsets:from_list([a,b,c,d]).
+2> S1 = ordsets:from_list([c,d,e,f]).
+3> ordsets:subtract(S0, S1).
+[a,b]
+4> ordsets:subtract(S1, S0).
+[e,f]
+```
+""".
-spec subtract(Ordset1, Ordset2) -> Ordset3 when
Ordset1 :: ordset(_),
Ordset2 :: ordset(_),
@@ -283,13 +445,22 @@ subtract([_E1|Es1], [_E2|Es2]) -> %E1 == E2
subtract([], _) -> [];
subtract(Es1, []) -> Es1.
-%% is_subset(OrdSet1, OrdSet2) -> boolean().
-%% Return 'true' when every element of OrdSet1 is also a member of
-%% OrdSet2, else 'false'.
-
-doc """
-Returns `true` when every element of `Ordset1` is also a member of `Ordset2`,
-otherwise `false`.
+Returns `true` when every element of `Ordset1` is also a member of `Ordset2`;
+otherwise, returns `false`.
+
+## Examples
+
+```erlang
+1> S0 = ordsets:from_list([a,b,c,d]).
+2> S1 = ordsets:from_list([c,d]).
+3> ordsets:is_subset(S1, S0).
+true
+4> ordsets:is_subset(S0, S1).
+false
+5> ordsets:is_subset(S0, S0).
+true
+```
""".
-spec is_subset(Ordset1, Ordset2) -> boolean() when
Ordset1 :: ordset(_),
@@ -304,12 +475,18 @@ is_subset([_E1|Es1], [_E2|Es2]) -> %E1 == E2
is_subset([], _) -> true;
is_subset(_, []) -> false.
-%% fold(Fun, Accumulator, OrdSet) -> Accumulator.
-%% Fold function Fun over all elements in OrdSet and return Accumulator.
-
-doc """
Folds `Function` over every element in `Ordset` and returns the final value of
the accumulator.
+
+## Examples
+
+```erlang
+1> S = ordsets:from_list([1,2,3,4]).
+2> Plus = fun erlang:'+'/2.
+3> ordsets:fold(Plus, 0, S).
+10
+```
""".
-spec fold(Function, Acc0, Ordset) -> Acc1 when
Function :: fun((Element :: T, AccIn :: term()) -> AccOut :: term()),
@@ -320,10 +497,18 @@ the accumulator.
fold(F, Acc, Set) ->
lists:foldl(F, Acc, Set).
-%% filter(Fun, OrdSet) -> OrdSet.
-%% Filter OrdSet with Fun.
+-doc """
+Filters elements in `Ordset1` using predicate function `Pred`.
--doc "Filters elements in `Ordset1` with boolean function `Pred`.".
+## Examples
+
+```erlang
+1> S = ordsets:from_list([1,2,3,4,5,6,7]).
+2> IsEven = fun(N) -> N rem 2 =:= 0 end.
+3> ordsets:filter(IsEven, S).
+[2,4,6]
+```
+""".
-spec filter(Pred, Ordset1) -> Ordset2 when
Pred :: fun((Element :: T) -> boolean()),
Ordset1 :: ordset(T),
@@ -332,10 +517,18 @@ fold(F, Acc, Set) ->
filter(F, Set) ->
lists:filter(F, Set).
-%% map(Fun, OrdSet) -> OrdSet.
-%% Map OrdSet with Fun.
+-doc """
+Maps elements in `Ordset1` with mapping function `Fun`.
+
+## Examples
--doc "Maps elements in `Ordset1` with mapping function `Fun`.".
+```erlang
+1> S = ordsets:from_list([1,2,3,4,5,6,7]).
+2> F = fun(N) -> N div 2 end.
+3> ordsets:map(F, S).
+[0,1,2,3]
+```
+""".
-doc(#{since => <<"OTP 27.0">>}).
-spec map(Fun, Ordset1) -> Ordset2 when
Fun :: fun((Element1 :: T1) -> Element2 :: T2),
@@ -345,9 +538,35 @@ filter(F, Set) ->
map(F, Set) ->
from_list(lists:map(F, Set)).
-%% filtermap(Fun, OrdSet) -> OrdSet.
-%% Filter and map Ordset with Fun.
--doc "Filters and maps elements in `Ordset1` with function `Fun`.".
+-doc """
+Calls `Fun(Elem)` for each `Elem` of `Ordset1` to update or remove
+elements from `Ordset1`.
+
+`Fun/1` must return either a Boolean or a tuple `{true, Value}`. The
+function returns the set of elements for which `Fun` returns a new
+value, with `true` being equivalent to `{true, Elem}`.
+
+`ordsets:filtermap/2` behaves as if it were defined as follows:
+
+```erlang
+filtermap(Fun, Ordset1) ->
+ ordsets:from_list(lists:filtermap(Fun, Ordset1)).
+```
+
+## Examples
+
+```erlang
+1> S = ordsets:from_list([2,4,5,6,8,9])
+2> F = fun(X) ->
+ case X rem 2 of
+ 0 -> {true, X div 2};
+ 1 -> false
+ end
+ end.
+3> ordsets:filtermap(F, S).
+[1,2,3,4]
+```
+""".
-doc(#{since => <<"OTP 27.0">>}).
-spec filtermap(Fun, Ordset1) -> Ordset2 when
Fun :: fun((Element1 :: T1) -> boolean | ({true, Element2 :: T2})),
diff --git a/lib/stdlib/src/sets.erl b/lib/stdlib/src/sets.erl
index 471cce4bbb..86c2e4688d 100644
--- a/lib/stdlib/src/sets.erl
+++ b/lib/stdlib/src/sets.erl
@@ -47,10 +47,11 @@ existing Erlang terms. See note on
[data types](`e:system:data_types.md#no_user_types`). Any code assuming
knowledge of the format is running on thin ice.
-This module provides the same interface as the `m:ordsets` module but with an
-undefined representation. One difference is that while this module considers two
-elements as different if they do not match (`=:=`), `ordsets` considers two
-elements as different if and only if they do not compare equal (`==`).
+This module provides the same interface as the `m:ordsets` module but
+with an undefined representation. One key difference is that this
+module considers two elements as different if they do not match
+(`=:=`), whereas `ordsets` considers them different if and only if
+they do not compare equal (`==`).
Erlang/OTP 24.0 introduced a new more performant representation for sets which
has become the default in Erlang/OTP 28. Developers can use the old representation
@@ -96,14 +97,14 @@ representations.
> do not match (`=:=`), while both `m:ordsets` and `m:gb_sets` consider elements
> as different if and only if they do not compare equal (`==`).
>
-> _Example:_
+> ### Examples
>
> ```erlang
> 1> sets:is_element(1.0, sets:from_list([1])).
> false
> 2> ordsets:is_element(1.0, ordsets:from_list([1])).
> true
-> 2> gb_sets:is_element(1.0, gb_sets:from_list([1])).
+> 3> gb_sets:is_element(1.0, gb_sets:from_list([1])).
> true
> ```
@@ -163,11 +164,31 @@ representations.
%%------------------------------------------------------------------------------
%% new() -> Set
--doc "Returns a new empty set.".
+-doc """
+Returns a new empty set.
+
+## Examples
+
+```erlang
+1> sets:to_list(sets:new()).
+[]
+```
+""".
-spec new() -> set(none()).
new() -> #{}.
--doc "Returns a new empty set at the given version.".
+-doc """
+Returns a new empty set of the given version.
+
+## Examples
+
+```erlang
+1> sets:to_list(sets:new([{version, 1}])).
+[]
+2> sets:new() =:= sets:new([{version, 2}]).
+true
+```
+""".
-doc(#{since => <<"OTP 24.0">>}).
-spec new([{version, 1..2}]) -> set(none()).
new([{version, 2}]) ->
@@ -180,16 +201,34 @@ new(Opts) ->
2 -> new()
end.
-%% from_list([Elem]) -> Set.
-%% Build a set from the elements in List.
--doc "Returns a set of the elements in `List`.".
+-doc """
+Returns a set of the elements in `List`.
+
+## Examples
+
+```erlang
+1> S = sets:from_list([a,b,c]).
+2> lists:sort(sets:to_list(S)).
+[a,b,c]
+```
+""".
-spec from_list(List) -> Set when
List :: [Element],
Set :: set(Element).
from_list(Ls) ->
maps:from_keys(Ls, ?VALUE).
--doc "Returns a set of the elements in `List` at the given version.".
+-doc """
+Returns a set of the elements in `List` of the given version.
+
+## Examples
+
+```erlang
+1> S = sets:from_list([a,b,c], [{version, 1}]).
+2> lists:sort(sets:to_list(S)).
+[a,b,c]
+```
+""".
-doc(#{since => <<"OTP 24.0">>}).
-spec from_list(List, [{version, 1..2}]) -> Set when
List :: [Element],
@@ -198,19 +237,39 @@ from_list(Ls, [{version, 2}]) ->
from_list(Ls);
from_list(Ls, Opts) ->
case proplists:get_value(version, Opts, 2) of
- 1 -> lists:foldl(fun (E, S) -> add_element(E, S) end, new([{version, 1}]), Ls);
- 2 -> from_list(Ls)
+ 1 ->
+ lists:foldl(fun (E, S) ->
+ add_element(E, S)
+ end, new([{version, 1}]), Ls);
+ 2 ->
+ from_list(Ls)
end.
%%------------------------------------------------------------------------------
-%% is_set(Set) -> boolean().
-%% Return 'true' if Set is a set of elements, else 'false'.
-doc """
-Returns `true` if `Set` appears to be a set of elements, otherwise `false`.
+Returns `true` if `Set` appears to be a set of elements; otherwise,
+returns `false`.
-Note that the test is shallow and will return `true` for any term that coincides with
-the possible representations of a set. See also note on [data types](`e:system:data_types.md#no_user_types`).
+> #### Note {: .info }
+>
+> Note that the test is shallow and will return `true` for any term that
+> coincides with the possible representations of a set. See also note on
+> [data types](`e:system:data_types.md#no_user_types`).
+>
+> Furthermore, since sets are opaque, calling this function on terms
+> that are not sets could result in `m:dialyzer` warnings.
+
+## Examples
+
+```erlang
+1> sets:is_set(sets:new()).
+true
+2> sets:is_set(sets:new([{version,1}])).
+true
+3> sets:is_set(0).
+false
+```
""".
-spec is_set(Set) -> boolean() when
Set :: term().
@@ -218,29 +277,60 @@ is_set(#{}) -> true;
is_set(#set{}) -> true;
is_set(_) -> false.
-%% size(Set) -> int().
-%% Return the number of elements in Set.
--doc "Returns the number of elements in `Set`.".
+-doc """
+Returns the number of elements in `Set`.
+
+## Examples
+
+```erlang
+1> sets:size(sets:new()).
+0
+2> sets:size(sets:from_list([4,5,6])).
+3
+```
+""".
-spec size(Set) -> non_neg_integer() when
Set :: set().
size(#{}=S) -> map_size(S);
size(#set{size=Size}) -> Size.
-%% is_empty(Set) -> boolean().
-%% Return 'true' if Set is an empty set, otherwise 'false'.
--doc "Returns `true` if `Set` is an empty set, otherwise `false`.".
+-doc """
+Returns `true` if `Set` is an empty set; otherwise, returns `false`.
+
+## Examples
+
+```erlang
+1> sets:is_empty(sets:new()).
+true
+2> sets:is_empty(sets:from_list([1])).
+false
+```
+""".
-doc(#{since => <<"OTP 21.0">>}).
-spec is_empty(Set) -> boolean() when
Set :: set().
-is_empty(#{}=S) -> map_size(S)=:=0;
-is_empty(#set{size=Size}) -> Size=:=0.
+is_empty(#{}=S) -> map_size(S) =:= 0;
+is_empty(#set{size=Size}) -> Size =:= 0.
-%% is_equal(Set1, Set2) -> boolean().
-%% Return 'true' if Set1 and Set2 contain the same elements,
-%% otherwise 'false'.
-doc """
-Returns `true` if `Set1` and `Set2` are equal, that is when every element of one
-set is also a member of the respective other set, otherwise `false`.
+Returns `true` if `Set1` and `Set2` are equal, that is, if every element
+of one set is also a member of the other set; otherwise, returns `false`.
+
+## Examples
+
+```erlang
+1> Empty = sets:new().
+2> S = sets:from_list([a,b]).
+3> sets:is_equal(S, S)
+true
+4> sets:is_equal(S, Empty)
+false
+5> OldSet = sets:from_list([a,b], [{version,1}]).
+6> sets:is_equal(S, OldSet).
+true
+7> S =:= OldSet.
+false
+```
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec is_equal(Set1, Set2) -> boolean() when
@@ -259,11 +349,18 @@ is_equal(S1, S2) ->
canonicalize_v2(S) ->
from_list(to_list(S)).
-%% to_list(Set) -> [Elem].
-%% Return the elements in Set as a list.
-doc """
-Returns the elements of `Set` as a list. The order of the returned elements is
-undefined.
+Returns the elements of `Set` as a list.
+
+The order of the returned elements is undefined.
+
+## Examples
+
+```erlang
+1> S = sets:from_list([1,2,3]).
+2> lists:sort(sets:to_list(S)).
+[1,2,3]
+```
""".
-spec to_list(Set) -> List when
Set :: set(Element),
@@ -273,9 +370,20 @@ to_list(#{}=S) ->
to_list(#set{} = S) ->
fold(fun (Elem, List) -> [Elem|List] end, [], S).
-%% is_element(Element, Set) -> boolean().
-%% Return 'true' if Element is an element of Set, else 'false'.
--doc "Returns `true` if `Element` is an element of `Set`, otherwise `false`.".
+-doc """
+Returns `true` if `Element` is an element of `Set`; otherwise, returns
+`false`.
+
+## Examples
+
+```erlang
+1> S = sets:from_list([a,b,c]).
+2> sets:is_element(42, S).
+false
+3> sets:is_element(b, S).
+true
+```
+""".
-spec is_element(Element, Set) -> boolean() when
Set :: set(Element).
is_element(E, #{}=S) ->
@@ -288,9 +396,24 @@ is_element(E, #set{}=S) ->
Bkt = get_bucket(S, Slot),
lists:member(E, Bkt).
-%% add_element(Element, Set) -> Set.
-%% Return Set with Element inserted in it.
--doc "Returns a new set formed from `Set1` with `Element` inserted.".
+-doc """
+Returns a new set formed from `Set1` with `Element` inserted.
+
+## Examples
+
+```erlang
+1> S0 = sets:new().
+2> S1 = sets:add_element(7, S0).
+3> sets:to_list(S1).
+[7]
+4> S2 = sets:add_element(42, S1).
+5> lists:sort(sets:to_list(S2)).
+[7,42]
+6> S2 = sets:add_element(42, S1).
+7> lists:sort(sets:to_list(S2)).
+[7,42]
+```
+""".
-spec add_element(Element, Set1) -> Set2 when
Set1 :: set(Element),
Set2 :: set(Element).
@@ -307,9 +430,20 @@ add_element(E, #set{}=S0) ->
maybe_expand(S1)
end.
-%% del_element(Element, Set) -> Set.
-%% Return Set but with Element removed.
--doc "Returns `Set1`, but with `Element` removed.".
+-doc """
+Returns a copy of `Set1` with `Element` removed.
+
+## Examples
+
+```erlang
+1> S = sets:from_list([a,b]).
+2> sets:to_list(sets:del_element(b, S)).
+[a]
+3> S = sets:del_element(x, S).
+4> lists:sort(sets:to_list(S)).
+[a,b]
+```
+""".
-spec del_element(Element, Set1) -> Set2 when
Set1 :: set(Element),
Set2 :: set(Element).
@@ -340,15 +474,28 @@ update_bucket(Set, Slot, NewBucket) ->
Seg = element(SegI, Segs),
Set#set{segs = setelement(SegI, Segs, setelement(BktI, Seg, NewBucket))}.
-%% union(Set1, Set2) -> Set
-%% Return the union of Set1 and Set2.
--doc "Returns the merged (union) set of `Set1` and `Set2`.".
+-doc """
+Returns the union of `Set1` and `Set2`.
+
+The union of two sets is a new set that contains all the elements from
+both sets, without duplicates.
+
+## Examples
+
+```erlang
+1> S0 = sets:from_list([a,b,c,d]).
+2> S1 = sets:from_list([c,d,e,f]).
+3> Union = sets:union(S0, S1).
+4> lists:sort(sets:to_list(Union)).
+[a,b,c,d,e,f]
+```
+""".
-spec union(Set1, Set2) -> Set3 when
Set1 :: set(Element),
Set2 :: set(Element),
Set3 :: set(Element).
union(#{}=S1, #{}=S2) ->
- maps:merge(S1,S2);
+ maps:merge(S1, S2);
union(S1, S2) ->
case size(S1) < size(S2) of
true ->
@@ -357,9 +504,24 @@ union(S1, S2) ->
fold(fun (E, S) -> add_element(E, S) end, S1, S2)
end.
-%% union([Set]) -> Set
-%% Return the union of the list of sets.
--doc "Returns the merged (union) set of the list of sets.".
+-doc """
+Returns the union of a list of sets.
+
+The union of multiple sets is a new set that contains all the elements from
+all sets, without duplicates.
+
+## Examples
+
+```erlang
+1> S0 = sets:from_list([a,b,c,d]).
+2> S1 = sets:from_list([d,e,f]).
+3> S2 = sets:from_list([q,r])
+4> Sets = [S0, S1, S2].
+5> Union = sets:union(Sets).
+6> lists:sort(sets:to_list(Union)).
+[a,b,c,d,e,f,q,r]
+```
+""".
-spec union(SetList) -> Set when
SetList :: [set(Element)],
Set :: set(Element).
@@ -373,9 +535,25 @@ union1(S1, [S2|Ss]) ->
union1(union(S1, S2), Ss);
union1(S1, []) -> S1.
-%% intersection(Set1, Set2) -> Set.
-%% Return the intersection of Set1 and Set2.
--doc "Returns the intersection of `Set1` and `Set2`.".
+-doc """
+Returns the intersection of `Set1` and `Set2`.
+
+The intersection of two sets is a new set that contains only the
+elements that are present in both sets.
+
+## Examples
+
+```erlang
+1> S0 = sets:from_list([a,b,c,d]).
+2> S1 = sets:from_list([c,d,e,f]).
+3> S2 = sets:from_list([q,r]).
+4> Intersection = sets:intersection(S0, S1).
+5> lists:sort(sets:to_list(Intersection)).
+[c,d]
+6> sets:to_list(sets:intersection(S1, S2)).
+[]
+```
+""".
-spec intersection(Set1, Set2) -> Set3 when
Set1 :: set(Element),
Set2 :: set(Element),
@@ -384,10 +562,12 @@ intersection(#{}=S1, #{}=S2) ->
case map_size(S1) < map_size(S2) of
true ->
Next = maps:next(maps:iterator(S1)),
- intersection_heuristic(Next, [], [], floor(map_size(S1) * 0.75), S1, S2);
+ intersection_heuristic(Next, [], [],
+ floor(map_size(S1) * 0.75), S1, S2);
false ->
Next = maps:next(maps:iterator(S2)),
- intersection_heuristic(Next, [], [], floor(map_size(S2) * 0.75), S2, S1)
+ intersection_heuristic(Next, [], [],
+ floor(map_size(S2) * 0.75), S2, S1)
end;
intersection(S1, S2) ->
case size(S1) < size(S2) of
@@ -400,23 +580,26 @@ intersection(S1, S2) ->
%% If we are keeping more than 75% of the keys, then it is
%% cheaper to delete them. Stop accumulating and start deleting.
intersection_heuristic(Next, _Keep, Delete, 0, Acc, Reference) ->
- intersection_decided(Next, remove_keys(Delete, Acc), Reference);
-intersection_heuristic({Key, _Value, Iterator}, Keep, Delete, KeepCount, Acc, Reference) ->
+ intersection_decided(Next, remove_keys(Delete, Acc), Reference);
+intersection_heuristic({Key, _Value, Iterator}, Keep, Delete, KeepCount,
+ Acc, Reference) ->
Next = maps:next(Iterator),
case Reference of
#{Key := _} ->
- intersection_heuristic(Next, [Key | Keep], Delete, KeepCount - 1, Acc, Reference);
- _ ->
- intersection_heuristic(Next, Keep, [Key | Delete], KeepCount, Acc, Reference)
+ intersection_heuristic(Next, [Key | Keep], Delete, KeepCount - 1,
+ Acc, Reference);
+ #{} ->
+ intersection_heuristic(Next, Keep, [Key | Delete], KeepCount,
+ Acc, Reference)
end;
intersection_heuristic(none, Keep, _Delete, _Count, _Acc, _Reference) ->
maps:from_keys(Keep, ?VALUE).
intersection_decided({Key, _Value, Iterator}, Acc0, Reference) ->
Acc1 = case Reference of
- #{Key := _} -> Acc0;
- #{} -> maps:remove(Key, Acc0)
- end,
+ #{Key := _} -> Acc0;
+ #{} -> maps:remove(Key, Acc0)
+ end,
intersection_decided(maps:next(Iterator), Acc1, Reference);
intersection_decided(none, Acc, _Reference) ->
Acc.
@@ -424,9 +607,25 @@ intersection_decided(none, Acc, _Reference) ->
remove_keys([K | Ks], Map) -> remove_keys(Ks, maps:remove(K, Map));
remove_keys([], Map) -> Map.
-%% intersection([Set]) -> Set.
-%% Return the intersection of the list of sets.
--doc "Returns the intersection of the non-empty list of sets.".
+-doc """
+Returns the intersection of the non-empty list of sets.
+
+The intersection of multiple sets is a new set that contains only the
+elements that are present in all sets.
+
+## Examples
+
+```erlang
+1> S0 = sets:from_list([a,b,c,d]).
+2> S1 = sets:from_list([d,e,f]).
+3> S2 = sets:from_list([q,r])
+4> Sets = [S0, S1, S2].
+5> sets:to_list(sets:intersection([S0, S1, S2])).
+[]
+6> sets:to_list(sets:intersection([S0, S1])).
+[d]
+```
+""".
-spec intersection(SetList) -> Set when
SetList :: [set(Element),...],
Set :: set(Element).
@@ -439,11 +638,26 @@ intersection1(S1, [S2|Ss]) ->
intersection1(intersection(S1, S2), Ss);
intersection1(S1, []) -> S1.
-%% is_disjoint(Set1, Set2) -> boolean().
-%% Check whether Set1 and Set2 are disjoint.
-doc """
-Returns `true` if `Set1` and `Set2` are disjoint (have no elements in common),
-otherwise `false`.
+Returns `true` if `Set1` and `Set2` are disjoint; otherwise, returns
+`false`.
+
+Two sets are disjoint if they have no elements in common.
+
+This function is equivalent to `sets:intersection(Set1, Set2) =:= []`,
+but faster.
+
+## Examples
+
+```erlang
+1> S0 = sets:from_list([a,b,c,d]).
+2> S1 = sets:from_list([d,e,f]).
+3> S2 = sets:from_list([q,r])
+4> sets:is_disjoint(S0, S1).
+false
+5> sets:is_disjoint(S1, S2).
+true
+```
""".
-spec is_disjoint(Set1, Set2) -> boolean() when
Set1 :: set(Element),
@@ -478,10 +692,20 @@ is_disjoint_1(Set, Iter) ->
true
end.
-%% subtract(Set1, Set2) -> Set.
-%% Return all and only the elements of Set1 which are not also in
-%% Set2.
--doc "Returns only the elements of `Set1` that are not also elements of `Set2`.".
+-doc """
+Returns the elements of `Set1` that are not elements in `Set2`.
+
+## Examples
+
+```erlang
+1> S0 = sets:from_list([a,b,c,d]).
+2> S1 = sets:from_list([c,d,e,f]).
+3> lists:sort(sets:to_list(sets:subtract(S0, S1))).
+[a,b]
+4> lists:sort(sets:to_list(sets:subtract(S1, S0))).
+[e,f]
+```
+""".
-spec subtract(Set1, Set2) -> Set3 when
Set1 :: set(Element),
Set2 :: set(Element),
@@ -538,12 +762,22 @@ subtract_decided({Key, _Value, Iterator}, Acc, Reference) ->
subtract_decided(none, Acc, _Reference) ->
Acc.
-%% is_subset(Set1, Set2) -> boolean().
-%% Return 'true' when every element of Set1 is also a member of
-%% Set2, else 'false'.
-doc """
-Returns `true` when every element of `Set1` is also a member of `Set2`,
-otherwise `false`.
+Returns `true` when every element of `Set1` is also a member of `Set2`;
+otherwise, returns `false`.
+
+## Examples
+
+```erlang
+1> S0 = sets:from_list([a,b,c,d]).
+2> S1 = sets:from_list([c,d]).
+3> sets:is_subset(S1, S0).
+true
+4> sets:is_subset(S0, S1).
+false
+5> sets:is_subset(S0, S0).
+true
+```
""".
-spec is_subset(Set1, Set2) -> boolean() when
Set1 :: set(Element),
@@ -570,11 +804,20 @@ is_subset_1(Set, Iter) ->
true
end.
-%% fold(Fun, Accumulator, Set) -> Accumulator.
-%% Fold function Fun over all elements in Set and return Accumulator.
-doc """
-Folds `Function` over every element in `Set` and returns the final value of the
-accumulator. The evaluation order is undefined.
+Folds `Function` over every element in `Set` and returns the final value of
+the accumulator.
+
+The evaluation order is undefined.
+
+## Examples
+
+```erlang
+1> S = sets:from_list([1,2,3,4]).
+2> Plus = fun erlang:'+'/2.
+3> sets:fold(Plus, 0, S).
+10
+```
""".
-spec fold(Function, Acc0, Set) -> Acc1 when
Function :: fun((Element, AccIn) -> AccOut),
@@ -596,9 +839,19 @@ fold_1(Fun, Acc, Iter) ->
Acc
end.
-%% filter(Fun, Set) -> Set.
-%% Filter Set with Fun.
--doc "Filters elements in `Set1` with boolean function `Pred`.".
+-doc """
+Filters elements in `Set1` using predicate function `Pred`.
+
+## Examples
+
+```erlang
+1> S = sets:from_list([1,2,3,4,5,6,7]).
+2> IsEven = fun(N) -> N rem 2 =:= 0 end.
+3> Filtered = sets:filter(IsEven, S).
+4> lists:sort(sets:to_list(Filtered)).
+[2,4,6]
+```
+""".
-spec filter(Pred, Set1) -> Set2 when
Pred :: fun((Element) -> boolean()),
Set1 :: set(Element),
@@ -610,9 +863,19 @@ filter(F, #{}=D) when is_function(F, 1)->
filter(F, #set{}=D) when is_function(F, 1)->
filter_set(F, D).
-%% map(Fun, Set) -> Set.
-%% Map Set with Map.
--doc "Maps elements in `Set1` with mapping function `Fun`.".
+-doc """
+Maps elements in `Set1` with mapping function `Fun`.
+
+## Examples
+
+```erlang
+1> S = sets:from_list([1,2,3,4,5,6,7]).
+2> F = fun(N) -> N div 2 end.
+3> Mapped = sets:map(F, S).
+4> lists:sort(sets:to_list(Mapped)).
+[0,1,2,3]
+```
+""".
-doc(#{since => <<"OTP 27.0">>}).
-spec map(Fun, Set1) -> Set2 when
Fun :: fun((Element1) -> Element2),
@@ -620,16 +883,43 @@ filter(F, #set{}=D) when is_function(F, 1)->
Set2 :: set(Element2).
map(F, #{}=D) when is_function(F, 1) ->
%% For this purpose, it is more efficient to use
- %% maps:from_keys than a map comprehension.
+ %% maps:from_keys/2 than a map comprehension.
maps:from_keys([F(K) || K := _ <- D], ?VALUE);
map(F, #set{}=D) when is_function(F, 1) ->
fold(fun(E, Acc) -> add_element(F(E), Acc) end,
new([{version, 1}]),
D).
-%% filtermap(Fun, Set) -> Set.
-%% Filter and map Set with Fun.
--doc "Filters and maps elements in `Set1` with function `Fun`.".
+-doc """
+Calls `Fun(Elem)` for each `Elem` of `Set1` to update or remove
+elements from `Set1`.
+
+`Fun/1` must return either a Boolean or a tuple `{true, Value}`. The
+function returns the set of elements for which `Fun` returns a new
+value, with `true` being equivalent to `{true, Elem}`.
+
+`sets:filtermap/2` behaves as if it were defined as follows:
+
+```erlang
+filtermap(Fun, Set1) ->
+ sets:from_list(lists:filtermap(Fun, Set1)).
+```
+
+## Examples
+
+```erlang
+1> S = sets:from_list([2,4,5,6,8,9])
+2> F = fun(X) ->
+ case X rem 2 of
+ 0 -> {true, X div 2};
+ 1 -> false
+ end
+ end.
+3> Set = sets:filtermap(F, S).
+4> lists:sort(sets:to_list(Set)).
+[1,2,3,4]
+```
+""".
-doc(#{since => <<"OTP 27.0">>}).
-spec filtermap(Fun, Set1) -> Set2 when
Fun :: fun((Element1) -> boolean() | {true, Element2}),
diff --git a/lib/stdlib/test/sets_SUITE.erl b/lib/stdlib/test/sets_SUITE.erl
index 733767d37b..37328e29d9 100644
--- a/lib/stdlib/test/sets_SUITE.erl
+++ b/lib/stdlib/test/sets_SUITE.erl
@@ -29,7 +29,8 @@
create/1,add_element/1,del_element/1,
subtract/1,intersection/1,union/1,is_subset/1,
is_equal/1, is_disjoint/1,is_set/1,is_empty/1,fold/1,filter/1,
- map/1, filtermap/1, take_smallest/1,take_largest/1, iterate/1]).
+ map/1, filtermap/1, take_smallest/1,take_largest/1, iterate/1,
+ doctests/1]).
-include_lib("common_test/include/ct.hrl").
@@ -49,7 +50,7 @@ all() ->
[create, add_element, del_element, subtract,
intersection, union, is_subset, is_set, fold, filter, map,
filtermap, take_smallest, take_largest, iterate, is_empty,
- is_disjoint, is_equal].
+ is_disjoint, is_equal, doctests].
groups() ->
[].
@@ -535,6 +536,14 @@ iterate_set_1(_, none, R) ->
iterate_set_1(M, {E, I}, R) ->
iterate_set_1(M, M(next, I), [E | R]).
+doctests(_Config) ->
+ Modules = [gb_sets, ordsets, sets],
+ lists:foreach(fun(M) ->
+ io:format("Testing module: ~p\n", [M]),
+ shell_docs:test(M, []),
+ io:nl()
+ end, Modules).
+
%%%
%%% Helper functions.
%%%
--
2.43.0