Single clause with if-the-else vs multiple clause predicates - performance

Let's say I want to implement a predicate that 'returns' a list of all elements shared by a list of lists.
I can implement it as a one clause (looks bit ugly for logic programing):
shared_members(Members, Lists) :-
Lists = [] ->
Members = []
; findall(M, (maplist(member(M), Lists)), Members).
or as a set of clauses:
shared_members([], []). % possibly adding cut here to increase effciency
shared_members(Members, Lists) :-
findall(M, (maplist(member(M), Lists)), Members).
Which implementation is considered to be more efficient?
I know it depends on the Prolog implementation but maybe there is a general stand about efficiency of these cases.

In this case, you don't even need the first clause shared_member([], []). The findall/3 call will result in Members = [] if Lists = [].
The question is still interesting, though, and so we'll ignore this for now. You could run some stats to determine time-efficiency. Memory efficiency difference is negligible. The second approach given, however, is considered to be the canonical approach in Prolog. But they are also not equivalent in their behavior. The "if-else" in Prolog, as represented by p1 -> p2 ; p3 cuts removes the choice point after evaluation of p1. It's equivalent to p1, !, p2 ; p3.
Here's why this matters. I'll use a contrived example (which also does not require both clauses, but illustrates the point). I'll define a len/2 predicate that is true if the first argument is the length of the second:
len(0, []).
len(N, L) :- length(L, N).
Obviously, as in the case of the original problem, the first clause here is redundant, but it is important for this illustration. If I run this query, I get the following results:
| ?- len(N, [a,b,c]).
N = 3
yes
| ?- len(3, L).
L = [_,_,_]
yes
| ?- len(N, L).
L = []
N = 0 ? ;
L = []
N = 0 ? ;
L = [_]
N = 1 ? ;
L = [_,_]
N = 2 ? ;
L = [_,_,_]
N = 3 ?
Note that if both arguments are variable, it enumerates solutions. (Also, due to the redundant first clause, one of the solutions appears twice.)
Let's rewrite this predicate using "if-else":
len(N, L) :-
( L = []
-> N = 0
; length(L, N)
).
And we'll run it:
| ?- len(N, [a,b,c]).
N = 3
yes
So far, so good. But...
| ?- len(3, L).
no
| ?- len(N, L).
L = []
N = 0
yes
| ?-
Yikes! This is quite different. What happened?
In the second approach, ( L = [] -> N = 0 ; length(L, N) ) first attempts to unify L and []. If L is a variable, this succeeds with L = []. Since it succeeded, Prolog then attempts to unify N = 0. But with the query len(3, L), N is already bound to 3. So N = 0 fails and the entire clause fails.
Using the -> ; construct then, in this case, greatly reduces the generality of the implementation and yields incorrect results in some of the call scenarios.

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.

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.

Coroutining in Prolog: when argument is a list (it has fixed length)

Question
Is it possible to schedule a goal to be executed as soon as the length of a list is known / fixed or, as #false pointed out in the comments, a given argument becomes a [proper] list? Something along this line:
when(fixed_length(L), ... some goal ...).
When-conditions can be constructed using ?=/2, nonvar/1, ground/1, ,/2, and ;/2 only and it seems they are not very useful when looking at the whole list.
As a further detail, I'm looking for a solution that presents logical-purity if that is possible.
Motivation
I think this condition might be useful when one wants to use a predicate p(L) to check a property for a list L, but without using it in a generative way.
E.g. it might be the case that [for efficiency or termination reasons] one prefers to execute the following conjunction p1(L), p2(L) in this order if L has a fixed length (i.e. L is a list), and in reversed order p2(L), p1(L) otherwise (if L is a partial list).
This might be achieved like this:
when(fixed_length(L), p1(L)), p2(L).
Update
I did implement a solution, but it lacks purity.
It would be nice if when/2 would support a condition list/1. In the meantime, consider:
list_ltruth(L, Bool) :-
freeze(L, nvlist_ltruth(L, Bool)).
nvlist_ltruth(Xs0, Bool) :-
( Xs0 == [] -> Bool = true
; Xs0 = [_|Xs1] -> freeze(Xs1, nvist_ltruth(Xs1, Bool))
; Bool = false
).
when_list(L, Goal_0) :-
nvlist_ltruth(L, Bool),
when(nonvar(Bool),( Bool == true, Goal_0 )).
So you can combine this also with other conditions.
Maybe produce a type error, if L is not a list.
when(nonvar(Bool), ( Bool == true -> Goal_0 ; sort([], L) ).
Above trick will only work in an ISO conforming Prolog system like SICStus or GNU that produces a type_error(list,[a|nonlist]) for sort([],[a|nonlist]), otherwise replace it by:
when(nonvar(Bool),
( Bool == true -> Goal_0 ; throw(error(type_error(list,L), _)).
Many systems contain some implementation specific built-in like '$skip_list' to traverse lists rapidly, you might want to use it here.
I've managed to answer my own question, but not with a pure solution.
Some observations
The difficulty encountered in writing a program that schedules some goal for execution when the length of a list is precisely known is the fact that the actual condition might change. Consider this:
when(fixed_length(L), Goal)
The length of the list might change if L is unbound or if the last tail is unbound. Say we have this argument L = [_,_|Tail]. L has a fixed width only if Tail has a fixed width (in other words, L is a list if T is a list). So, a condition that checks Tail might be the only thing to do at first. But if Tail becomes [a|Tail2] a new when-condition that tests if Tail2 is a list is needed.
The solution
1. Getting the when-condition
I've implemented a predicate that relates a partial list with the when-condition that signals when it might become a list (i.e. nonvar(T) where T is the deepest tail).
condition_fixed_length(List, Cond):-
\+ (List = []),
\+ \+ (List = [_|_]),
List = [_|Tail],
condition_fixed_length(Tail, Cond).
condition_fixed_length(List, Cond):-
\+ \+ (List = []),
\+ \+ (List = [_|_]),
Cond = nonvar(List).
2. Recursively when-conditioning
check_on_fixed_length(List, Goal):-
(
condition_fixed_length(List, Condition)
->
when(Condition, check_on_fixed_length(List, Goal))
;
call(Goal)
).
Example queries
Suppose we want to check that all elements of L are a when the size of L is fixed:
?- check_on_fixed_length(L, maplist(=(a), L)).
when(nonvar(L), check_on_fixed_length(L, maplist(=(a), L))).
... and then L = [_,_|Tail]:
?- check_on_fixed_length(L, maplist(=(a), L)), L = [_,_|L1].
L = [_G2887, _G2890|L1],
when(nonvar(L1), check_on_fixed_length([_G2887, _G2890|L1], maplist(=(a), [_G2887, _G2890|L1]))).
?- check_on_fixed_length(L, maplist(=(a), L)), L = [_,_|L1], length(L1, 3).
L = [a, a, a, a, a],
L1 = [a, a, a].
Impurity
conditon_fixed_length/2 is the source of impurity as it can be seen from the following query:
?- L = [X, Y|Tail], condition_fixed_length(L, Cond), L = [a,a].
L = [a, a],
X = Y, Y = a,
Tail = [],
Cond = nonvar([]).
?- L = [X, Y|Tail], L = [a, a], condition_fixed_length(L, Cond).
false.

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]
...

Implement a Prolog predicate that say if an element belong to a list. Problems with not numerical lists

I am studying Prolog for an university exam and I have problems with this exercise:
Implement the predicate not_member(X,L) that is TRUE if the element X does not belong to the list L.
If my reasoning is correct, I have found a solution:
% FACT (BASE CASE): It is TRUE that X is not in the list if the list is empty.
not_member(_,[]).
% RULE (GENERAL CASE): If the list is non-empty, I can divide it in its Head
% element and the sublist Tail. X does not belong to the list if it is different
% from the current Head element and if it does not belong to the sublist Tail.
not_member(X,[Head|Tail]) :-
X =\= Head,
not_member(X,Tail).
This code works well with lists of numbers, as the following queries show:
2 ?- not_member(4, [1,2,3]).
true.
3 ?- not_member(1, [1,2,3]).
false.
With lists having some non-numerical elements, however,
it does not work and reports an error:
4 ?- not_member(a, [a,b,c]).
ERROR: =\=/2: Arithmetic: `a/0' is not a function
Why?
Let's check the documentation!
(=\=)/2 is an arithmetic operator.
+Expr1 =\= +Expr2
True if expression Expr1 evaluates to a number non-equal to Expr2.
You have to use (\=)/2 to compare two generic terms:
not_member(_, []) :- !.
not_member(X, [Head|Tail]) :-
X \= Head,
not_member(X, Tail).
and:
?- not_member(d, [a,b,c]).
true.
Use prolog-dif to get logically sound answers—for both ground and non-ground cases!
Just like in this answer, we define non_member(E,Xs) as maplist(dif(E),Xs).
Let's put maplist(dif(E),Xs) and not_member(E,Xs) by #Haile to the test!
?- not_member(E,[1,2,3]).
false. % wrong! What about `E=4`?
?- maplist(dif(E),[1,2,3]).
dif(E,1), dif(E,2), dif(E,3). % success with pending goals
Is it steadfast? (For more info on this important issue, read
this, this, this, and this answer.)
?- E=d, not_member(E,[a,b,c]).
E = d.
?- not_member(E,[a,b,c]), E=d.
false. % not steadfast
?- E=d, maplist(dif(E),[a,b,c]).
E = d.
?- maplist(dif(E),[a,b,c]), E=d. % steadfast
E = d.
Let's not forget about the most general use!
?- not_member(E,Xs).
Xs = []. % a lot of solutions are missing!
?- maplist(dif(E),Xs).
Xs = []
; Xs = [_A] , dif(E,_A)
; Xs = [_A,_B] , dif(E,_A), dif(E,_B)
; Xs = [_A,_B,_C], dif(E,_A), dif(E,_B), dif(E,_C)
...

Resources