Consider the following graph
and that it is described by the below Prolog term :
graph([connected(a,[b,c]), connected(b,[a,c]), connected(c,[a,b,d]), connected(d,[c]) ]).
I would like to define a predicate which transforms the above connections into a list of the corresponding pairs. In other words, a predicate which yields
[[a,b],[a,c],[b,c],[c,d]] for the above term-graph.
Could you please advise how to do it ?
My attempt so far is the following :
map 2-neighbor vertex to pairs :
map2ne(adjacent(H,[K|T]),Pair) :-
append([H],[K],L),
append([H],T,M),
append([L],[M],Pair).
This runs ok.
map 3-neighbor vertex to pairs :
map3n(adjacent(H,[K,L|T]),Pair) :-
append([H],[K],A1),
append([H],[L],A2),
append([A1],[A2],Z),
append([H],T,M),
append(Z,[M],Pair).
This also runs ok.
But when I try to extend it to n-neighbor vertex, then it fails :
mapmany(adjacent(H, [K|_]),Pair) :-
append([H],[K],L),
append(L,[],Pair),
mapmany(adjacent(H,[K|_]),M),
append(M,Pair,Pair).
And also the below fails, which was intented to map many n-neighbor vertices to pairs :
mapping(Map,Pairs) :-
select(X,Map,Y),
mapmany(X,PairX),
append([PairX],Pairs),
mapping(Y,Pairs).
If you're going to use a solution based on setof/3, I strongly recommend defining an auxiliary predicate. This predicate should define exactly what we want a set of. When we want to define "the set of all edges in the graph", mathematically we might say something like "Edges is the set of all Edge terms where Edge is an edge in Graph".
We can write this very directly as follows:
graph_edges(Graph, Edges) :-
setof( Edge,
graph_edge(Graph, Edge),
Edges ).
It remains to define graph_edge/2 itself. The core of this can be lifted from slago's solution:
graph_edge(Graph, Edge) :-
member(connected(V, Ns), Graph),
member(W, Ns),
edge(V, W, Edge).
The advantages of having this as a separate predicate are:
the setof call is easier to read
the predicate itself has a nice descriptive name
the predicate can be tested in isolation
the predicate can be reused
no ^ signs anywhere, which have no meaning in Prolog except for complicating setof calls that don't use an auxiliary predicate
no worrying about "existential quantification", which has no meaning in Prolog except for complicating setof calls that don't use an auxiliary predicate
There are too many flaws in your code:
The adjacency list defined by graph/1 is composed of terms of the form connected(Vertex, Neighbors); however, your code deals with an adjacency list of terms of the form adjacent(Vertex, Neighbors).
Predicate append/3 should not be used to create all lists; for example, instead of append([H], [K], L), you should use L = [H, K].
In Prolog, it is more idiomatic to represent a pair of items V and W as V-W, instead of [V,W].
By the answer you expect for the example given (i.e., [a-b,a-c,b-c,c-d]), a single term V-W (i.e., {V,W}) represents both the edges (V,W) and (W,V). So, to avoid redundancy, you must exclusively choose V-W or W-V to put in your answer (without loss of generality, you can choose the term where V precedes W).
To to create an edge, you can do the following:
edge(V, W, Edge) :-
( V #< W
-> Edge = V-W
; Edge = W-V ).
Examples:
?- edge(a, b, Edge).
Edge = a-b.
?- edge(b, a, Edge).
Edge = a-b.
To create all edges connecting a vertex V to its neighbors Ns, without duplicates, just ask:
?- V=a, Ns=[b,c,d], setof(E, W^Ns^(member(W,Ns), edge(V,W,E)), Edges).
V = a,
Ns = [b, c, d],
Edges = [a-b, a-c, a-d].
Notice that the construct Var^Goal tells setof/3 not to bind variable Var in Goal (in other words, indicates that Var is existentially quantified).
Generalizing this idea, we have:
graph_edges(Graph, Edges) :-
setof( Edge,
V^Ns^W^( member(connected(V, Ns), Graph),
member(W, Ns),
edge(V, W, Edge)),
Edges ).
graph([connected(a, [b, c]),
connected(b, [a, c]),
connected(c, [a, b, d]),
connected(d, [c])]).
Example:
?- graph(G), graph_edges(G, E).
G = [connected(a, [b, c]), connected(b, [a, c]), connected(c, [a, b, d]), connected(d, [c])],
E = [a-b, a-c, b-c, c-d].
LIBRARY UGRAPHS
In SWI-Prolog, a trivial solution would be to use the predicate edges/2 from library(ugraphs). Be careful though, because the representation of undirected graphs on which the predicate edge/2 is based is different from the one you are considering (an undirected graph in the library(ugraphs) is represented by a list of vertex pairs where the order of the vertices in these pairs matters). For example:
?- edges([a-[b,c], b-[a,c], c-[a,b,d], d-[c]], E).
E = [a-b, a-c, b-a, b-c, c-a, c-b, c-d, d-c].
Related
I need a method that returns all the roads* used in a route between two points, here's the map I have:
Example, to point A to E, i need a list of roads used, like that:
route(a, e, R).
R = [1,5].
I'm having problems in marking the routes that i've already visited, and on top of that, register the number of the road used in a list.
So here's my code so far:
road(1,a,b).
road(2,a,d).
road(3,b,c).
road(4,c,d).
road(5,b,e).
road(6,c,f).
road(7,d,f).
road(8,e,f).
connected(A,B) :- road(_,A,B).
route(A, B, R) :- road(R, A, B), road(R, B, A).
route(A, B, [R2|R]) :- route(A, C, R2), route(C, B, R2).
Thanks for the help!
I did know the procedure, but i was finding difficult in appending the roads to the list, here's the final code:
road(1,a,b).
road(2,a,d).
road(3,b,c).
road(4,c,d).
road(5,b,e).
road(6,c,f).
road(7,d,f).
road(8,e,f).
route(X,Y,[R]) :- road(R,X,Y).
route(X,Y,[R1|R2]) :- road(R1,X,Z), route(Z,Y, R2).
Here's my desired output:
?- route(a,f,R).
R = [1, 3, 6] .
I was making a confusion in appending the list in the second definition of route, the examples helped me.
Thanks for the help!!
Your solution is still not resisting cycles in graph, here is once that keeps it in mind
route(A,A,R,R).
route(A,B,R,R2) :- road(Rx,A,C), \+ member(Rx,R) , route(C,B,[Rx|R],R2).
route(A,B,R) :- route(A,B,[],Rx), reverse(R,Rx).
The predicate if_/3 seems to be fairly popular among the few main contributors in the Prolog part of Stack Overflow.
This predicate is implemented as such, courtesy of #false:
if_(If_1, Then_0, Else_0) :-
call(If_1, T),
( T == true -> call(Then_0)
; T == false -> call(Else_0)
; nonvar(T) -> throw(error(type_error(boolean,T),_))
; /* var(T) */ throw(error(instantiation_error,_))
).
However, I have been unable to find a clear, simple, and concise explanation of what this predicate does, and what use it has compared to e.g. the classical if-then-else construct of Prolog if -> then ; else.
Most links I have found directly use this predicate and provide little explanation as to why it gets used, that a non-expert in Prolog could understand easily.
In old-fashioned Prolog code, the following pattern arises rather frequently:
predicate([], ...).
predicate([L|Ls], ...) :-
condition(L),
then(Ls, ...).
predicate([L|Ls], ...) :-
\+ condition(L),
else(Ls, ...).
I am using lists here as an example where this occurs (see for example include/3, exclude/3 etc.), although the pattern of course also occurs elsewhere.
The tragic is the following:
For an instantiated list, pattern matching can distinguish the first clause from the remaining two, but it cannot distinguish the second one from the last one because they both have '.'(_, _) as the primary functor and arity of their first argument.
The conditions in which the last two clauses apply are obviously mutually exclusive.
Thus, when everything is known, we want to obtain an efficient, deterministic predicate that does not leave choice points, and ideally does not even create choice points.
However, as long as not everything can be safely determined, we want to benefit from backtracking to see all solutions, so we cannot afford to commit to either of the clauses.
In summary, the existing constructs and language features all fall short in some way to express a pattern that often occurs in practice. Therefore, for decades, it seemed necessary to compromise. And you can make a pretty good guess in which direction the "compromises" usually go in the Prolog community: Almost invariably, correctness is sacrificed for efficiency in case of doubt. After all, who cares about correct results as long as your programs are fast, right? Therefore, until the invention of if_/3, this was frequently wrongly written as:
predicate([], ...).
predicate([L|Ls], ...) :-
( condition(L) ->
then(Ls, ...).
; else(Ls, ...).
)
The mistake in this is of course that when the elements are not sufficiently instantiated, then this may incorrectly commit to one branch even though both alternatives are logically possible. For this reason, using if-then-else is almost always declaratively wrong, and stands massively in the way of declarative debugging approaches due to its violation of the most elementary properties we expect from pure Prolog programs.
Using if_/3, you can write this as:
predicate([], ...).
predicate([L|Ls], ...) :-
if_(condition(L),
then(Ls, ...),
else(Ls, ...)).
and retain all desirable aspects. This is:
deterministic if everything can be safely decided
efficient in that it does not even create choice points
complete in that you never incorrectly commit to one particular branch.
The price of this is rather affordable: As Boris mentioned in the comments, you need to implement a reification. I have now some experience with this and found it rather easy with some practice.
Good news everyone: In many cases, condition is of the form (=)/2, or (#=)/2, and the first even ships with library(reif) for free.
For more information, see Indexing dif/2 by Ulrich Neumerkel and Stefan Kral!
Let's try to solve a simple problem using if_/3; for example, I will try to partition a list (sorted on a predicate p/2) in two lists: a prefix in which, for every element X, we have p(X, true), and a rest (in which, if the list was sorted on p/2, we would have p(X, false).
I will use the library reif as here. So, here is the complete code of my program:
:- use_module(reif).
pred_prefix(Pred_1, List, L_true, L_false) :-
pred_prefix_aux(List, Pred_1, L_true, L_false).
pred_prefix_aux([], _, [], []).
pred_prefix_aux([X|Xs], Pred_1, True, False) :-
if_( call(Pred_1, X),
( True = [X|True0],
pred_prefix_aux(Xs, Pred_1, True0, False)
),
( True = [],
False = [X|Xs]
)
).
The predicate passed to this meta-predicate will take two arguments: the first is the current list element, and the second will be either true or false. Ideally, this predicate will always succeed and not leave behind choice points.
In the first argument of if_/2, the predicate is evaluated with the current list element; the second argument is what happens when true; the third argument is what happens when false.
With this, I can split a list in leading as and a rest:
?- pred_prefix([X, B]>>(=(a, X, B)), [a,a,b], T, F).
T = [a, a],
F = [b].
?- pred_prefix([X, B]>>(=(a, X, B)), [b,c,d], T, F).
T = [],
F = [b, c, d].
?- pred_prefix([X, B]>>(=(a, X, B)), [b,a], T, F).
T = [],
F = [b, a].
?- pred_prefix([X, B]>>(=(a, X, B)), List, T, F).
List = T, T = F, F = [] ;
List = T, T = [a],
F = [] ;
List = T, T = [a, a],
F = [] ;
List = T, T = [a, a, a],
F = [] .
How can you get rid of leading 0's for example:
?- pred_prefix([X, B]>>(=(0, X, B)), [0,0,1,2,0,3], _, F).
F = [1, 2, 0, 3].
Of course, this could have been written much simpler:
drop_leading_zeros([], []).
drop_leading_zeros([X|Xs], Rest) :-
if_(=(0, X), drop_leading_zeros(Xs, Rest), [X|Xs] = Rest).
Here I have just removed all unnecessary arguments.
If you would have to do this without if_/3, you would have had to write:
drop_leading_zeros_a([], []).
drop_leading_zeros_a([X|Xs], Rest) :-
=(0, X, T),
( T == true -> drop_leading_zeros_a(Xs, Rest)
; T == false -> [X|Xs] = Rest
).
Here, we assume that =/3 will indeed always succeed without choice points and the T will always be either true or false.
And, if we didn't have =/3 either, you'd write:
drop_leading_zeros_full([], []).
drop_leading_zeros_full([X|Xs], Rest) :-
( X == 0 -> T = true
; X \= 0 -> T = false
; T = true, X = 0
; T = false, dif(0, X)
),
( T == true -> drop_leading_zeros_full(Xs, Rest)
; T == false -> [X|Xs] = Rest
).
which is not ideal. But now at least you can see for yourself, in one single place, what is actually going on.
PS: Please read the code and the top level interaction carefully.
My database follows this format:
aminotodna (Amincoacid, [DNA sequence]).
Here are a few examples from the database:
aminotodna(a,[g,c,a]).
aminotodna(a,[g,c,c]).
aminotodna(a,[g,c,g]).
aminotodna(a,[g,c,t]).
aminotodna(c,[t,g,c]).
aminotodna(c,[t,g,t]).
aminotodna(d,[g,a,c]).
aminotodna(d,[g,a,t]).
aminotodna(e,[g,a,a]).
aminotodna(e,[g,a,g]).
aminotodna(f,[t,t,c]).
aminotodna(f,[t,t,t]).
Some aminoacids have multiple DNA sequences.
Here is my question, so in a given list of amino acids for example [d,c,e,f], how can I append their DNA sequences together and give all combinations, as some have more than one sequence.
If it was just two I could do it, it'd just be
listamino(X,Y) :-
aminotodna(X,L),
aminotodna(Y,M),
append(L,M,Z),
print(Z).
hitting ; gives all combinations.
I've tired doing it with a list, but this is my attempt, and it didnt work:
listamino([]).
listamino([H|T]) :-
aminotodna(H,L),
aminotodna(T,M),
append(L,M,X),
print(X).
listamino(T).
When describing lists with Prolog, always consider using DCG notation for convenience and clarity. For example, using a subset of your examples, I first use DCG rules to describe the correspondence (note that I am using a name that makes sense in all directions):
amino_dna(a) --> [g,c,a].
amino_dna(a) --> [g,c,c].
amino_dna(c) --> [t,g,c].
amino_dna(c) --> [t,g,t].
an then I again use DCG rules to describe the concatenation of such lists:
aminos([]) --> [].
aminos([A|As]) --> amino_dna(A), aminos(As).
Sample query:
?- phrase(aminos([a,c]), As).
As = [g, c, a, t, g, c] ;
As = [g, c, a, t, g, t] ;
As = [g, c, c, t, g, c] ;
etc.
No append/3, no additional variables, no additional arguments, no nonsense. Use dcg!
You need an extra parameter to keep track of the current combination:
; invoke a version of listamino which tracks the current combination of DNA sequences, which is initially empty
listamino(X) :-
listamino(X,[]).
; If there are no ore aminos, print the DNA seq list, and we're done
listamino([],X) :-
print(X).
; Otherwise, append the DNA for the first amino to our list, and process the rest of the mains
listamino([H|T],X) :-
aminotodna(H,L),
append(X,L,X2),
listamino(T,X2).
I am studying prolog and was wondering if anybody give me guidance on how to go about doing this question, It's the first of many in this area and knowing how to do this question will really help me progress. Thank-you in advance.
Using Prolog define a predicate mapof(K, M, V) such that, when invoked with K instantiated to a key, and M instantiated to a mapping, mapof will instantiate the variable V to the value (or one of the values) associated with K in mapping M. The predicate should fail if K does not appear as a key in mapping M.
It really depends how you want to represent your "mapping". In Prolog, a table of facts is the most obvious approach. For two mappings m and n:
m(a, 1).
m(b, 2).
m(c, 3). % and so on
n(a, foo).
n(b, bar).
n(c, baz). % and so on
Then, your mapof would be something along the lines of:
mapof(K, m, V) :- m(K, V).
mapof(K, n, V) :- n(K, V).
or maybe:
mapof(K, M, V) :- call(M, K, V).
A list can be used to represent a mapping, as shown by #Yasel, but a list [a, b, c] in Prolog is a nested term like .(a, .(b, .(c, []))). You don't usually represent an associative array as a singly linked list, right?
In SWI-Prolog there is a library that is better than using a simple list for a backtrackable associative array represented as a Prolog term: library(assoc). With it, you can do:
mapof(K, M, V) :- gen_assoc(K, M, V).
This library represents the associative array as an AVL tree. You can find in the SWI-Prolog code source two more associative array implementations: one using RB-trees, and one that uses non-backtrackable RB-trees.
All three libraries mentioned here are probably more efficient than a simple list of key-value pairs [k1-v1, k2-v2...] if your associative array has more than say around 100 key-value pairs in it. This doesn't mean that using a list of pairs and doing member(Key-Value, List_of_pairs) is wrong; it is the cheapest solution for simple cases.
Using the built-in predicate member/2 you can build your predicate mapof/3 like this:
mapof(K, M, V):- member((K,V), M).
Consult:
?- mapof(k1, [(k, a),(k1,b),(k2,c),(k1,d)], V).
V = b ;
V = d.
I've been trying to solve the following problem for a while now, but can't seem to find the right solution.
Lets say there is a function test(X,Y,Z) such that X is a single pair of numbers, Y is a list of pairs, and Z is the resulting list of transitive pairs.
For example:
test((1,5), [(7,3),(5,2),(5,9)], Z).
Z = [(1,2),(1,9)]
(because of transitivity 1->5->2 and 1->5->9)
So far I've managed to create the following code:
test(_,[],_):- false.
test((X1,C),[(C,Y2)|_],(X1,Y2)).
test((X1,X2),[_|YT],Result) :- test((X1,X2),YT,Result).
It returns each individual result pair like so:
Z = (1, 2) ;
Z = (1, 9) ;
But I can't seem to return them all into a single list like in the example above:
Z = [(1,2),(1,9)]
Any help would be greatly appreciated.
I think the problem is that you're not building the list of transitive pairs. You're just returning a single pair as the third argument of test/3.
Here's one possible solution:
I made a predicate to handle comparing pairs and describing their transitive marriage, so that i didn't have to juggle those tuples in the subsequent rules:
transit((X,T), (T,Y), (X,Y)).
Then it's just a matter of standard list processing with recursive predicates:
t(_, [], []).
t(X, [T|ToTransit], [Y|Transited]) :-
transit(X,T,Y),
t(X,ToTransit,Transited).
t(X, [T|ToTransit], Transited) :-
\+ transit(X,T,_),
t(X,ToTransit, Transited).
Of course, once you have a predicate like transit/3 that defines the relation, you can also do something like
findall( TP,
( member(T, [(2,2), (2,5), (1,5)]), transit((1,2), T, TP) ),
Tps).