Functions for manipulating sets of sets.
This module provides operations on finite sets and relations represented as sets. Intuitively, a set is a collection of elements; every element belongs to the set, and the set contains every element.
Given a set A and a sentence S(x), where x is a free variable, a new set B whose elements are exactly those elements of A for which S(x) holds can be formed, this is denoted B = {x in A : S(x)}. Sentences are expressed using the logical operators "for some" (or "there exists"), "for all", "and", "or", "not". If the existence of a set containing all the specified elements is known (as is always the case in this module), this is denoted B = {x : S(x)}.
-
The unordered set containing the elements a, b, and c is denoted {a, b, c}. This notation is not to be confused with tuples.
The ordered pair of a and b, with first coordinate a and second coordinate b, is denoted (a, b). An ordered pair is an ordered set of two elements. In this module, ordered sets can contain one, two, or more elements, and parentheses are used to enclose the elements.
Unordered sets and ordered sets are orthogonal, again in this module; there is no unordered set equal to any ordered set.
-
The empty set contains no elements.
Set A is equal to set B if they contain the same elements, which is denoted A = B. Two ordered sets are equal if they contain the same number of elements and have equal elements at each coordinate.
Set B is a subset of set A if A contains all elements that B contains.
The union of two sets A and B is the smallest set that contains all elements of A and all elements of B.
The intersection of two sets A and B is the set that contains all elements of A that belong to B.
Two sets are disjoint if their intersection is the empty set.
The difference of two sets A and B is the set that contains all elements of A that do not belong to B.
The symmetric difference of two sets is the set that contains those element that belong to either of the two sets, but not both.
The union of a collection of sets is the smallest set that contains all the elements that belong to at least one set of the collection.
The intersection of a non-empty collection of sets is the set that contains all elements that belong to every set of the collection.
-
The Cartesian product of two sets X and Y, denoted X × Y, is the set {a : a = (x, y) for some x in X and for some y in Y}.
A relation is a subset of X × Y. Let R be a relation. The fact that (x, y) belongs to R is written as x R y. As relations are sets, the definitions of the last item (subset, union, and so on) apply to relations as well.
The domain of R is the set {x : x R y for some y in Y}.
The range of R is the set {y : x R y for some x in X}.
The converse of R is the set {a : a = (y, x) for some (x, y) in R}.
If A is a subset of X, the image of A under R is the set {y : x R y for some x in A}. If B is a subset of Y, the inverse image of B is the set {x : x R y for some y in B}.
If R is a relation from X to Y, and S is a relation from Y to Z, the relative product of R and S is the relation T from X to Z defined so that x T z if and only if there exists an element y in Y such that x R y and y S z.
The restriction of R to A is the set S defined so that x S y if and only if there exists an element x in A such that x R y.
If S is a restriction of R to A, then R is an extension of S to X.
If X = Y, then R is called a relation in X.
The field of a relation R in X is the union of the domain of R and the range of R.
If R is a relation in X, and if S is defined so that x S y if x R y and not x = y, then S is the strict relation corresponding to R. Conversely, if S is a relation in X, and if R is defined so that x R y if x S y or x = y, then R is the weak relation corresponding to S.
A relation R in X is reflexive if x R x for every element x of X, it is symmetric if x R y implies that y R x, and it is transitive if x R y and y R z imply that x R z.
-
A function F is a relation, a subset of X × Y, such that the domain of F is equal to X and such that for every x in X there is a unique element y in Y with (x, y) in F. The latter condition can be formulated as follows: if x F y and x F z, then y = z. In this module, it is not required that the domain of F is equal to X for a relation to be considered a function.
Instead of writing (x, y) in F or x F y, we write F(x) = y when F is a function, and say that F maps x onto y, or that the value of F at x is y.
As functions are relations, the definitions of the last item (domain, range, and so on) apply to functions as well.
If the converse of a function F is a function F', then F' is called the inverse of F.
The relative product of two functions F1 and F2 is called the composite of F1 and F2 if the range of F1 is a subset of the domain of F2.
-
Sometimes, when the range of a function is more important than the function itself, the function is called a family.
The domain of a family is called the index set, and the range is called the indexed set.
If x is a family from I to X, then x[i] denotes the value of the function at index i. The notation "a family in X" is used for such a family.
When the indexed set is a set of subsets of a set X, we call x a family of subsets of X.
If x is a family of subsets of X, the union of the range of x is called the union of the family x.
If x is non-empty (the index set is non-empty), the intersection of the family x is the intersection of the range of x.
In this module, the only families that are considered are families of subsets of some set X; in the following, the word "family" is used for such families of subsets.
-
A partition of a set X is a collection S of non-empty subsets of X whose union is X and whose elements are pairwise disjoint.
A relation in a set is an equivalence relation if it is reflexive, symmetric, and transitive.
If R is an equivalence relation in X, and x is an element of X, the equivalence class of x with respect to R is the set of all those elements y of X for which x R y holds. The equivalence classes constitute a partitioning of X. Conversely, if C is a partition of X, the relation that holds for any two elements of X if they belong to the same equivalence class, is an equivalence relation induced by the partition C.
If R is an equivalence relation in X, the canonical map is the function that maps every element of X onto its equivalence class.
-
Relations as defined above (as sets of ordered pairs) are from now on referred to as binary relations.
We call a set of ordered sets (x[1], ..., x[n]) an (n-ary) relation, and say that the relation is a subset of the Cartesian product X[1] × ... × X[n], where x[i] is an element of X[i], 1 <= i <= n.
The projection of an n-ary relation R onto coordinate i is the set {x[i] : (x[1], ..., x[i], ..., x[n]) in R for some x[j] in X[j], 1 <= j <= n and not i = j}. The projections of a binary relation R onto the first and second coordinates are the domain and the range of R, respectively.
The relative product of binary relations can be generalized to n-ary relations as follows. Let TR be an ordered set (R[1], ..., R[n]) of binary relations from X to Y[i] and S a binary relation from (Y[1] × ... × Y[n]) to Z. The relative product of TR and S is the binary relation T from X to Z defined so that x T z if and only if there exists an element y[i] in Y[i] for each 1 <= i <= n such that x R[i] y[i] and (y[1], ..., y[n]) S z. Now let TR be a an ordered set (R[1], ..., R[n]) of binary relations from X[i] to Y[i] and S a subset of X[1] × ... × X[n]. The multiple relative product of TR and S is defined to be the set {z : z = ((x[1], ..., x[n]), (y[1],...,y[n])) for some (x[1], ..., x[n]) in S and for some (x[i], y[i]) in R[i], 1 <= i <= n}.
The natural join of an n-ary relation R and an m-ary relation S on coordinate i and j is defined to be the set {z : z = (x[1], ..., x[n], y[1], ..., y[j-1], y[j+1], ..., y[m]) for some (x[1], ..., x[n]) in R and for some (y[1], ..., y[m]) in S such that x[i] = y[j]}.
-
The sets recognized by this module are represented by elements of the relation Sets, which is defined as the smallest set such that:
-
For every atom T, except '_', and for every term X, (T, X) belongs to Sets (atomic sets).
-
(['_'], []) belongs to Sets (the untyped empty set).
-
For every tuple T = {T[1], ..., T[n]} and for every tuple X = {X[1], ..., X[n]}, if (T[i], X[i]) belongs to Sets for every 1 <= i <= n, then (T, X) belongs to Sets (ordered sets).
-
For every term T, if X is the empty list or a non-empty sorted list [X[1], ..., X[n]] without duplicates such that (T, X[i]) belongs to Sets for every 1 <= i <= n, then ([T], X) belongs to Sets (typed unordered sets).
An external set is an element of the range of Sets.
A type is an element of the domain of Sets.
If S is an element (T, X) of Sets, then T is a valid type of X, T is the type of S, and X is the external set of S.
from_term/2
creates a set from a type and an Erlang term turned into an external set.The sets represented by Sets are the elements of the range of function Set from Sets to Erlang terms and sets of Erlang terms:
- Set(T,Term) = Term, where T is an atom
- Set({T[1], ..., T[n]}, {X[1], ..., X[n]}) = (Set(T[1], X[1]), ..., Set(T[n], X[n]))
- Set([T], [X[1], ..., X[n]]) = {Set(T, X[1]), ..., Set(T, X[n])}
- Set([T], []) = {}
When there is no risk of confusion, elements of Sets are identified with the sets they represent. For example, if U is the result of calling
union/2
with S1 and S2 as arguments, then U is said to be the union of S1 and S2. A more precise formulation is that Set(U) is the union of Set(S1) and Set(S2). -
The types are used to implement the various conditions that
sets must fulfill. As an example, consider the relative
product of two sets R and S, and recall that the relative
product of R and S is defined if R is a binary relation to Y and
S is a binary relation from Y. The function that implements the
relative product,
relative_product/2
, checks
that the arguments represent binary relations by matching [{A,B}]
against the type of the first argument (Arg1 say), and [{C,D}]
against the type of the second argument (Arg2 say). The fact
that [{A,B}] matches the type of Arg1 is to be interpreted as
Arg1 representing a binary relation from X to Y, where X is
defined as all sets Set(x) for some element x in Sets the type
of which is A, and similarly for Y. In the same way Arg2 is
interpreted as representing a binary relation from W to Z.
Finally it is checked that B matches C, which is sufficient to
ensure that W is equal to Y. The untyped empty set is handled
separately: its type, ['_'], matches the type of any unordered
set.
A few functions of this module
(drestriction/3
,
family_projection/2
,
partition/2
,
partition_family/2
,
projection/2
,
restriction/3
,
substitution/2
)
accept an Erlang
function as a means to modify each element of a given unordered
set. Such a function, called
SetFun in the following, can be specified as a functional object (fun),
a tuple {external, Fun}
, or an integer:
-
If SetFun is specified as a fun, the fun is applied to each element of the given set and the return value is assumed to be a set.
-
If SetFun is specified as a tuple
{external, Fun}
, Fun is applied to the external set of each element of the given set and the return value is assumed to be an external set. Selecting the elements of an unordered set as external sets and assembling a new unordered set from a list of external sets is in the present implementation more efficient than modifying each element as a set. However, this optimization can only be used when the elements of the unordered set are atomic or ordered sets. It must also be the case that the type of the elements matches some clause of Fun (the type of the created set is the result of applying Fun to the type of the given set), and that Fun does nothing but selecting, duplicating, or rearranging parts of the elements. -
Specifying a SetFun as an integer I is equivalent to specifying
{external, fun(X) -> element(I, X) end}
, but is to be preferred, as it makes it possible to handle this case even more efficiently.
Examples of SetFuns:
fun sofs:union/1 fun(S) -> sofs:partition(1, S) end {external, fun(A) -> A end} {external, fun({A,_,C}) -> {C,A} end} {external, fun({_,{_,C}}) -> C end} {external, fun({_,{_,{_,E}=C}}) -> {E,{E,C}} end} 2
The order in which a SetFun is applied to the elements of an unordered set is not specified, and can change in future versions of this module.
The execution time of the functions of this module is dominated
by the time it takes to sort lists. When no sorting is needed,
the execution time is in the worst case proportional to the sum
of the sizes of the input arguments and the returned value. A
few functions execute in constant time:
from_external/2
,
is_empty_set/1
,
is_set/1
,
is_sofs_set/1
,
to_external/1
type/1
.
The functions of this module exit the process with a
badarg
, bad_function
, or type_mismatch
message when given badly formed arguments or sets the types of
which are not compatible.
When comparing external sets, operator ==/2
is used.
Types
binary_relation() = relation()
external_set() = term()
An external set.
family() = a_function()
A family (of subsets).
a_function() = relation()
A function.
ordset()
An ordered set.
relation() = a_set()
An n-ary relation.
a_set()
An unordered set.
set_of_sets() = a_set()
An unordered set of unordered sets.
set_fun() =
integer() >= 1 |
{external, fun((external_set()) -> external_set())} |
fun((anyset()) -> anyset())
A SetFun.
spec_fun() =
{external, fun((external_set()) -> boolean())} |
fun((anyset()) -> boolean())
type() = term()
A type.
tuple_of(T)
A tuple where the elements are of type T
.
Functions
a_function(Tuples) -> Function
Function = a_function()
Tuples = [tuple()]
a_function(Tuples, Type) -> Function
Function = a_function()
Tuples = [tuple()]
Type = type()
canonical_relation(SetOfSets) -> BinRel
BinRel = binary_relation()
SetOfSets = set_of_sets()
Returns the binary relation containing the elements
(E, Set) such that Set belongs to
and E belongs to Set. If SetOfSets
is
a partition of a set X and
R is the equivalence relation in X induced by SetOfSets
,
then the returned relation is
the canonical map from
X onto the equivalence classes with respect to R.
1>Ss = sofs:from_term([[a,b],[b,c]]),
CR = sofs:canonical_relation(Ss),
sofs:to_external(CR).
[{a,[a,b]},{b,[a,b]},{b,[b,c]},{c,[b,c]}]
composite(Function1, Function2) -> Function3
Function1 = Function2 = Function3 = a_function()
Returns the composite of
the functions
and
.
1>F1 = sofs:a_function([{a,1},{b,2},{c,2}]),
F2 = sofs:a_function([{1,x},{2,y},{3,z}]),
F = sofs:composite(F1, F2),
sofs:to_external(F).
[{a,x},{b,y},{c,y}]
constant_function(Set, AnySet) -> Function
AnySet = anyset()
Function = a_function()
Set = a_set()
Creates the function
that maps each element of set Set
onto AnySet
.
1>S = sofs:set([a,b]),
E = sofs:from_term(1),
R = sofs:constant_function(S, E),
sofs:to_external(R).
[{a,1},{b,1}]
converse(BinRel1) -> BinRel2
BinRel1 = BinRel2 = binary_relation()
Returns the converse
of the binary relation
.
1>R1 = sofs:relation([{1,a},{2,b},{3,a}]),
R2 = sofs:converse(R1),
sofs:to_external(R2).
[{a,1},{a,3},{b,2}]
difference(Set1, Set2) -> Set3
Set1 = Set2 = Set3 = a_set()
Returns the difference of
the sets
and
.
digraph_to_family(Graph) -> Family
Graph = digraph:graph()
Family = family()
digraph_to_family(Graph, Type) -> Family
Graph = digraph:graph()
Family = family()
Type = type()
Creates a family from
the directed graph
. Each vertex a of
is
represented by a pair (a, {b[1], ..., b[n]}),
where the b[i]:s are the out-neighbors of a. If no type is
explicitly specified, [{atom, [atom]}] is used as type of
the family. It is assumed that
is
a valid type of the
external set of the family.
If G is a directed graph, it holds that the vertices and
edges of G are the same as the vertices and edges of
family_to_digraph(digraph_to_family(G))
.
domain(BinRel) -> Set
BinRel = binary_relation()
Set = a_set()
Returns the domain of
the binary relation
.
1>R = sofs:relation([{1,a},{1,b},{2,b},{2,c}]),
S = sofs:domain(R),
sofs:to_external(S).
[1,2]
drestriction(BinRel1, Set) -> BinRel2
BinRel1 = BinRel2 = binary_relation()
Set = a_set()
Returns the difference between the binary relation
and the restriction
of
to
.
1>R1 = sofs:relation([{1,a},{2,b},{3,c}]),
S = sofs:set([2,4,6]),
R2 = sofs:drestriction(R1, S),
sofs:to_external(R2).
[{1,a},{3,c}]
drestriction(R, S)
is equivalent to
difference(R, restriction(R, S))
.
drestriction(SetFun, Set1, Set2) -> Set3
Returns a subset of
containing those
elements that do not give
an element in
as the result of applying
.
1>SetFun = {external, fun({_A,B,C}) -> {B,C} end},
R1 = sofs:relation([{a,aa,1},{b,bb,2},{c,cc,3}]),
R2 = sofs:relation([{bb,2},{cc,3},{dd,4}]),
R3 = sofs:drestriction(SetFun, R1, R2),
sofs:to_external(R3).
[{a,aa,1}]
drestriction(F, S1, S2)
is equivalent to
difference(S1, restriction(F, S1, S2))
.
empty_set() -> Set
Set = a_set()
Returns the untyped empty
set. empty_set()
is equivalent to
from_term([], ['_'])
.
extension(BinRel1, Set, AnySet) -> BinRel2
AnySet = anyset()
BinRel1 = BinRel2 = binary_relation()
Set = a_set()
Returns the extension of
such that for
each element E in
that does not belong to the
domain of
,
contains the
pair (E, AnySet
).
1>S = sofs:set([b,c]),
A = sofs:empty_set(),
R = sofs:family([{a,[1,2]},{b,[3]}]),
X = sofs:extension(R, S, A),
sofs:to_external(X).
[{a,[1,2]},{b,[3]},{c,[]}]
family(Tuples) -> Family
Family = family()
Tuples = [tuple()]
family(Tuples, Type) -> Family
Creates a family of subsets.
family(F, T)
is equivalent to
from_term(F, T)
if the result is a family. If
no type is explicitly
specified, [{atom, [atom]}]
is used as the
family type.
family_difference(Family1, Family2) -> Family3
Family1 = Family2 = Family3 = family()
If
and
are families, then
is the family
such that the index set is equal to the index set of
, and
[i] is
the difference between
[i]
and
[i] if
maps i, otherwise
.
1>F1 = sofs:family([{a,[1,2]},{b,[3,4]}]),
F2 = sofs:family([{b,[4,5]},{c,[6,7]}]),
F3 = sofs:family_difference(F1, F2),
sofs:to_external(F3).
[{a,[1,2]},{b,[3]}]
family_domain(Family1) -> Family2
Family1 = Family2 = family()
If
is
a family
and
[i] is a binary relation for every i
in the index set of
,
then
is the family with the same index
set as
such
that
[i] is
the domain of
.
1>FR = sofs:from_term([{a,[{1,a},{2,b},{3,c}]},{b,[]},{c,[{4,d},{5,e}]}]),
F = sofs:family_domain(FR),
sofs:to_external(F).
[{a,[1,2,3]},{b,[]},{c,[4,5]}]
family_field(Family1) -> Family2
Family1 = Family2 = family()
If
is
a family
and
[i] is a binary relation for every i
in the index set of
,
then
is the family with the same index
set as
such
that
[i] is
the field of
[i].
1>FR = sofs:from_term([{a,[{1,a},{2,b},{3,c}]},{b,[]},{c,[{4,d},{5,e}]}]),
F = sofs:family_field(FR),
sofs:to_external(F).
[{a,[1,2,3,a,b,c]},{b,[]},{c,[4,5,d,e]}]
family_field(Family1)
is equivalent to
family_union(family_domain(Family1),
family_range(Family1))
.
family_intersection(Family1) -> Family2
Family1 = Family2 = family()
If
is
a family
and
[i] is a set of sets for every i in
the index set of
,
then
is the family with the same index
set as
such
that
[i] is
the intersection
of
[i].
If
[i] is an empty set for some i,
the process exits with a badarg
message.
1>F1 = sofs:from_term([{a,[[1,2,3],[2,3,4]]},{b,[[x,y,z],[x,y]]}]),
F2 = sofs:family_intersection(F1),
sofs:to_external(F2).
[{a,[2,3]},{b,[x,y]}]
family_intersection(Family1, Family2) -> Family3
Family1 = Family2 = Family3 = family()
If
and
are families,
then
is the family such that the index
set is the intersection of
:s and
:s index sets,
and
[i] is the intersection of
[i] and
[i].
1>F1 = sofs:family([{a,[1,2]},{b,[3,4]},{c,[5,6]}]),
F2 = sofs:family([{b,[4,5]},{c,[7,8]},{d,[9,10]}]),
F3 = sofs:family_intersection(F1, F2),
sofs:to_external(F3).
[{b,[4]},{c,[]}]
family_projection(SetFun, Family1) -> Family2
If
is
a family,
then
is the family with the same index
set as
such
that
[i] is the result of
calling
with
[i]
as argument.
1>F1 = sofs:from_term([{a,[[1,2],[2,3]]},{b,[[]]}]),
F2 = sofs:family_projection(fun sofs:union/1, F1),
sofs:to_external(F2).
[{a,[1,2,3]},{b,[]}]
family_range(Family1) -> Family2
Family1 = Family2 = family()
If
is
a family
and
[i] is a binary relation for every i
in the index set of
,
then
is the family with the same index
set as
such
that
[i] is
the range of
[i].
1>FR = sofs:from_term([{a,[{1,a},{2,b},{3,c}]},{b,[]},{c,[{4,d},{5,e}]}]),
F = sofs:family_range(FR),
sofs:to_external(F).
[{a,[a,b,c]},{b,[]},{c,[d,e]}]
family_specification(Fun, Family1) -> Family2
Fun = spec_fun()
Family1 = Family2 = family()
If
is
a family,
then
is
the restriction of
to those elements i of the index set
for which
applied
to
[i] returns
true
. If
is a
tuple {external, Fun2}
, then Fun2
is applied to
the external set
of
[i], otherwise
is applied to
[i].
1>F1 = sofs:family([{a,[1,2,3]},{b,[1,2]},{c,[1]}]),
SpecFun = fun(S) -> sofs:no_elements(S) =:= 2 end,
F2 = sofs:family_specification(SpecFun, F1),
sofs:to_external(F2).
[{b,[1,2]}]
family_to_digraph(Family) -> Graph
Graph = digraph:graph()
Family = family()
family_to_digraph(Family, GraphType) -> Graph
Graph = digraph:graph()
Family = family()
GraphType = [digraph:d_type()]
Creates a directed graph from
family
.
For each pair (a, {b[1], ..., b[n]})
of
, vertex
a and the edges (a, b[i]) for
1 <= i <= n are added to a newly
created directed graph.
If no graph type is specified,
digraph:new/0
is used for
creating the directed graph, otherwise argument
is passed on as second argument to
digraph:new/1
.
It F is a family, it holds that F is a subset of
digraph_to_family(family_to_digraph(F), type(F))
.
Equality holds if union_of_family(F)
is a subset of
domain(F)
.
Creating a cycle in an acyclic graph exits the process with
a cyclic
message.
family_to_relation(Family) -> BinRel
Family = family()
BinRel = binary_relation()
If
is
a family,
then
is the binary relation containing
all pairs (i, x) such that i belongs to the index set
of
and x belongs
to
[i].
1>F = sofs:family([{a,[]}, {b,[1]}, {c,[2,3]}]),
R = sofs:family_to_relation(F),
sofs:to_external(R).
[{b,1},{c,2},{c,3}]
family_union(Family1) -> Family2
Family1 = Family2 = family()
If
is
a family
and
[i] is a set of sets for each i in
the index set of
,
then
is the family with the same index
set as
such
that
[i] is
the union of
[i].
1>F1 = sofs:from_term([{a,[[1,2],[2,3]]},{b,[[]]}]),
F2 = sofs:family_union(F1),
sofs:to_external(F2).
[{a,[1,2,3]},{b,[]}]
family_union(F)
is equivalent to
family_projection(fun sofs:union/1, F)
.
family_union(Family1, Family2) -> Family3
Family1 = Family2 = Family3 = family()
If
and
are families,
then
is the family such that the index
set is the union of
:s
and
:s index sets,
and
[i] is the union
of
[i] and
[i]
if both map i, otherwise
[i]
or
[i].
1>F1 = sofs:family([{a,[1,2]},{b,[3,4]},{c,[5,6]}]),
F2 = sofs:family([{b,[4,5]},{c,[7,8]},{d,[9,10]}]),
F3 = sofs:family_union(F1, F2),
sofs:to_external(F3).
[{a,[1,2]},{b,[3,4,5]},{c,[5,6,7,8]},{d,[9,10]}]
field(BinRel) -> Set
BinRel = binary_relation()
Set = a_set()
Returns the field of the
binary relation
.
1>R = sofs:relation([{1,a},{1,b},{2,b},{2,c}]),
S = sofs:field(R),
sofs:to_external(S).
[1,2,a,b,c]
field(R)
is equivalent
to union(domain(R), range(R))
.
from_external(ExternalSet, Type) -> AnySet
ExternalSet = external_set()
AnySet = anyset()
Type = type()
Creates a set from the external
set
and
the type
.
It is assumed that
is
a valid
type of
.
Returns the unordered
set containing the sets of list
.
1>S1 = sofs:relation([{a,1},{b,2}]),
S2 = sofs:relation([{x,3},{y,4}]),
S = sofs:from_sets([S1,S2]),
sofs:to_external(S).
[[{a,1},{b,2}],[{x,3},{y,4}]]
Returns the ordered
set containing the sets of the non-empty tuple
.
from_term(Term) -> AnySet
AnySet = anyset()
Term = term()
from_term(Term, Type) -> AnySet
Creates an element
of Sets by
traversing term
, sorting lists,
removing duplicates, and
deriving or verifying a valid
type for the so obtained external set. An
explicitly specified type
can be used to limit the depth of the traversal; an atomic
type stops the traversal, as shown by the following example
where "foo"
and {"foo"}
are left unmodified:
1>S = sofs:from_term([{{"foo"},[1,1]},{"foo",[2,2]}], [{atom,[atom]}]),
sofs:to_external(S).
[{{"foo"},[1]},{"foo",[2]}]
from_term
can be used for creating atomic or ordered
sets. The only purpose of such a set is that of later
building unordered sets, as all functions in this module
that do anything operate on unordered sets.
Creating unordered sets from a collection of ordered sets
can be the way to go if the ordered sets are big and one
does not want to waste heap by rebuilding the elements of
the unordered set. The following example shows that a set can be
built "layer by layer":
1>A = sofs:from_term(a),
S = sofs:set([1,2,3]),
P1 = sofs:from_sets({A,S}),
P2 = sofs:from_term({b,[6,5,4]}),
Ss = sofs:from_sets([P1,P2]),
sofs:to_external(Ss).
[{a,[1,2,3]},{b,[4,5,6]}]
Other functions that create sets are
from_external/2
and from_sets/1
.
Special cases of from_term/2
are
a_function/1,2
,
empty_set/0
,
family/1,2
,
relation/1,2
, and
set/1,2
.
image(BinRel, Set1) -> Set2
BinRel = binary_relation()
Set1 = Set2 = a_set()
Returns the image of
set
under the binary
relation
.
1>R = sofs:relation([{1,a},{2,b},{2,c},{3,d}]),
S1 = sofs:set([1,2]),
S2 = sofs:image(R, S1),
sofs:to_external(S2).
[a,b,c]
intersection(SetOfSets) -> Set
Set = a_set()
SetOfSets = set_of_sets()
Returns
the intersection of
the set of sets
.
Intersecting an empty set of sets exits the process with a
badarg
message.
intersection(Set1, Set2) -> Set3
Set1 = Set2 = Set3 = a_set()
Returns
the intersection of
and
.
intersection_of_family(Family) -> Set
Returns the intersection of
family
.
Intersecting an empty family exits the process with a
badarg
message.
1>F = sofs:family([{a,[0,2,4]},{b,[0,1,2]},{c,[2,3]}]),
S = sofs:intersection_of_family(F),
sofs:to_external(S).
[2]
inverse(Function1) -> Function2
Function1 = Function2 = a_function()
Returns the inverse
of function
.
1>R1 = sofs:relation([{1,a},{2,b},{3,c}]),
R2 = sofs:inverse(R1),
sofs:to_external(R2).
[{a,1},{b,2},{c,3}]
inverse_image(BinRel, Set1) -> Set2
BinRel = binary_relation()
Set1 = Set2 = a_set()
Returns the inverse
image of
under the binary
relation
.
1>R = sofs:relation([{1,a},{2,b},{2,c},{3,d}]),
S1 = sofs:set([c,d,e]),
S2 = sofs:inverse_image(R, S1),
sofs:to_external(S2).
[2,3]
is_a_function(BinRel) -> Bool
Bool = boolean()
BinRel = binary_relation()
Returns true
if the binary relation
is a function or the
untyped empty set, otherwise false
.
is_disjoint(Set1, Set2) -> Bool
Bool = boolean()
Set1 = Set2 = a_set()
Returns true
if
and
are disjoint, otherwise
false
.
is_empty_set(AnySet) -> Bool
AnySet = anyset()
Bool = boolean()
Returns true
if
is an empty
unordered set, otherwise false
.
is_equal(AnySet1, AnySet2) -> Bool
AnySet1 = AnySet2 = anyset()
Bool = boolean()
Returns true
if
and
are equal, otherwise
false
. The following example shows that ==/2
is
used when comparing sets for equality:
1>S1 = sofs:set([1.0]),
S2 = sofs:set([1]),
sofs:is_equal(S1, S2).
true
is_set(AnySet) -> Bool
AnySet = anyset()
Bool = boolean()
Returns true
if
is
an unordered set, and
false
if
is an ordered set or an
atomic set.
is_sofs_set(Term) -> Bool
Bool = boolean()
Term = term()
Returns true
if
is
an unordered set, an
ordered set, or an atomic set, otherwise false
.
is_subset(Set1, Set2) -> Bool
Bool = boolean()
Set1 = Set2 = a_set()
Returns true
if
is
a subset
of
, otherwise false
.
join(Relation1, I, Relation2, J) -> Relation3
Relation1 = Relation2 = Relation3 = relation()
I = J = integer() >= 1
Returns the natural
join of the relations
and
on coordinates
and
.
1>R1 = sofs:relation([{a,x,1},{b,y,2}]),
R2 = sofs:relation([{1,f,g},{1,h,i},{2,3,4}]),
J = sofs:join(R1, 3, R2, 1),
sofs:to_external(J).
[{a,x,1,f,g},{a,x,1,h,i},{b,y,2,3,4}]
multiple_relative_product(TupleOfBinRels, BinRel1) -> BinRel2
TupleOfBinRels = tuple_of(BinRel)
BinRel = BinRel1 = BinRel2 = binary_relation()
If
is a non-empty tuple
{R[1], ..., R[n]} of binary relations
and
is a binary relation,
then
is
the multiple relative
product of the ordered set
(R[i], ..., R[n]) and
.
1>Ri = sofs:relation([{a,1},{b,2},{c,3}]),
R = sofs:relation([{a,b},{b,c},{c,a}]),
MP = sofs:multiple_relative_product({Ri, Ri}, R),
sofs:to_external(sofs:range(MP)).
[{1,2},{2,3},{3,1}]
no_elements(ASet) -> NoElements
Returns the number of elements of the ordered or unordered
set
.
partition(SetOfSets) -> Partition
SetOfSets = set_of_sets()
Partition = a_set()
Returns the partition of
the union of the set of sets
such that
two elements are considered equal if they belong to the same
elements of
.
1>Sets1 = sofs:from_term([[a,b,c],[d,e,f],[g,h,i]]),
Sets2 = sofs:from_term([[b,c,d],[e,f,g],[h,i,j]]),
P = sofs:partition(sofs:union(Sets1, Sets2)),
sofs:to_external(P).
[[a],[b,c],[d],[e,f],[g],[h,i],[j]]
partition(SetFun, Set) -> Partition
Returns the partition of
such that two elements are considered equal
if the results of applying
are equal.
1>Ss = sofs:from_term([[a],[b],[c,d],[e,f]]),
SetFun = fun(S) -> sofs:from_term(sofs:no_elements(S)) end,
P = sofs:partition(SetFun, Ss),
sofs:to_external(P).
[[[a],[b]],[[c,d],[e,f]]]
partition(SetFun, Set1, Set2) -> {Set3, Set4}
Returns a pair of sets that, regarded as constituting a
set, forms a partition of
. If the
result of applying
to an element of
gives an element in
,
the element belongs to
, otherwise the
element belongs to
.
1>R1 = sofs:relation([{1,a},{2,b},{3,c}]),
S = sofs:set([2,4,6]),
{R2,R3} = sofs:partition(1, R1, S),
{sofs:to_external(R2),sofs:to_external(R3)}.
{[{2,b}],[{1,a},{3,c}]}
partition(F, S1, S2)
is equivalent to
{restriction(F, S1, S2),
drestriction(F, S1, S2)}
.
partition_family(SetFun, Set) -> Family
Returns family
where the indexed set is
a partition
of
such that two elements are considered
equal if the results of applying
are the
same value i. This i is the index that
maps onto the equivalence
class.
1>S = sofs:relation([{a,a,a,a},{a,a,b,b},{a,b,b,b}]),
SetFun = {external, fun({A,_,C,_}) -> {A,C} end},
F = sofs:partition_family(SetFun, S),
sofs:to_external(F).
[{{a,a},[{a,a,a,a}]},{{a,b},[{a,a,b,b},{a,b,b,b}]}]
product(TupleOfSets) -> Relation
Relation = relation()
TupleOfSets = tuple_of(a_set())
Returns the Cartesian
product of the non-empty tuple of sets
. If (x[1], ..., x[n]) is
an element of the n-ary relation
, then
x[i] is drawn from element i of
.
1>S1 = sofs:set([a,b]),
S2 = sofs:set([1,2]),
S3 = sofs:set([x,y]),
P3 = sofs:product({S1,S2,S3}),
sofs:to_external(P3).
[{a,1,x},{a,1,y},{a,2,x},{a,2,y},{b,1,x},{b,1,y},{b,2,x},{b,2,y}]
product(Set1, Set2) -> BinRel
BinRel = binary_relation()
Set1 = Set2 = a_set()
Returns the Cartesian
product of
and
.
1>S1 = sofs:set([1,2]),
S2 = sofs:set([a,b]),
R = sofs:product(S1, S2),
sofs:to_external(R).
[{1,a},{1,b},{2,a},{2,b}]
product(S1, S2)
is equivalent to
product({S1, S2})
.
projection(SetFun, Set1) -> Set2
Returns the set created by substituting each element of
by the result of
applying
to the element.
If
is a number i >= 1 and
is a relation, then the returned set is
the projection of
onto coordinate i.
1>S1 = sofs:from_term([{1,a},{2,b},{3,a}]),
S2 = sofs:projection(2, S1),
sofs:to_external(S2).
[a,b]
range(BinRel) -> Set
BinRel = binary_relation()
Set = a_set()
Returns the range of the
binary relation
.
1>R = sofs:relation([{1,a},{1,b},{2,b},{2,c}]),
S = sofs:range(R),
sofs:to_external(S).
[a,b,c]
relation(Tuples) -> Relation
Relation = relation()
Tuples = [tuple()]
relation(Tuples, Type) -> Relation
N = integer()
Type = N | type()
Relation = relation()
Tuples = [tuple()]
Creates a relation.
relation(R, T)
is equivalent to
from_term(R, T)
, if T is
a type and the result is a
relation. If
is an integer N, then
[{atom, ..., atom}])
, where the tuple size
is N, is used as type of the relation. If no type is
explicitly specified, the size of the first tuple of
is
used if there is such a tuple. relation([])
is
equivalent to relation([], 2)
.
relation_to_family(BinRel) -> Family
Family = family()
BinRel = binary_relation()
relative_product(ListOfBinRels) -> BinRel2
ListOfBinRels = [BinRel, ...]
BinRel = BinRel2 = binary_relation()
If
is a non-empty list
[R[1], ..., R[n]] of binary relations and
is a binary relation, then
is the
relative product
of the ordered set (R[i], ..., R[n]) and
.
If
is omitted, the relation of equality
between the elements of
the Cartesian
product of the ranges of R[i],
range R[1] × ... × range R[n],
is used instead (intuitively, nothing is "lost").
1>TR = sofs:relation([{1,a},{1,aa},{2,b}]),
R1 = sofs:relation([{1,u},{2,v},{3,c}]),
R2 = sofs:relative_product([TR, R1]),
sofs:to_external(R2).
[{1,{a,u}},{1,{aa,u}},{2,{b,v}}]
Notice that relative_product([R1], R2)
is
different from relative_product(R1, R2)
; the
list of one element is not identified with the element itself.
Returns the relative
product of the binary relations
and
.
relative_product1(BinRel1, BinRel2) -> BinRel3
BinRel1 = BinRel2 = BinRel3 = binary_relation()
Returns the relative
product of
the converse of the
binary relation
and the binary
relation
.
1>R1 = sofs:relation([{1,a},{1,aa},{2,b}]),
R2 = sofs:relation([{1,u},{2,v},{3,c}]),
R3 = sofs:relative_product1(R1, R2),
sofs:to_external(R3).
[{a,u},{aa,u},{b,v}]
relative_product1(R1, R2)
is equivalent to
relative_product(converse(R1), R2)
.
restriction(BinRel1, Set) -> BinRel2
BinRel1 = BinRel2 = binary_relation()
Set = a_set()
Returns the restriction of
the binary relation
to
.
1>R1 = sofs:relation([{1,a},{2,b},{3,c}]),
S = sofs:set([1,2,4]),
R2 = sofs:restriction(R1, S),
sofs:to_external(R2).
[{1,a},{2,b}]
restriction(SetFun, Set1, Set2) -> Set3
Returns a subset of
containing those
elements that gives an element in
as the
result of applying
.
1>S1 = sofs:relation([{1,a},{2,b},{3,c}]),
S2 = sofs:set([b,c,d]),
S3 = sofs:restriction(2, S1, S2),
sofs:to_external(S3).
[{2,b},{3,c}]
set(Terms) -> Set
Set = a_set()
Terms = [term()]
set(Terms, Type) -> Set
Creates an unordered
set. set(L, T)
is equivalent to
from_term(L, T)
, if the result is an unordered
set. If no type is
explicitly specified, [atom]
is used as the set type.
specification(Fun, Set1) -> Set2
Fun = spec_fun()
Set1 = Set2 = a_set()
Returns the set containing every element
of
for which
returns true
. If
is a tuple
{external, Fun2}
, Fun2
is applied to the
external set of
each element, otherwise
is applied to each
element.
1>R1 = sofs:relation([{a,1},{b,2}]),
R2 = sofs:relation([{x,1},{x,2},{y,3}]),
S1 = sofs:from_sets([R1,R2]),
S2 = sofs:specification(fun sofs:is_a_function/1, S1),
sofs:to_external(S2).
[[{a,1},{b,2}]]
strict_relation(BinRel1) -> BinRel2
BinRel1 = BinRel2 = binary_relation()
Returns the strict
relation corresponding to the binary
relation
.
1>R1 = sofs:relation([{1,1},{1,2},{2,1},{2,2}]),
R2 = sofs:strict_relation(R1),
sofs:to_external(R2).
[{1,2},{2,1}]
substitution(SetFun, Set1) -> Set2
Returns a function, the domain of which
is
. The value of an element of the domain
is the result of applying
to the
element.
1>L = [{a,1},{b,2}].
[{a,1},{b,2}] 2>sofs:to_external(sofs:projection(1,sofs:relation(L))).
[a,b] 3>sofs:to_external(sofs:substitution(1,sofs:relation(L))).
[{{a,1},a},{{b,2},b}] 4>SetFun = {external, fun({A,_}=E) -> {E,A} end},
sofs:to_external(sofs:projection(SetFun,sofs:relation(L))).
[{{a,1},a},{{b,2},b}]
The relation of equality between the elements of {a,b,c}:
1>I = sofs:substitution(fun(A) -> A end, sofs:set([a,b,c])),
sofs:to_external(I).
[{a,a},{b,b},{c,c}]
Let SetOfSets
be a set of sets and BinRel
a binary
relation. The function that maps each element Set
of
SetOfSets
onto the image
of Set
under BinRel
is returned by the following
function:
images(SetOfSets, BinRel) -> Fun = fun(Set) -> sofs:image(BinRel, Set) end, sofs:substitution(Fun, SetOfSets).
External unordered sets are represented as sorted lists. So,
creating the image of a set under a relation R can traverse all
elements of R (to that comes the sorting of results, the
image). In image/2
,
BinRel
is traversed once
for each element of SetOfSets
, which can take too long. The
following efficient function can be used instead under the
assumption that the image of each element of SetOfSets
under
BinRel
is non-empty:
images2(SetOfSets, BinRel) -> CR = sofs:canonical_relation(SetOfSets), R = sofs:relative_product1(CR, BinRel), sofs:relation_to_family(R).
symdiff(Set1, Set2) -> Set3
Set1 = Set2 = Set3 = a_set()
Returns the symmetric
difference (or the Boolean sum)
of
and
.
1>S1 = sofs:set([1,2,3]),
S2 = sofs:set([2,3,4]),
P = sofs:symdiff(S1, S2),
sofs:to_external(P).
[1,4]
symmetric_partition(Set1, Set2) -> {Set3, Set4, Set5}
Set1 = Set2 = Set3 = Set4 = Set5 = a_set()
Returns a triple of sets:
contains the elements ofSet3
that do not belong toSet1
.Set2
contains the elements ofSet4
that belong toSet1
.Set2
contains the elements ofSet5
that do not belong toSet2
.Set1
to_external(AnySet) -> ExternalSet
ExternalSet = external_set()
AnySet = anyset()
Returns the external set of an atomic, ordered, or unordered set.
to_sets(ASet) -> Sets
Returns the elements of the ordered set
as a tuple of sets, and the elements of the unordered set
as a sorted list of sets without
duplicates.
type(AnySet) -> Type
Returns the type of an atomic, ordered, or unordered set.
union(SetOfSets) -> Set
Set = a_set()
SetOfSets = set_of_sets()
Returns the union of the
set of sets
.
union_of_family(Family) -> Set
Returns the union of family
.
1>F = sofs:family([{a,[0,2,4]},{b,[0,1,2]},{c,[2,3]}]),
S = sofs:union_of_family(F),
sofs:to_external(S).
[0,1,2,3,4]
weak_relation(BinRel1) -> BinRel2
BinRel1 = BinRel2 = binary_relation()
Returns a subset S of the weak
relation W
corresponding to the binary relation
.
Let F be the field of
. The
subset S is defined so that x S y if x W y for some x in F
and for some y in F.
1>R1 = sofs:relation([{1,1},{1,2},{3,1}]),
R2 = sofs:weak_relation(R1),
sofs:to_external(R2).
[{1,1},{1,2},{2,2},{3,1},{3,3}]