View Source ordsets (stdlib v6.0)

Functions for manipulating sets as ordered lists.

Sets are collections of elements with no duplicate elements. An ordset is a representation of a set, where an ordered list is used to store the elements of the set. An ordered list is more efficient than an unordered list. Elements are ordered according to the Erlang term order.

This module provides the same interface as the sets module but with a defined representation. One difference is that while sets considers two elements as different if they do not match (=:=), this module considers two elements as different if and only if they do not compare equal (==).

See the Compatibility Section in the sets module for more information about the compatibility of the different implementations of sets in the Standard Library.

See Also

gb_sets, sets

Summary

Types

As returned by new/0.

Functions

Returns a new ordered set formed from Ordset1 with Element inserted.

Returns Ordset1, but with Element removed.

Filters elements in Ordset1 with boolean function Pred.

Filters and maps elements in Ordset1 with function Fun.

Folds Function over every element in Ordset and returns the final value of the accumulator.

Returns an ordered set of the elements in List.

Returns the intersection of the non-empty list of sets.

Returns the intersection of Ordset1 and Ordset2.

Returns true if Ordset1 and Ordset2 are disjoint (have no elements in common), otherwise false.

Returns true if Element is an element of Ordset, otherwise false.

Returns true if Ordset is an empty set, otherwise false.

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 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 when every element of Ordset1 is also a member of Ordset2, otherwise false.

Maps elements in Ordset1 with mapping function Fun.

Returns a new empty ordered set.

Returns the number of elements in Ordset.

Returns only the elements of Ordset1 that are not also elements of Ordset2.

Returns the elements of Ordset as a list.

Returns the merged (union) set of the list of sets.

Returns the merged (union) set of Ordset1 and Ordset2.

Types

-type ordset(T) :: [T].

As returned by new/0.

Functions

Link to this function

add_element(Element, Ordset1)

View Source
-spec add_element(Element, Ordset1) -> Ordset2
                     when Element :: E, Ordset1 :: ordset(T), Ordset2 :: ordset(T | E).

Returns a new ordered set formed from Ordset1 with Element inserted.

Link to this function

del_element(Element, Ordset1)

View Source
-spec del_element(Element, Ordset1) -> Ordset2
                     when Element :: term(), Ordset1 :: ordset(T), Ordset2 :: ordset(T).

Returns Ordset1, but with Element removed.

-spec filter(Pred, Ordset1) -> Ordset2
                when
                    Pred :: fun((Element :: T) -> boolean()), Ordset1 :: ordset(T), Ordset2 :: ordset(T).

Filters elements in Ordset1 with boolean function Pred.

Link to this function

filtermap(Fun, Ordset1)

View Source (since OTP 27.0)
-spec filtermap(Fun, Ordset1) -> Ordset2
                   when
                       Fun :: fun((Element1 :: T1) -> boolean | {true, Element2 :: T2}),
                       Ordset1 :: ordset(T1),
                       Ordset2 :: ordset(T1 | T2).

Filters and maps elements in Ordset1 with function Fun.

Link to this function

fold(Function, Acc0, Ordset)

View Source
-spec fold(Function, Acc0, Ordset) -> Acc1
              when
                  Function :: fun((Element :: T, AccIn :: term()) -> AccOut :: term()),
                  Ordset :: ordset(T),
                  Acc0 :: term(),
                  Acc1 :: term().

Folds Function over every element in Ordset and returns the final value of the accumulator.

-spec from_list(List) -> Ordset when List :: [T], Ordset :: ordset(T).

Returns an ordered set of the elements in List.

Link to this function

intersection(OrdsetList)

View Source
-spec intersection(OrdsetList) -> Ordset when OrdsetList :: [ordset(_), ...], Ordset :: ordset(_).

Returns the intersection of the non-empty list of sets.

Link to this function

intersection(Ordset1, Ordset2)

View Source
-spec intersection(Ordset1, Ordset2) -> Ordset3
                      when Ordset1 :: ordset(_), Ordset2 :: ordset(_), Ordset3 :: ordset(_).

Returns the intersection of Ordset1 and Ordset2.

Link to this function

is_disjoint(Ordset1, Ordset2)

View Source
-spec is_disjoint(Ordset1, Ordset2) -> boolean() when Ordset1 :: ordset(_), Ordset2 :: ordset(_).

Returns true if Ordset1 and Ordset2 are disjoint (have no elements in common), otherwise false.

Link to this function

is_element(Element, Ordset)

View Source
-spec is_element(Element, Ordset) -> boolean() when Element :: term(), Ordset :: ordset(_).

Returns true if Element is an element of Ordset, otherwise false.

Link to this function

is_empty(Ordset)

View Source (since OTP 21.0)
-spec is_empty(Ordset) -> boolean() when Ordset :: ordset(_).

Returns true if Ordset is an empty set, otherwise false.

Link to this function

is_equal(Ordset1, Ordset2)

View Source (since OTP 27.0)
-spec is_equal(Ordset1, Ordset2) -> boolean() when Ordset1 :: ordset(_), Ordset2 :: ordset(_).

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.

-spec is_set(Ordset) -> boolean() when Ordset :: term().

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.

Link to this function

is_subset(Ordset1, Ordset2)

View Source
-spec is_subset(Ordset1, Ordset2) -> boolean() when Ordset1 :: ordset(_), Ordset2 :: ordset(_).

Returns true when every element of Ordset1 is also a member of Ordset2, otherwise false.

Link to this function

map(Fun, Ordset1)

View Source (since OTP 27.0)
-spec map(Fun, Ordset1) -> Ordset2
             when
                 Fun :: fun((Element1 :: T1) -> Element2 :: T2),
                 Ordset1 :: ordset(T1),
                 Ordset2 :: ordset(T2).

Maps elements in Ordset1 with mapping function Fun.

-spec new() -> [].

Returns a new empty ordered set.

-spec size(Ordset) -> non_neg_integer() when Ordset :: ordset(_).

Returns the number of elements in Ordset.

Link to this function

subtract(Ordset1, Ordset2)

View Source
-spec subtract(Ordset1, Ordset2) -> Ordset3
                  when Ordset1 :: ordset(_), Ordset2 :: ordset(_), Ordset3 :: ordset(_).

Returns only the elements of Ordset1 that are not also elements of Ordset2.

-spec to_list(Ordset) -> List when Ordset :: ordset(T), List :: [T].

Returns the elements of Ordset as a list.

-spec union(OrdsetList) -> Ordset when OrdsetList :: [ordset(T)], Ordset :: ordset(T).

Returns the merged (union) set of the list of sets.

-spec union(Ordset1, Ordset2) -> Ordset3
               when Ordset1 :: ordset(T1), Ordset2 :: ordset(T2), Ordset3 :: ordset(T1 | T2).

Returns the merged (union) set of Ordset1 and Ordset2.