View Source sets (stdlib v6.1.2)
Sets are collections of elements with no duplicate elements.
The data representing a set as used by this module is to be regarded as opaque by other modules. In abstract terms, the representation is a composite type of existing Erlang terms. See note on data types. Any code assuming knowledge of the format is running on thin ice.
This module provides the same interface as the 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 (==
).
Erlang/OTP 24.0 introduced a new internal representation for sets which is more
performant. Developers can use this new representation by passing the
{version, 2}
flag to new/1
and from_list/2
, such as
sets:new([{version, 2}])
. This new representation will become the default in
future Erlang/OTP versions. Functions that work on two sets, such as union/2
and similar, will work with sets of different versions. In such cases, there is
no guarantee about the version of the returned set. Explicit conversion from the
old version to the new one can be done with
sets:from_list(sets:to_list(Old), [{version,2}])
.
Compatibility
The following functions in this module also exist and provide the same
functionality in the gb_sets
and ordsets
modules. That is, by only
changing the module name for each call, you can try out different set
representations.
add_element/2
del_element/2
filter/2
filtermap/2
fold/3
from_list/1
intersection/1
intersection/2
is_element/2
is_empty/1
is_equal/2
is_set/1
is_subset/2
map/2
new/0
size/1
subtract/2
to_list/1
union/1
union/2
Note
While the three set implementations offer the same functionality with respect to the aforementioned functions, their overall behavior may differ. As mentioned, this module considers elements as different if and only if they do not match (
=:=
), while bothordsets
andgb_sets
consider elements as different if and only if they do not compare equal (==
).Example:
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])). true
See Also
Summary
Functions
Returns a new set formed from Set1
with Element
inserted.
Returns Set1
, but with Element
removed.
Filters elements in Set1
with boolean function Pred
.
Filters and maps elements in Set1
with function Fun
.
Folds Function
over every element in Set
and returns the final value of the
accumulator. The evaluation order is undefined.
Returns a set of the elements in List
.
Returns a set of the elements in List
at the given version.
Returns the intersection of the non-empty list of sets.
Returns the intersection of Set1
and Set2
.
Returns true
if Set1
and Set2
are disjoint (have no elements in common),
otherwise false
.
Returns true
if Element
is an element of Set
, otherwise false
.
Returns true
if Set
is an empty set, otherwise false
.
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 Set
appears to be a set of elements, otherwise false
.
Returns true
when every element of Set1
is also a member of Set2
,
otherwise false
.
Maps elements in Set1
with mapping function Fun
.
Returns a new empty set.
Returns a new empty set at the given version.
Returns the number of elements in Set
.
Returns only the elements of Set1
that are not also elements of Set2
.
Returns the elements of Set
as a list. The order of the returned elements is
undefined.
Returns the merged (union) set of the list of sets.
Returns the merged (union) set of Set1
and Set2
.
Types
Functions
Returns a new set formed from Set1
with Element
inserted.
Returns Set1
, but with Element
removed.
-spec filter(Pred, Set1) -> Set2 when Pred :: fun((Element) -> boolean()), Set1 :: set(Element), Set2 :: set(Element).
Filters elements in Set1
with boolean function Pred
.
-spec filtermap(Fun, Set1) -> Set2 when Fun :: fun((Element1) -> boolean() | {true, Element2}), Set1 :: set(Element1), Set2 :: set(Element1 | Element2).
Filters and maps elements in Set1
with function Fun
.
-spec fold(Function, Acc0, Set) -> Acc1 when Function :: fun((Element, AccIn) -> AccOut), Set :: set(Element), Acc0 :: Acc, Acc1 :: Acc, AccIn :: Acc, AccOut :: Acc.
Folds Function
over every element in Set
and returns the final value of the
accumulator. The evaluation order is undefined.
-spec from_list(List) -> Set when List :: [Element], Set :: set(Element).
Returns a set of the elements in List
.
-spec from_list(List, [{version, 1..2}]) -> Set when List :: [Element], Set :: set(Element).
Returns a set of the elements in List
at the given version.
Returns the intersection of the non-empty list of sets.
-spec intersection(Set1, Set2) -> Set3 when Set1 :: set(Element), Set2 :: set(Element), Set3 :: set(Element).
Returns the intersection of Set1
and Set2
.
Returns true
if Set1
and Set2
are disjoint (have no elements in common),
otherwise false
.
Returns true
if Element
is an element of Set
, otherwise false
.
Returns true
if Set
is an empty set, otherwise false
.
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 Set
appears to be a set of elements, otherwise 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.
Returns true
when every element of Set1
is also a member of Set2
,
otherwise false
.
-spec map(Fun, Set1) -> Set2 when Fun :: fun((Element1) -> Element2), Set1 :: set(Element1), Set2 :: set(Element2).
Maps elements in Set1
with mapping function Fun
.
Returns a new empty set.
Returns a new empty set at the given version.
-spec size(Set) -> non_neg_integer() when Set :: set().
Returns the number of elements in Set
.
-spec subtract(Set1, Set2) -> Set3 when Set1 :: set(Element), Set2 :: set(Element), Set3 :: set(Element).
Returns only the elements of Set1
that are not also elements of Set2
.
-spec to_list(Set) -> List when Set :: set(Element), List :: [Element].
Returns the elements of Set
as a list. The order of the returned elements is
undefined.
Returns the merged (union) set of the list of sets.
-spec union(Set1, Set2) -> Set3 when Set1 :: set(Element), Set2 :: set(Element), Set3 :: set(Element).
Returns the merged (union) set of Set1
and Set2
.