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
Set B is a
The
The
Two sets are
The
The
The
The
The
A
The
The
The
If A is a subset of X, the
If R is a relation from X to Y, and S is a relation from Y to Z, the
The
If S is a restriction of R to A, then R is an
If X = Y, then R is called a relation in X.
The
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
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
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
The relative product of two functions F1 and F2 is called
the
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
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
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
If R is an equivalence relation in X, the
We call a set of ordered sets (x[1], ..., x[n]) an
The
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
The
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
A
If S is an element (T, X) of Sets, then T is a
The sets represented by Sets are the elements of the range of function Set from Sets to Erlang terms and sets of Erlang terms:
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
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,
A few functions of this module
(
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
Specifying a SetFun as an integer I is equivalent to
specifying
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:
The functions of this module exit the process with a
When comparing external sets, operator
Any kind of set (also included are the atomic sets).
A
An
A
A
An
An
An
An
A
A
A tuple where the elements are of type
Creates a
Returns the binary relation containing the elements
(E, Set) such that Set belongs to
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]}]
Returns the
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}]
Creates the
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}]
Returns the
1> R1 = sofs:relation([{1,a},{2,b},{3,a}]), R2 = sofs:converse(R1), sofs:to_external(R2). [{a,1},{a,3},{b,2}]
Returns the
Creates a
If G is a directed graph, it holds that the vertices and
edges of G are the same as the vertices and edges of
Returns the
1> R = sofs:relation([{1,a},{1,b},{2,b},{2,c}]), S = sofs:domain(R), sofs:to_external(S). [1,2]
Returns the difference between the binary relation
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}]
Returns a subset of
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}]
Returns the
Returns the
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,[]}]
Creates a
If
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]}]
If
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]}]
If
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]}]
If
If
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]}]
If
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,[]}]
If
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,[]}]
If
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]}]
If
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]}]
Creates a directed graph from
If no graph type is specified,
It F is a family, it holds that F is a subset of
Creating a cycle in an acyclic graph exits the process with
a
If
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}]
If
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,[]}]
If
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]}]
Returns the
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]
Creates a set from the
Returns the
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
1> S = sofs:from_term([{{"foo"},[1,1]},{"foo",[2,2]}], [{atom,[atom]}]), sofs:to_external(S). [{{"foo"},[1]},{"foo",[2]}]
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
Returns the
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]
Returns
the
Intersecting an empty set of sets exits the process with a
Returns
the
Returns the intersection of
Intersecting an empty family exits the process with a
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]
Returns the
1> R1 = sofs:relation([{1,a},{2,b},{3,c}]), R2 = sofs:inverse(R1), sofs:to_external(R2). [{a,1},{b,2},{c,3}]
Returns the
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]
Returns
Returns
Returns
Returns
1> S1 = sofs:set([1.0]), S2 = sofs:set([1]), sofs:is_equal(S1, S2). true
Returns
Returns
Returns
Returns
Returns the
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}]
If
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}]
Returns the number of elements of the ordered or unordered
set
Returns the
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]]
Returns the
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]]]
Returns a pair of sets that, regarded as constituting a
set, forms a
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}]}
Returns
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}]}]
Returns the
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}]
Returns the
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}]
Returns the set created by substituting each element of
If
1> S1 = sofs:from_term([{1,a},{2,b},{3,a}]), S2 = sofs:projection(2, S1), sofs:to_external(S2). [a,b]
Returns the
1> R = sofs:relation([{1,a},{1,b},{2,b},{2,c}]), S = sofs:range(R), sofs:to_external(S). [a,b,c]
Creates a
Returns
1> R = sofs:relation([{b,1},{c,2},{c,3}]), F = sofs:relation_to_family(R), sofs:to_external(F). [{b,[1]},{c,[2,3]}]
If
If
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
Returns the
Returns the
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}]
Returns the
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}]
Returns a subset of
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}]
Creates an
Returns the set containing every element
of
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}]]
Returns the
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}]
Returns a function, the domain of which
is
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
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
images2(SetOfSets, BinRel) -> CR = sofs:canonical_relation(SetOfSets), R = sofs:relative_product1(CR, BinRel), sofs:relation_to_family(R).
Returns the
1> S1 = sofs:set([1,2,3]), S2 = sofs:set([2,3,4]), P = sofs:symdiff(S1, S2), sofs:to_external(P). [1,4]
Returns a triple of sets:
Returns the
Returns the elements of the ordered set
Returns the
Returns the
Returns the
Returns the union of
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]
Returns a subset S of the
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}]