sets

Functions for set manipulation.

Sets are collections of elements with no duplicate elements. The representation of a set is undefined.

This module provides the same interface as the ordsets(3) 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 (==).

Types


set(Element)

As returned by new/0.

set() = set(term())

Functions


add_element(Element, Set1) -> Set2

  • Set1 = Set2 = set(Element)

Returns a new set formed from Set1 with Element inserted.

del_element(Element, Set1) -> Set2

  • Set1 = Set2 = set(Element)

Returns Set1, but with Element removed.

filter(Pred, Set1) -> Set2

  • Pred = fun((Element) -> boolean())
  • Set1 = Set2 = set(Element)

Filters elements in Set1 with boolean function Pred.

fold(Function, Acc0, Set) -> Acc1

  • Function = fun((Element, AccIn) -> AccOut)
  • Set = set(Element)
  • Acc0 = Acc1 = AccIn = AccOut = Acc

Folds Function over every element in Set and returns the final value of the accumulator. The evaluation order is undefined.

from_list(List) -> Set

  • List = [Element]
  • Set = set(Element)

Returns a set of the elements in List.

intersection(SetList) -> Set

  • SetList = [set(Element), ...]
  • Set = set(Element)

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

intersection(Set1, Set2) -> Set3

  • Set1 = Set2 = Set3 = set(Element)

Returns the intersection of Set1 and Set2.

is_disjoint(Set1, Set2) -> boolean()

  • Set1 = Set2 = set(Element)

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

is_element(Element, Set) -> boolean()

  • Set = set(Element)

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

is_empty(Set) -> boolean()

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

is_set(Set) -> boolean()

  • Set = term()

Returns true if Set is a set of elements, otherwise false.

is_subset(Set1, Set2) -> boolean()

  • Set1 = Set2 = set(Element)

Returns true when every element of Set1 is also a member of Set2, otherwise false.

new() -> set()

Returns a new empty set.

size(Set) -> integer() >= 0

Returns the number of elements in Set.

subtract(Set1, Set2) -> Set3

  • Set1 = Set2 = Set3 = set(Element)

Returns only the elements of Set1 that are not also elements of Set2.

to_list(Set) -> List

  • Set = set(Element)
  • List = [Element]

Returns the elements of Set as a list. The order of the returned elements is undefined.

union(SetList) -> Set

  • SetList = [set(Element)]
  • Set = set(Element)

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

union(Set1, Set2) -> Set3

  • Set1 = Set2 = Set3 = set(Element)

Returns the merged (union) set of Set1 and Set2.