How do [ H | _ ] and [ _ | T ] in predicates work? - prolog

I am still learning Prolog and I came across this little snippet of code that I don't quite know if I have understood correctly.
Code:
% Takes the spiders friends and returns a list with persons who don't know each other.
getConspirators( [], Res, Res).
getConspirators( [H|T], CConspirators, Res):-
append( [H|T], CConspirators, PK),
knowsAtleastOne( PK),
% Gets all the friends of the possible conspirator H.
allFriends( H, PFriends),
subtract( T, PFriends, Pprim),
getConspirators( Pprim, [H|CConspirators], Res).
getConspirators( [_|T], CConspirators, Res) :-
getConspirators( T, CConspirators, Res).
% Checks if any person Y or Y's friends know anybody in PK.
knowsAtleastOne( PK):-
forall( person(Y), (memberchk(Y,PK) ; friendCons(Y,PK)) ).
% Checks if a person X's friends know any of the conspirators.
friendCons( X, Conspirators):-
friend( X, Y),
memberchk( Y, Conspirators),
!.
(this is NOT the whole program, just a small snippet of it)
I am not sure if I have understood the getConspirators( [H|T], CConspirators, Res) :- and the getConspirators( [_|T], CConspirators, Res) :- parts of the
getConspirators predicate. They look almost the same! Now, I do know that the "_" symbol means "literally any value" (AKA Prolog doesn't care about what value it is). But how does Prolog know which case to pick when running through the code? My theory is that Prolog runs the getConspirators( [_|T], CConspirators, Res) :- case if and only if the getConspirators( [H|T], CConspirators, Res) :- case fails (returns false) somewhere along the way. Have I understood this correctly?

There are three elements in play here: backtracking, unification and the list notation. I'll explain the three with a simpler example:
moon(europa).
moon(ganymede).
planet(jupiter).
planet(saturn).
We know that Europa and Ganymede are two moons (of Jupiter) and that Jupiter and Saturn are planets. When we query what planets are known, we write:
?- planet(X).
X = jupiter ; % type ; for the next answer
X = saturn. % there's no more answer, hence .
Unification happens when prolog looks for a rule head which fits to the query where the variables are substituted accordingly. For instance, there is no substitution that makes moon(X) = planet(Y) equal, but there is one for planet(jupiter) = planet(X), namely X=jupiter. That's how you obtain the first solution. For the second solution, Prolog needs to unifywith the second rule head, namely planet(saturn) = planet(X). Because this is done after the first option is completely enumerated, we call this backtracking.
Now we can focus on (linked) lists. A list is either empty ([]) or it has a first element X prepended to a tail list Xs ([X|Xs]). Prolog has also a nicer notation for the list [X | [Y | [] ]], namely [X,Y]. Internally they are the same. When we now want to collect a list of astral objects, we can formulate the following three rules:
astral_objects([]). % The empty list is a list of astral objects.
astral_objects([X|Xs]) :- % The list [X | Xs] is a list of astral objects if...
moon(X), % ... its first element X is a moon
astral_objects(Xs). % ... and the remaining list Xs is a list of astral objects
astral_object([X|Xs]) :- % Likewise for planets
planet(X),
astral_objects(Xs).
When we formulate query for a two-element list, we get all combinations of objects:
?- astral_object([A,B]).
A = B, B = europa ;
A = europa,
B = ganymede ;
A = europa,
B = jupiter ;
A = europa,
B = saturn ;
A = ganymede,
B = europa ;
A = B, B = ganymede ;
A = ganymede,
B = jupiter
%...
By unification, only rules 2 and 3 apply. In both cases we have astral_objects([X|Xs]) = astral_objects([A,B]). Remember that [A,B] is shorthand for [A|[B]] and there for X=A and Xs=[B]. The first rule of the body will unify X with the corresponding moon/planet and the recursion step describes the tail. Again, we unify astral_objects([X|Xs]) = astral_objects([B]), leading to X=B and Xs = []. Now the recursion step will only match the terminal case of the empty list and we have fully explored this path.
Now what happens if we look for an arbitrary list of astral objects?
?- astral_object(Xs).
Xs = [] ;
Xs = [europa] ;
Xs = [europa, europa] ;
Xs = [europa, europa, europa] ;
Xs = [europa, europa, europa, europa] ;
Xs = [europa, europa, europa, europa, europa]
%... does not terminate
The head astral_objects(Xs) matches all three bodies. After returning the substitution for the terminal case, it descends into the first rule over and over again. Since the length of the list is unrestricted, there are an infinite number of solutions to find before the third rule is ever tried. To avoid this, you can fairly enumerate the lists before you try to make them satisfy the predicate:
?- length(Xs,_), astral_object(Xs).
Xs = [] ;
Xs = [europa] ;
Xs = [ganymede] ;
Xs = [jupiter] ;
Xs = [saturn] ;
Xs = [europa, europa] ;
Xs = [europa, ganymede] ;
Xs = [europa, jupiter] ;
Xs = [europa, saturn] ;
Xs = [ganymede, europa]
%...
It still does not terminate, but you see the lists in ascending length and therefore the variety.

the question asked was "the getConspirators([H|T], CConspirators, Res) :- _body_ and the getConspirators([_|T], CConspirators, Res) :- _body_ parts ... My theory is that Prolog runs the getConspirators([_|T], CConspirators, Res) :- case if and only if the getConspirators([H|T], CConspirators, Res) :- case fails (returns false)"
Your theory is incorrect . Both of them will match . The only difference is that for the case of getConspirators([H|T], CConspirators, Res) :- _body_ the first element of the list will be available in the body as variable named H . But for getConspirators([_|T], CConspirators, Res) :- _body_ the first element of the list will not be available in the body as a named variable .
A good way to interpret the meaning of _ as demonstrated in this code is "a variable that I do not care to refer to later" .

Related

Understanding Prolog Lists

I am trying to understand Prolog lists, and how values are 'returned' / instantiated at the end of a recursive function.
I am looking at this simple example:
val_and_remainder(X,[X|Xs],Xs).
val_and_remainder(X,[Y|Ys],[Y|R]) :-
val_and_remainder(X,Ys,R).
If I call val_and_remainder(X, [1,2,3], R). then I will get the following outputs:
X = 1, R = [2,3];
X = 2, R = [1,3];
X = 3, R = [1,2];
false.
But I am confused as to why in the base case (val_and_remainder(X,[X|Xs],Xs).) Xs has to appear as it does.
If I was to call val_and_remainder(2, [1,2,3], R). then it seems to me as though it would run through the program as:
% Initial call
val_and_remainder(2, [1,2,3], R).
val_and_remainder(2, [1|[2,3]], [1|R]) :- val_and_remainder(2, [2,3], R).
% Hits base case
val_and_remainder(2, [2|[3]], [3]).
If the above run through is correct then how does it get the correct value for R? As in the above case the value of R should be R = [1,3].
In Prolog, you need to think of predicates not as functions as you would normally in other languages. Predicates describe relationships which might include arguments that help define that relationship.
For example, let's take this simple case:
same_term(X, X).
This is a predicate that defines a relationship between two arguments. Through unification it is saying that the first and second arguments are the same if they are unified (and that definition is up to us, the writers of the predicate). Thus, same_term(a, a) will succeed, same_term(a, b) will fail, and same_term(a, X) will succeed with X = a.
You could also write this in a more explicit form:
same_term(X, Y) :-
X = Y. % X and Y are the same if they are unified
Now let's look at your example, val_and_remainder/3. First, what does it mean?
val_and_remainder(X, List, Rest)
This means that X is an element of List and Rest is a list consisting of all of the rest of the elements (without X). (NOTE: You didn't explain this meaning right off, but I'm determining this meaning from the implementation your example.)
Now we can write out to describe the rules. First, a simple base case:
val_and_remainder(X,[X|Xs],Xs).
This says that:
Xs is the remainder of list [X|Xs] without X.
This statement should be pretty obvious by the definition of the [X|Xs] syntax for a list in Prolog. You need all of these arguments because the third argument Xs must unify with the tail (rest) of list [X|Xs], which is then also Xs (variables of the same name are, by definition, unified). As before, you could write this out in more detail as:
val_and_remainder(X, [H|T], R) :-
X = H,
R = T.
But the short form is actually more clear.
Now the recursive clause says:
val_and_remainder(X, [Y|Ys], [Y|R]) :-
val_and_remainder(X, Ys, R).
So this means:
[Y|R] is the remainder of list [Y|Ys] without X if R is the remainder of list Ys without the element X.
You need to think about that rule to convince yourself that it is logically true. The Y is the same in second and third arguments because they are referring to the same element, so they must unify.
So these two predicate clauses form two rules that cover both cases. The first case is the simple case where X is the first element of the list. The second case is a recursive definition for when X is not the first element.
When you make a query, such as val_and_remainder(2, [1,2,3], R). Prolog looks to see if it can unify the term val_and_remainder(2, [1,2,3], R) with a fact or the head of one of your predicate clauses. It fails in its attempt to unify with val_and_remainder(X,[X|Xs],Xs) because it would need to unify X with 2, which means it would need to unify [1,2,3] with [2|Xs] which fails since the first element of [1,2,3] is 1, but the first element of [2|Xs] is 2.
So Prolog moves on and successfully unifies val_and_remainder(2, [1,2,3], R) with val_and_remainder(X,[Y|Ys],[Y|R]) by unifying X with 2, Y with 1, Ys with [2,3], and R with [Y|R] (NOTE, this is important, the R variable in your call is NOT the same as the R variable in the predicate definition, so we should name this R1 to avoid that confusion). We'll name your R as R1 and say that R1 is unified with [Y|R].
When the body of the second clause is executed, it calls val_and_remainder(X,Ys,R). or, in other words, val_and_remainder(2, [2,3], R). This will unify now with the first clause and give you R = [3]. When you unwind all of that, you get, R1 = [Y|[3]], and recalling that Y was bound to 1, the result is R1 = [1,3].
Stepwise reproduction of Prolog's mechanism often leads to more confusion than it helps. You probably have notions like "returning" meaning something very specific—more appropriate to imperative languages.
Here are different approaches you can always use:
Ask the most general query
... and let Prolog explain you what the relation is about.
?- val_and_remainder(X, Xs, Ys).
Xs = [X|Ys]
; Xs = [_A,X|_B], Ys = [_A|_B]
; Xs = [_A,_B,X|_C], Ys = [_A,_B|_C]
; Xs = [_A,_B,_C,X|_D], Ys = [_A,_B,_C|_D]
; Xs = [_A,_B,_C,_D,X|_E], Ys = [_A,_B,_C,_D|_E]
; ... .
So Xs and Ys share a common list prefix, Xs has thereafter an X, followed by a common rest. This query would continue producing further answers. Sometimes, you want to see all answers, then you have to be more specific. But don't be too specific:
?- Xs = [_,_,_,_], val_and_remainder(X, Xs, Ys).
Xs = [X,_A,_B,_C], Ys = [_A,_B,_C]
; Xs = [_A,X,_B,_C], Ys = [_A,_B,_C]
; Xs = [_A,_B,X,_C], Ys = [_A,_B,_C]
; Xs = [_A,_B,_C,X], Ys = [_A,_B,_C]
; false.
So here we got all possible answers for a four-element list. All of them.
Stick to ground goals when going through specific inferences
So instead of val_and_remainder(2, [1,2,3], R). (which obviously got your head spinning) rather consider val_and_remainder(2, [1,2,3], [1,3]). and then
val_and_remainder(2, [2,3],[3]). From this side it should be obvious.
Read Prolog rules right-to-left
See Prolog rules as production rules. Thus, whenever everything holds on the right-hand side of a rule, you can conclude what is on the left. Thus, the :- is an early 1970s' representation of a ←
Later on, you may want to ponder more complex questions, too. Like
Functional dependencies
Does the first and second argument uniquely determine the last one? Does X, Xs → Ys hold?
Here is a sample query that asks for Ys and Ys2 being different for the same X and Xs.
?- val_and_remainder(X, Xs, Ys), val_and_remainder(X, Xs, Ys2), dif(Ys,Ys2).
Xs = [X,_A,X|_B], Ys = [_A,X|_B], Ys2 = [X,_A|_B], dif([_A,X|_B],[X,_A|_B])
; ... .
So apparently, there are different values for Ys for a given X and Xs. Here is a concrete instance:
?- val_and_remainder(x, [x,a,x], Ys).
Ys = [a,x]
; Ys = [x,a]
; false.
There is no classical returning here. It does not return once but twice. It's more of a yield.
Yet, there is in fact a functional dependency between the arguments! Can you find it? And can you Prolog-wise prove it (as much as Prolog can do a proof, indeed).
From comment:
How the result of R is correct, because if you look at my run-though
of a program call, the value of Xs isn't [1,3], which is what it
eventually outputs; it is instead [3] which unifies to R (clearly I am
missing something along the way, but I am unsure what that is).
This is correct:
% Initial call
val_and_remainder(2, [1,2,3], R).
val_and_remainder(2, [1|[2,3]], [1|R]) :- val_and_remainder(2, [2,3], R).
% Hits base case
val_and_remainder(2, [2|[3]], [3]).
however Prolog is not like other programming languages where you enter with input and exit with output at a return statement. In Prolog you move forward through the predicate statements unifying and continuing with predicates that are true, and upon backtracking also unifying the unbound variables. (That is not technically correct but it is easier to understand for some if you think of it that way.)
You did not take into consideration the the unbound variables that are now bound upon backtracking.
When you hit the base case Xs was bound to [3],
but when you backtrack you have look at
val_and_remainder(2, [1|[2,3]], [1|R])
and in particular [1|R] for the third parameter.
Since Xs was unified with R in the call to the base case, i.e.
val_and_remainder(X,[X|Xs],Xs).
R now has [3].
Now the third parameter position in
val_and_remainder(2, [1|[2,3]], [1|R])
is [1|R] which is [1|[3]] which as syntactic sugar is [1,3] and not just [3].
Now when the query
val_and_remainder(2, [1,2,3], R).
was run, the third parameter of the query R was unified with the third parameter of the predicate
val_and_remainder(X,[Y|Ys],[Y|R])
so R was unified with [Y|R] which unpon backtracking is [1,3]
and thus the value bound to the query variable R is [1,3]
I don't understand the name of your predicate. It is a distraction anyway. The non-uniform naming of the variables is a distraction as well. Let's use some neutral, short one-syllable names to focus on the code itself in its clearest form:
foo( H, [H | T], T). % 1st clause
foo( X, [H | T], [H | R]) :- foo( X, T, R). % 2nd clause
So it's the built-in select/3. Yay!..
Now you ask about the query foo( 2, [1,2,3], R) and how does R gets its value set correctly. The main thing missing from your rundown is the renaming of variables when a matching clause is selected. The resolution of the query goes like this:
|- foo( 2, [1,2,3], R) ? { }
%% SELECT -- 1st clause, with rename
|- ? { foo( H1, [H1|T1], T1) = foo( 2, [1,2,3], R) }
**FAIL** (2 = 1)
**BACKTRACK to the last SELECT**
%% SELECT -- 2nd clause, with rename
|- foo( X1, T1, R1) ?
{ foo( X1, [H1|T1], [H1|R1]) = foo( 2, [1,2,3], R) }
**OK**
%% REWRITE
|- foo( X1, T1, R1) ?
{ X1=2, [H1|T1]=[1,2,3], [H1|R1]=R }
%% REWRITE
|- foo( 2, [2,3], R1) ? { R=[1|R1] }
%% SELECT -- 1st clause, with rename
|- ? { foo( H2, [H2|T2], T2) = foo( 2, [2,3], R1), R=[1|R1] }
** OK **
%% REWRITE
|- ? { H2=2, T2=[3], T2=R1, R=[1|R1] }
%% REWRITE
|- ? { R=[1,3] }
%% DONE
The goals between |- and ? are the resolvent, the equations inside { } are the substitution. The knowledge base (KB) is implicitly to the left of |- in its entirety.
On each step, the left-most goal in the resolvent is chosen, a clause with the matching head is chosen among the ones in the KB (while renaming all of the clause's variables in the consistent manner, such that no variable in the resolvent is used by the renamed clause, so there's no accidental variable capture), and the chosen goal is replaced in the resolvent with that clause's body, while the successful unification is added into the substitution. When the resolvent is empty, the query has been proven and what we see is the one successful and-branch in the whole and-or tree.
This is how a machine could be doing it. The "rewrite" steps are introduced here for ease of human comprehension.
So we can see here that the first successful clause selection results in the equation
R = [1 | R1 ]
, and the second, --
R1 = [3]
, which together entail
R = [1, 3]
This gradual top-down instantiation / fleshing-out of lists is a very characteristic Prolog's way of doing things.
In response to the bounty challenge, regarding functional dependency in the relation foo/3 (i.e. select/3): in foo(A,B,C), any two ground values for B and C uniquely determine the value of A (or its absence):
2 ?- foo( A, [0,1,2,1,3], [0,2,1,3]).
A = 1 ;
false.
3 ?- foo( A, [0,1,2,1,3], [0,1,2,3]).
A = 1 ;
false.
4 ?- foo( A, [0,1,2,1,3], [0,1,2,4]).
false.
f ?- foo( A, [0,1,1], [0,1]).
A = 1 ;
A = 1 ;
false.
Attempt to disprove it by a counterargument:
10 ?- dif(A1,A2), foo(A1,B,C), foo(A2,B,C).
Action (h for help) ? abort
% Execution Aborted
Prolog fails to find a counterargument.
Tying to see more closely what's going on, with iterative deepening:
28 ?- length(BB,NN), foo(AA,BB,CC), XX=[AA,BB,CC], numbervars(XX),
writeln(XX), (NN>3, !, fail).
[A,[A],[]]
[A,[A,B],[B]]
[A,[B,A],[B]]
[A,[A,B,C],[B,C]]
[A,[B,A,C],[B,C]]
[A,[B,C,A],[B,C]]
[A,[A,B,C,D],[B,C,D]]
false.
29 ?- length(BB,NN), foo(AA,BB,CC), foo(AA2,BB,CC),
XX=[AA,AA2,BB,CC], numbervars(XX), writeln(XX), (NN>3, !, fail).
[A,A,[A],[]]
[A,A,[A,B],[B]]
[A,A,[A,A],[A]]
[A,A,[A,A],[A]]
[A,A,[B,A],[B]]
[A,A,[A,B,C],[B,C]]
[A,A,[A,A,B],[A,B]]
[A,A,[A,A,A],[A,A]]
[A,A,[A,A,B],[A,B]]
[A,A,[B,A,C],[B,C]]
[A,A,[B,A,A],[B,A]]
[A,A,[A,A,A],[A,A]]
[A,A,[B,A,A],[B,A]]
[A,A,[B,C,A],[B,C]]
[A,A,[A,B,C,D],[B,C,D]]
false.
AA and AA2 are always instantiated to the same variable.
There's nothing special about the number 3, so it is safe to conjecture by generalization that it will always be so, for any length tried.
Another attempt at Prolog-wise proof:
ground_list(LEN,L):-
findall(N, between(1,LEN,N), NS),
member(N,NS),
length(L,N),
maplist( \A^member(A,NS), L).
bcs(N, BCS):-
bagof(B-C, A^(ground_list(N,B),ground_list(N,C),foo(A,B,C)), BCS).
as(N, AS):-
bagof(A, B^C^(ground_list(N,B),ground_list(N,C),foo(A,B,C)), AS).
proof(N):-
as(N,AS), bcs(N,BCS),
length(AS,N1), length(BCS, N2), N1 =:= N2.
This compares the number of successful B-C combinations overall with the number of As they produce. Equality means one-to-one correspondence.
And so we have,
2 ?- proof(2).
true.
3 ?- proof(3).
true.
4 ?- proof(4).
true.
5 ?- proof(5).
true.
And so for any N it holds. Getting slower and slower. A general, unlimited query is trivial to write, but the slowdown seems exponential.

How to insert data into a list in recursive Prolog

Trying to figure out how to return a list which contains ancestors of person A until person B. For example, I have the following facts:
parent(john,paul).
parent(paul,henry).
parent(henry,helen).
I can use the following code to find the ancestor of Y
ancestor(X,Y):-parent(X,Y).
ancestor(X,Y):-parent(X,Z), ancestor(Z,Y).
And I want to have a function list(X,Y,L) which will return the list of ancestors between X, Y.
Ex, List(john,helen,L) will return L = [paul, henry]
Based on the previous code, I know the Z is the value needed. But I do not know how to insert these value into a list and return.
I tried this but does not work as expected:
list([]).
ancestorList(X,Y,L):- parent(X,Y).
ancestorList(X,Y,L):- parent(P,Y), list(Old), L = [P | Old], ancestorList(X,P,L).
Any help will be appreciated.
If it must hold that
ancestorList( john, helen, L) :- L = [paul, henry], L = [paul | [henry ] ].
then it must also hold that
ancestorList( paul, helen, L) :- L = [ henry], L = [henry | [] ] . % and,
ancestorList( henry, helen, L) :- L = [] .
But we also know that
ancestorList( henry, helen, L) :- parent( henry, helen), L = [] .
Thus we know that
% Parent, Child, List
ancestorList( Henry, Helen, L) :- parent( Henry, Helen), L = [] .
% Ancestor, Descendant, List
ancestorList( Paul, Helen, L) :- parent( Paul, Henry), L = [ Paul | T ] ,
ancestorList( Henry, Helen, T ) .
This will create the list which is almost what you want. You can make it be exactly so by changing one name in the above definition.
Based on your approach, you - like many other people that start working in Prolog - aim to program in Prolog as an "imperative language".
In Prolog you can not reassign a variable. If you write L = [], then this means that, unless you backtrack, L will always be the empty list. So calling L = [P|Old] later on, will result in false, since unficiation will never yield that [] and [_|_] are equal.
You thus can not "create" a list by first initializing it to [] and then later "altering" it, since altering is (or well should) not be possible. There are some noteworthy exceptions (like adding facts with assert/1, but these are typically "bad design").
Before implementing a predicate, it is better to first design an inductive definition that specifies the logical relation you aim to implement. Then you can translate this definition into a predicate.
An inductive definition here could look like:
The ancestorList(X, Z, L) of two persons X and Z is [X] given parent(X, Z) holds; and
The ancestorList(X, Y, L) of two persons X and Y is a list that starts with X given parent(X, Y) hols, and the rest of the list is the ancestorList/3 of Y up to Z.
Once we have this inductive definition, we can translate this into code. The "skeleton" of this look like:
ancestorList(X, Z, ___):-
___.
ancestorList(X, Z, ___) :-
parent(X, Y),
___.
with the ___ that still need to be filled in.
Given there aren no infinite parent/2 chains, we know that this program will not get stuck in an infinite loop, and eventually fail if there is no chain of parents between the two given ones.
A minimal edit fix to your code, while following the ancestor predicate as you indeed wanted to, could be
% (* ancestor(X,Y) :- parent(X,Y). *)
% (* ancestor(X,Y) :- parent(X,Z), ancestor(Z,Y). *)
ancestor_list(X,Y,L) :- parent(X,Y), L = [].
ancestor_list(X,Y,L) :- parent(X,Z), L = [Z | Next], ancestor_list(Z,Y,Next).
The Prolog way of building lists is top-down, not just bottom-up like in most other functional languages (it can do that too, but top-down is neater, more efficient). So we indeed "insert" the value, Z, at the top of the list L = [Z | Next] being built, and the recursive call ancestor_list(Z,Y,Next) completes that Next list until the base case which ends it with the [] as it should, thus creating the list
[Z1 , Z2 , Z3 , ...., ZN ]
[Z1 | [Z2 | [Z3 | .... [ZN | []] .... ]]]
Next1
Next2 ....
NextN_1 % (N-1)th Next
NextN
after N recursive calls. The list itself is not "returned" from the last recursive call, but it is set up by the very first call, and the rest of the recursive calls finish "setting" (unifying, really) its elements up one by one.
See also:
Tail recursion modulo cons
tailrecursion-modulo-cons tag-info

Prolog list of predicates to list of lists

I have a list like: [a([x,y]), b([u,v])] and I want my result as [[x,y], [u,v]].
Here is my code:
p(L, Res) :-
findall(X, (member(a(X), L)), A1), append([A1],[],L1),
findall(Y, (member(b(Y), L)), A2), append(L1,[A2],L2),
append(L2, Res).
This provides a partially good result but if my list is [a([x,y]), c([u,v])], I would like the result to be: [[x,y],[]] and it is [[x,y]].
More examples:
p([b([u,v]), a([x,y]), c([s,t]), d([e,f])], R)
The result I get: [[x,y],[u,v]] (as expected).
p([b([u,v]), z([x,y]), c([s,t]), d([e,f])], R)
The result I get: [[u,v]]'.
The result I want: [[],[u,v]].
EDIT: Added more examples.
Now that it's clear what the problem statement really is, the solution is a little more understood. Your current solution is a little bit overdone and can be simplified. Also, the case where you want to have a [] element when the term isn't found falls a little outside of the paradigm, so can be handled as an exception. #AnsPiter has the right idea about using =../2, particularly if you need a solution that handles multiple occurrences of a and/or b in the list.
p(L, Res) :-
find_term(a, L, As), % Find the a terms
find_term(b, L, Bs), % Find the b terms
append(As, Bs, Res). % Append the results
find_term(F, L, Terms) :-
Term =.. [F, X],
findall(X, member(Term, L), Ts),
( Ts = [] % No results?
-> Terms = [[]] % yes, then list is single element, []
; Terms = Ts % no, then result is the list of terms
).
Usage:
| ?- p([b([u,v]), z([x,y]), c([s,t]), d([e,f])], R).
R = [[],[u,v]]
yes
| ?- p([b([x,y]), a([u,v])], L).
L = [[u,v],[x,y]]
yes
| ?-
The above solution will handle multiple occurrences of a and b.
If the problem really is restricted to one occurrence of each, then findall/3 and append/3 are way overkill and the predicate can be written:
p(L, [A,B]) :-
( member(a(A), L)
-> true
; A = []
),
( member(b(B), L)
-> true
; B = []
).
Term =.. List : Unifies List with a list whose head is the atom corresponding to the principal functor of
Term and whose tail is a list of the arguments of Term.
Example :
| ?- foo(n,n+1,n+2)=..List.
List = [foo,n,n+1,n+2] ?
| ?- Term=..[foo,n,n+1,n+2].
Term = foo(n,n+1,n+2)
rely on your suggestion; you have a term contains a single argument List
so ;
p([],[]).
p([X|Xs], Result) :-
X=..[F,Y],
(%IF
\+(F='c')-> % not(F=c)
Result=[Y|Res];
%ELSE
Result = Res % Result = [Res] ==> [[x,y],[]]
),
p(Xs,Res).
Test :
| ?- p([a([x,y]), c([u,v])],R).
R = [[x,y]] ?
yes
| ?- p([a([x,y]), b([u,v])],R).
R = [[x,y],[u,v]] ?
yes

Extracting sequences (Lists) Prolog

Given a list eg [1,2,3,7,2,5,8,9,3,4] how would I extract the sequences within the list?
A sequence is defined as an ordered list (Normally I would say n-tuple but I have been told in prolog a tuple is referred to as a sequence). So we want to cut the list at the point where the next element is smaller than the previous one.
So for the list [1,2,3,7,2,5,8,9,3,4] it should return:
[ [1,2,3,7], [2,5,8,9], [3,4] ] %ie we have cut the list at position 4 & 8.
For this exercise you CANNOT use the construct ; or ->
Many thanks in advance!
EXAMPLE RESULTS:
eg1.
?-function([1,2,3,7,2,5,8,9,3,4],X): %so we cut the list at position 4 & 9
X = [ [1,2,3,7], [2,5,8,9], [3,4] ].
eg2.
?-function([1,2,3,2,2,3,4,3],X): %so we cut the list at position 3,4 & 8
X = [ [1,2,3], [2], [2,3,4], [3] ].
Hopefully that helps clarify the problem. If you need further clarification just let me know! Thanks again in advance for any help you are able to provide.
First, let's break it down conceptually. The predicate list_ascending_rest/3 defines a relation between a list Xs, the left-most ascending sublist of maximum length Ys, and the remaining items Rest. We will use it like in the following query:
?- Xs = [1,2,3,7,2,5,8,9,3,4], list_ascending_rest(Xs,Ys,Rest).
Ys = [1,2,3,7],
Rest = [2,5,8,9,3,4] ;
false.
The straight-forward predicate definition goes like this:
:- use_module(library(clpfd)).
list_ascending_rest([],[],[]).
list_ascending_rest([A],[A],[]).
list_ascending_rest([A1,A2|As], [A1], [A2|As]) :-
A1 #>= A2.
list_ascending_rest([A1,A2|As], [A1|Bs], Cs) :-
A1 #< A2,
list_ascending_rest([A2|As], Bs,Cs).
Then, let's implement predicate list_ascendingParts/2. This predicate repeatedly uses list_ascending_rest/3 for each part until nothing is left.
list_ascendingParts([],[]).
list_ascendingParts([A|As],[Bs|Bss]) :-
list_ascending_rest([A|As],Bs,As0),
list_ascendingParts(As0,Bss).
Example queries:
?- list_ascendingParts([1,2,3,7,2,5,8,9,3,4],Xs).
Xs = [[1,2,3,7], [2,5,8,9], [3,4]] ;
false.
?- list_ascendingParts([1,2,3,2,2,3,4,3],Xs).
Xs = [[1,2,3], [2], [2,3,4], [3]] ;
false.
Edit 2015/04/05
What if the ascending parts are known but the list is unknown? Let's find out:
?- list_ascendingParts(Ls, [[3,4,5],[4],[2,7],[5,6],[6,8],[3]]).
Ls = [3,4,5,4,2,7,5,6,6,8,3] ? ;
no
And let's not forget about the most general query using list_ascendingParts/2:
?- assert(clpfd:full_answer).
yes
?- list_ascendingParts(Ls, Ps).
Ls = [], Ps = [] ? ;
Ls = [_A], Ps = [[_A]] ? ;
Ls = [_A,_B], Ps = [[_A],[_B]], _B#=<_A, _B in inf..sup, _A in inf..sup ? ...
Edit 2015-04-27
Room for improvement? Yes, definitely!
By using the meta-predicate splitlistIfAdj/3 one can "succeed deterministically" and "use non-determinism when required", depending on the situation.
splitlistIfAdj/3 is based on if_/3 as proposed by #false in this answer. So the predicate passed to it has to obey the same convention as (=)/3 and memberd_truth/3.
So let's define (#>)/3 and (#>=)/3:
#>=(X,Y,Truth) :- X #>= Y #<==> B, =(B,1,Truth).
#>( X,Y,Truth) :- X #> Y #<==> B, =(B,1,Truth).
Let's re-ask above queries, using splitlistIfAdj(#>=)
instead of list_ascendingParts:
?- splitlistIfAdj(#>=,[1,2,3,7,2,5,8,9,3,4],Pss).
Pss = [[1,2,3,7],[2,5,8,9],[3,4]]. % succeeds deterministically
?- splitlistIfAdj(#>=,[1,2,3,2,2,3,4,3],Pss).
Pss = [[1,2,3],[2],[2,3,4],[3]]. % succeeds deterministically
?- splitlistIfAdj(#>=,Ls,[[3,4,5],[4],[2,7],[5,6],[6,8],[3]]).
Ls = [3,4,5,4,2,7,5,6,6,8,3] ; % works the other way round, too
false. % universally terminates
Last, the most general query. I wonder what the answers look like:
?- splitlistIfAdj(#>=,Ls,Pss).
Ls = Pss, Pss = [] ;
Ls = [_G28], Pss = [[_G28]] ;
Ls = [_G84,_G87], Pss = [[_G84],[_G87]], _G84#>=_G87 ;
Ls = [_G45,_G48,_G41], Pss = [[_G45],[_G48],[_G41]], _G45#>=_G48, _G48#>=_G41
% and so on...
maplist/3 as suggested in the comment won't help you here because maplist/3 is good at taking a list and mapping each element into a same-size collection of something else, or establishing a relation evenly across all of the individual elements. In this problem, you are trying to gather contiguous sublists that have certain properties.
Here's a DCG solution. The idea here is to examine the list as a series of increasing sequences where, at the boundary between them, the last element of the prior sequence is less than or equal to the first element of the following sequence (as the problem statement basically indicates).
% A set of sequences is an increasing sequence ending in X
% followed by a set of sequences that starts with a value =< X
sequences([S|[[Y|T]|L]]) --> inc_seq(S, X), sequences([[Y|T]|L]), { X >= Y }.
sequences([S]) --> inc_seq(S, _).
sequences([]) --> [].
% An increasing sequence, where M is the maximum value
inc_seq([X,Y|T], M) --> [X], inc_seq([Y|T], M), { X < Y }.
inc_seq([X], X) --> [X].
partition(L, R) :- phrase(sequences(R), L).
| ?- partition([1,2,3,4,2,3,8,7], R).
R = [[1,2,3,4],[2,3,8],[7]] ? ;
(1 ms) no
| ?- partition([1,2,3,2,2,3,4,3],X).
X = [[1,2,3],[2],[2,3,4],[3]] ? ;
(1 ms) no
The only reason for the rule sequences([]) --> []. is if you want partition([], []) to be true. Otherwise, the rule isn't required.

Appending lists in prolog without repetition

I need to know how can i get all of combination of appending two lists with each other without repetition like [1,2] & [3,4] the result will be [1,3] [1,4] [2,3] [2,4]
This is the solution that does not work as desired:
(1) comb([], [], []).
(2) comb([H|T], [X|Y], [H,X]).
(3) comb([H,T|T1], [X,Y|T2], [T,Y]).
(4) comb([H|T], [X|Y], L) :-
comb(T, Y, [H|X]).
(1) says, Combining an empty list with an empty list is an empty list. This sounds logically correct.
(2) says, [H,X] is a pair of elements from [H|T] and [X|Y]. This is true (provides only one of the combinations for the solution).
(3) says, [T,Y] is a pair of elements from [H,T|T1] and [X,Y|T2]. This is also true (provides only one other combination for the solution, different to #2).
(4) says, L is a pair of elements from [H|T] and [X|Y] if [H|X] is a pair of elements from T and Y. This can't be true since L doesn't appear in the consequent of the clause, so it will never be instantiated with a value.
The above solution is over-thought and more complicated than it needs to be. It fails because it hard-codes two solutions (matching the first two elements and the second two elements). The recursive clause is then faulty since it doesn't have a logical basis, and the solution is left as a singleton variable.
To start, you need to decide what your predicate means. In this particular problem, you can think of your predicate comb(Xs, Ys, P). as being TRUE if P is a pair (say it's [X,Y]) where X is from Xs (i.e., X is a member of Xs) and Y is from Ys (Y is a member of Ys). Then, when you query your predicate, it will prompt you with each solution until all of them have been found.
This problem can be stated with one rule: [X,Y] is a combination of elements taken from Xs and Ys, respectively, if X is a member of Xs and Y is a member of Ys. That sounds like a trivially true statement, but it's all you need to solve this problem.
Translating this into Prolog gives this:
comb(Xs, Ys, [X,Y]) :- % [X,Y] is combination of elements from Xs and Ys if...
member(X, Xs), % X is a member of Xs, and
member(Y, Ys). % Y is a member of Ys
Now let's try it:
| ?- comb([1,2],[3,4],P).
P = [1,3] ? ;
P = [1,4] ? ;
P = [2,3] ? ;
P = [2,4]
(2 ms) yes
| ?-
It found all of the combinations. We let Prolog do all the work and we only had to declare what the rule was.
If you want to collect all the results in a single list, you can use a built-in predicate such as findall/3:
| ?- findall(P, comb([1,2], [3,4], P), AllP).
AllP = [[1,3],[1,4],[2,3],[2,4]]
yes
| ?-
And voilà. :)
You can also generalize the solution very easily and choose one element each from each list in a given list of lists. Here, multicomb/2 has as a first argument a list of lists (e.g., [[1,2], [3,4]]` and generates every combination of elements, one from each of these sublists:
multicomb([L|Ls], [X|Xs]) :-
member(X, L),
multicomb(Ls, Xs).
multicomb([], []).
Which gives:
| ?- multicomb([[1,2],[3,4]], P).
P = [1,3] ? a
P = [1,4]
P = [2,3]
P = [2,4]
yes
| ?-
And:
| ?- multicomb([[1,2],[a,b],[x,y,z]], P).
P = [1,a,x] ? a
P = [1,a,y]
P = [1,a,z]
P = [1,b,x]
P = [1,b,y]
P = [1,b,z]
...

Resources