How to call a relation raised to a function

For a list [x-a, x-b, y-c] of pairs which allows multiple keys, does the dict like list [x-[a,b], y-[c]] have a standard name ? More general, for a binary relation R how the derived function F_R is called, where F_R(x) = \{y \mid R(x,y)\}. I found no name for such raised function from a relation in the literature of mathematics or programming. F_R appears often in
my programming and feel like a friend. I would like to know its name. Thanks for proposed name in advance.

1 Like

When working with graphs they are called Adjacency list

The SWI-Prolog library ugraphs works with such graphs.

I donā€™t know of a similar name in the area of binary relations or functions, my math terminology is more limited than my computer terminology.


Welcome to SWI-Prolog (threaded, 64 bits, version 8.5.13)
...

?- use_module(library(ugraphs)).
true.

?- vertices_edges_to_ugraph([],[x-a,x-b,y-c],UGraph).
UGraph = [a-[], b-[], c-[], x-[a, b], y-[c]].

Thanks for a reasonable answer. I remember that I also used the name successors list on directed graphs. The binary relation R was for that between so called types and tokens, not graph theoretical one but something supporting relation. ā€œSupporters listā€ sounds to fit your suggestion. Thanks.

In the database and data analysis worlds, the operation is usually called ā€œgroupingā€ or ā€œgroupbyā€. I did a bit of searching, but there doesnā€™t seem to be a term for the grouped list, other than ā€œgrouped listā€ or ā€œgrouped itemsā€. Another possible term: ā€œhierarchical listā€. E.g. pandas.DataFrame.groupby ā€” pandas 1.4.3 documentation and GROUP BY (Transact-SQL) - SQL Server | Microsoft Docs

See also library(solution_sequences)

ā€œGroupingā€ sounds more close to my intuition. In fact,
I am wondering what is more appropriate name for the following predicates, which is a bidirectional predicate
to convert a relation to the equivalent function which takes values from the powerset of the range of given relation. ā€œpfnā€ there indicates set valued function. Now gfn sounds better than pfn. For those like me who are not so good at English, naming predicates is often more difficult than prolog programming and takes rather time longer than coding.

% ?- rel_to_pfn([1-a, 1-b, 2-b],R).
% ?- rel_to_pfn([1-a, 1-b, 2-b],R), ifmap:rel_to_pfn(S, R).

rel_to_pfn(X, Y):-
	(	var(X) -> pfn_to_rel(Y, X)
	;	rel_to_pfn(X, Y, [])
	).

%
rel_to_pfn([], Y, Y).
rel_to_pfn([A-B|R], [A-[B|P]|Y], Z):-
	rel_to_pfn(R, A, R0, P, []),
	rel_to_pfn(R0, Y, Z).
%
rel_to_pfn([], _, [], P, P).
rel_to_pfn([A-B|R], A, U, [B|P], Q):-!,
	rel_to_pfn(R, A, U, P, Q).
rel_to_pfn(R, _, R, P, P).

%%	pfn_to_rel(+X:fn, -Y:rel) is det.
%	Y is a relation version of X, i.e.,
%   b in X(a)  <==> Y(a, b).
%   Property;  if X is sorded  then so is Y.

% ?- rel_to_pfn([a-b, a-c, b-d], X), ifmap:pfn_to_rel(X, Y).

pfn_to_rel(X, Y):- pfn_to_rel(X, Y0, []),
				   keysort(Y0, Y).


pfn_to_rel([], Y, Y).
pfn_to_rel([U-L|X], Y, Z):-
	pfn_to_rel(L, U, Y, Y0),
	pfn_to_rel(X, Y0, Z).
%
pfn_to_rel([], _, Z, Z).
pfn_to_rel([V|Vs], U, [U-V|Y], Z):-
	pfn_to_rel(Vs, U, Y, Z).

(directed) Hypergraph??? Hypergraph - Wikipedia

Wikipedia first example image would be:

[ e1-[v1,e2],e2-[v2,v3],e3-[v5,v6,v3],e4-[v4],universe-[e4,e3,e1,v7] ]

If a graph [a-[b,c]] is translated to a hypergraph [[a, b, c]], then b and c get connected by the hyperedge [a, b, c], though they are not connected by any edge of the original graph. What is wrong with this translation ?

Edit (24 hours later): This is propably my own weird idea because I could not find any paper or page to support this. You regular commentators here at this Discource forum you know much more than I, I admit that I am not an expert.

ā€˜aā€™ is the name of a hypergraph edge, it is a directed hypergraph, so vertex ā€˜bā€™ and vertex ā€˜cā€™ are not connected to each other.
kuva

Well ā€¦ this is an interesting subject, is it even possible to draw hypergraph using arrow-lines, here is a paper that has Venn image and an hypergraph drawn as lines. https://www.researchgate.net/figure/The-hypergraph-in-Figure-1-as-a-binary-relation_fig1_220801486

As far as I know, muti-valued function is different from set-valued function. For example, log is thought as a multi-valued function, not a set-valued function, and mathematician makes it a function by building appropriate covering spaces on which log becomes a function. Anyway thank you for comment. I will consult
to hypergraph if necessary in the future. For now its seems too much for my simple minded purpose.

If a is a hyperedge, then a = \{b, c\}, I think, which implies nodes b and c are connected by a, isnā€™t it ?

If it is a directed hypergraph then you canā€™t traverse from b to c. You can traverse from a to b and a to c

A parent node seems to have a role of hyperlink. If this is correct, I feel I understand the point.

1 Like

I hope this is correct.

A directed graph given in successors list style [a-[x,y], b-[z,u]] is translated to a directed hypergraph { {a} -> {x, y} , {b} -> {z, u} }.

Also a directed graph [a-[x,y], b-[x,y]] is translated to a directed hypergraph { {a} -> {x, y}, {b} -> {x, y} }. But for this case, Iā€™m not sure. It may be translated to { {a,b} -> {x, y} }, though I think the latter is another story.

Am I missing something about basics of directed hypergraph ?

Is a relation a multi-valued function ? AFAIK, itā€™s not, but related.

Thanks for lectures. In fact currification was one of the candidates of naming. But now I prefer ā€œtokens listā€ because of prolog-like neutral sound. (Thanks peter.ludemann)

Findall, bagof, setof are blackboxes for me as an average prologer, and that currifying predicate is most busy one in that application. So I would like to keep my codes.

Below I ran a benchmark. The time statistics showed
as I expected that my codes is 1000 times faster than that uses findall and bagof, though the benchmark is not fair. And I could not find a way to resolve the unfair point.

rel_pfn_by_findall(X, Y):- 
     findall(A-L, (member(A-_, X), bagof(U, member(A-U, X), L)), Y0),
     sort(Y0, Y).

% ?- N = 1000,  findall(I-I, between(1, N, I), Zip),
%	time(repeat(1000, rel_pfn_by_findall(Zip, R))).
%@ % 1,016,015,001 inferences, 79.852 CPU in 80.332 seconds (99% CPU, 12723746 Lips)
%@ N = 1000,
%@ Zip = [1-1, 2-2, 3-3, 4-4, 5-5, 6-6, 7-7, 8-8, ... - ...|...].
% ?- N = 1000,  findall(I-I, between(1, N, I), Zip),
%	time(repeat(1000, rel_pfn(Zip, R))).
%@ % 2,006,001 inferences, 0.162 CPU in 0.162 seconds (100% CPU, 12371954 Lips)
%@ N = 1000,
%@ Zip = [1-1, 2-2, 3-3, 4-4, 5-5, 6-6, 7-7, 8-8, ... - ...|...].

Thats wrong usage of bagof/3. You call member/2 two times in your
code. Its enough to have only one occurence of member/2, like
here there is only one occurence of the predicate p/2:

You also can use bagof/3, with only one occurence of member/2:

?- R = [a-1,b-2,a-3], findall(X-Z, bagof(Y, member(X-Y,R), Z), L).
R = [a-1, b-2, a-3],
L = [a-[1, 3], b-[2]].

If you do measurement now, its probably faster.

Also there is a bug in your rel_to_pfn/3, I get:

?- R = [a-1,b-2,a-3], rel_to_pfn(R, L, []).
R = [a-1, b-2, a-3],
L = [a-[1], b-[2], a-[3]] 

But I expected rather L = [a-[1,3], b-[2]].

Was using this code:

Whats the error?

Edit 05.07.2022:
I think you can fix the error, by changing the last clause into:

rel_to_pfn([H|R], A, [H|U], P, Q) :-
     rel_to_pfn(R, A, U, P, Q).

Now it wurks:

?- R = [a-1,b-2,a-3], rel_to_pfn(R, L, []).
R = [a-1, b-2, a-3],
L = [a-[1, 3], b-[2]].

Sorry, the query is error; the input relation is assumed to be keysort-ed.

% ?- R0 = [a-1,b-2,a-3], keysort(R0, R),  rel_pfn(R, L).
%@ R0 = [a-1, b-2, a-3],
%@ R = [a-1, a-3, b-2],
%@ L = [a-[1, 3], b-[2]] .

No, I am missing basics, thanks for polltely tolerating my ignorance :slight_smile: