Reification integration issues - prolog

I offered the following clpfd-based code for the recent question Segregating Lists in Prolog:
list_evens_odds([],[],[]).
list_evens_odds([X|Xs],[X|Es],Os) :-
X mod 2 #= 0,
list_evens_odds(Xs,Es,Os).
list_evens_odds([X|Xs],Es,[X|Os]) :-
X mod 2 #= 1,
list_evens_odds(Xs,Es,Os).
It is concise and pure, but can leave behind many unnecessary choice-points. Consider:
?- list_evens_odds([1,2,3,4,5,6,7],Es,Os).
Above query leaves behind a useless choice-point for every non-odd item in [1,2,3,4,5,6,7].
Alternative implementation
Using the reification technique demonstrated by #false in Prolog union for A U B U C can reduce the number of unnecessary choice-points. The implementation could change to:
list_evens_odds([],[],[]).
list_evens_odds([X|Xs],Es,Os) :-
if_(#<=>(X mod 2 #= 0), (Es=[X|Es0],Os= Os0),
(Es= Es0, Os=[X|Os0])),
list_evens_odds(Xs,Es0,Os0).
To directly interact with clpfd-reification the implementation of if_/3 could be adapted like this:
if_( C_1, Then_0, Else_0) :-
call(C_1,Truth01),
indomain(Truth01),
( Truth01 == 1 -> Then_0 ; Truth01 == 0, Else_0 ).
Of course, (=)/3 would also need to be adapted to this convention.
The bottom line
So I wonder: Is using 0 and 1 as truth-values instead of false and true a good idea?
Am I missing problems along that road? Help, please! Thank you in advance!

In SWI-Prolog, you can use zcompare/3:
:- use_module(library(clpfd)).
list_evens_odds([], [], []).
list_evens_odds([X|Xs], Es, Os) :-
Mod #= X mod 2,
zcompare(Ord, 0, Mod),
ord_(Ord, X, Es0, Es, Os0, Os),
list_evens_odds(Xs, Es0, Os0).
ord_(=, X, Es0, [X|Es0], Os, Os).
ord_(<, X, Es, Es, Os0, [X|Os0]).
Example query:
?- list_evens_odds([1,2,3,4,5,6,7], Es, Os).
Es = [2, 4, 6],
Os = [1, 3, 5, 7].

I have reconsidered my proposed "double-use" of if_/3 and I feel like I'm seeing better through it now.
The comments by #false and #lurker and the answer by #mat have had their fair share in aiding my understanding. Thank you!
The "insights" I have gained are by no means dramatic; still I'd like to share them with you:
Adapting if_/3 like I did is do-able and may same some LOC's.
However, it mixes up two concepts that are procedurally quite different from each other: By default, clpfd propagates and then delays. Reified term equality OTOH forces a choice right away.
It is therefore cleaner to separate these two use cases. And of course, "Cleanliness is indeed next to Godliness"...

The straightforward solution (which works for any reifiable clp(fd) condition) would seem to be
:- use_module(library(clpfd)).
list_evens_odds([],[],[]).
list_evens_odds([X|Xs],Es,Os) :-
B #<==> (X mod 2 #= 0),
freeze(B, (B=1 -> Es=[X|Es0],Os=Os0 ; Es=Es0,Os=[X|Os0])),
list_evens_odds(Xs,Es0,Os0).
Whether 0/1 or true/false are used as truth values doesn't really matter here. The reason the 0/1 convention is preferred in arithmetic solvers is simply that you can easily reuse the truth values in arithmetic constraints, e.g. add them up, etc.

Related

How to check order in prolog?

I am trying to solve this puzzle in prolog
Five people were eating apples, A finished before B, but behind C. D finished before E, but behind B. What was the finishing order?
My current solution has singleton variable, I am not sure how to fix this.
finishbefore(A, B, Ls) :- append(_, [A,B|_], Ls).
order(Al):-
length(Al,5),
finishbefore(A,B,Al),
finishbefore(C,A,Al),
finishbefore(D,E,Al),
finishbefore(B,D,Al).
%%query
%%?- order(Al).
Here is a pure version using constraints of library(clpz) or library(clpfd). The idea is to ask for a slightly different problem.
How can an endpoint in time be associated to each person respecting the constraints given?
Since we have five persons, five different points in time are sufficient but not strictly necessary, like 1..5.
:- use_module(library(clpz)). % or clpfd
:- set_prolog_flag(double_quotes, chars). % for "abcde" below.
appleeating_(Ends, Zs) :-
Ends = [A,B,C,D,E],
Zs = Ends,
Ends ins 1..5,
% alldifferent(Ends),
A #< B,
C #< A,
D #< E,
B #< D.
?- appleeating_(Ends, Zs).
Ends = [2, 3, 1, 4, 5], Zs = [2, 3, 1, 4, 5].
There is exactly one solution! Note that alldifferent/1 is not directly needed since nowhere is it stated that two persons are not allowed to end at precisely the same time. In fact, above proves that there is no shorter solution. #CapelliC's solution imposes an order, even if two persons finish ex aequo. But for the sake of compatibility, lets now map the solution back to your representation.
list_nth1(Es, N, E) :-
nth1(N, Es, E).
appleeatingorder(OrderedPeople) :-
appleeating_(Ends, Zs),
same_length(OrderedPeople, Ends),
labeling([], Zs), % not strictly needed
maplist(list_nth1(OrderedPeople), Ends,"abcde"). % effectively enforces alldifferent/1
?- appleeatingorder(OrderedPeople).
OrderedPeople = [c,a,b,d,e].
?- appleeatingorder(OrderedPeople).
OrderedPeople = "cabde".
The last solution using double quotes produces Scryer directly. In SWI use library(double_quotes).
(The extra argument Zs of appleeating_/2 is not strictly needed in this case, but it is a very useful convention for CLP predicates in general. It separates the modelling part (appleeating_/2) from the search part (labeling([], Zs)) such that you can easily try various versions for search/labeling at the same time. In order to become actually solved, all variables in Zs have to have an actual value.)
Let's correct finishbefore/3:
finishbefore(X, Y, L) :-
append(_, [X|R], L),
memberchk(Y, R).
then let's encode the known constraints:
check_finish_time(Order) :-
forall(
member(X<Y, [a<b,c<a, d<e,d<b]),
finishbefore(X,Y,Order)).
and now let's test all possible orderings
?- permutation([a,b,c,d,e],P),check_finish_time(P).
I get 9 solutions, backtracking with ;... maybe there are implicit constraints that should be encoded.
edit
Sorry for the noise, have found the bug. Swap the last constraint order, that is b<d instead of d<b, and now only 1 solution is allowed...

Prolog Program Not Merging Sorted Lists Correctly

I have a simple program I'm trying to write in Prolog. Essentially, as I learning exercise, I'm trying to write a program that takes two sorted lists as input, and returns the merged list that is also sorted. I have dubbed the predicate "merge2" as to no be confused with the included predicate "merge" that seems to do this already.
I am using recursion. My implementation is below
merge2([],[],[]).
merge2([X],[],[X]).
merge2([],[Y],[Y]).
merge2([X|List1],[Y|List2],[X|List]):- X =< Y,merge2(List1,[Y|List2],List).
merge2([X|List1],[Y|List2],[Y|List]):- merge2([X|List1],List2,List).
When I run this, I get X = [1,2,4,5,3,6] which is obviously incorrect. I've been able to code multiple times and tried to draw out the recursion. To the best of my knowledge, this should be returning the correct result. I'm not sure why the actualy result is so strange.
Thank you.
QuickCheck is your friend. In this case, the property that you want to verify can be expressed using the following predicate:
sorted(L1, L2) :-
sort(L1, S1),
sort(L2, S2),
merge2(S1, S2, L),
sort(L, S),
L == S.
Note that sort/2 is a standard Prolog built-in predicate. Using the QuickCheck implementation provided by Logtalk's lgtunit tool, which you can run using most Prolog systems, we get:
?- lgtunit::quick_check(sorted(+list(integer),+list(integer))).
* quick check test failure (at test 2 after 0 shrinks):
* sorted([0],[0])
false.
I.e. you code fails for L1 = [0] and L2 = [0]:
?- merge2([0], [0], L).
L = [0, 0] ;
L = [0, 0] ;
false.
Tracing this specific query should allow you to quickly find at least one of the bugs in your merge2/4 predicate definition. In most Prolog systems, you can simply type:
?- trace, merge2([0], [0], L).
If you want to keep duplicates in the merged list, you can use the de facto standard predicates msort/2 in the definition of the property:
sorted(L1, L2) :-
sort(L1, S1),
sort(L2, S2),
merge2(S1, S2, L),
msort(L, S),
L == S.
In this case, running QuickCheck again:
?- lgtunit::quick_check(sorted(+list(integer),+list(integer))).
* quick check test failure (at test 3 after 8 shrinks):
* sorted([],[475,768,402])
false.
This failure is more informative if you compare the query with your clauses that handle the case where the first list is empty...
This is done using difference list and since you are learning it uses reveals, AKA spoiler, which are the empty boxes that you have to mouse over to ravel the contents. Note that the reveals don't allow for nice formatting of code. At the end is the final version of the code with nice formatting but not hidden by a reveal so don't peek at the visible code at the very end if you want to try it for yourself.
This answer takes it that you have read my Difference List wiki.
Your basic idea was sound and the basis for this answer using difference list. So obviously the big change is to just change from closed list to open list.
As your code is recursive, the base case can be used to set up the pattern for the rest of the clauses in the predicate.
Your simplest base case is
merge2([],[],[]).
but a predicate using difference list can use various means to represent a difference list with the use of L-H being very common but not one I chose to use. Instead this answer will follow the pattern in the wiki of using two variables, the first for the open list and the second for the hole at the end of the open list.
Try to create the simple base case on your own.
merge2_prime([],[],Hole,Hole).
Next is needed the two base cases when one of the list is empty.
merge2_prime([X],[],Hole0,Hole) :-
Hole0 = [X|Hole].
merge2_prime([],[Y],Hole0,Hole) :-
Hole0 = [Y|Hole].
Then the cases that select an item from one or the other list.
merge2_prime([X|List1],[Y|List2],Hole0,Hole) :-
X =< Y,
Hole0 = [X|Hole1],
merge2_prime(List1,[Y|List2],Hole1,Hole).
merge2_prime(List1,[Y|List2],Hole0,Hole) :-
Hole0 = [Y|Hole1],
merge2_prime(List1,List2,Hole1,Hole).
Lastly a helper predicate is needed so that the query merge2(L1,L2,L3) can be used.
merge2(L1,L2,L3) :-
merge2_prime(L1,L2,Hole0,Hole),
Hole = [],
L3 = Hole0.
If you run the code as listed it will produce multiple answer because of backtracking. A few cuts will solve the problem.
merge2(L1,L2,L3) :-
merge2_prime(L1,L2,Hole0,Hole),
Hole = [],
L3 = Hole0.
merge2_prime([],[],Hole,Hole) :- !.
merge2_prime([X],[],Hole0,Hole) :-
!,
Hole0 = [X|Hole].
merge2_prime([],[Y],Hole0,Hole) :-
!,
Hole0 = [Y|Hole].
merge2_prime([X|List1],[Y|List2],Hole0,Hole) :-
X =< Y,
!,
Hole0 = [X|Hole1],
merge2_prime(List1,[Y|List2],Hole1,Hole).
merge2_prime(List1,[Y|List2],Hole0,Hole) :-
Hole0 = [Y|Hole1],
merge2_prime(List1,List2,Hole1,Hole).
Example run:
?- merge2([1,3,4],[2,5,6],L).
L = [1, 2, 3, 4, 5, 6].
?- merge2([0],[0],L).
L = [0, 0].
I didn't check this with lots of examples as this was just to demonstrate that an answer can be found using difference list.

How to check which items on the list meet certain condition?

How to make a function called busLineLonger, which receives at least two parameters to decide if a bus line is longer or not?
*/This is how it works*/
* busStops(number_of_the_bus,number_of_stops)*/
/*?- busLineLonger([busStops(1,7),busStops(2,4),busStops(3,6)],5,WHICH).
* WHICH = [1,3].
Using only comparative things, like #> <# /==#.
Sorry my english
Edit...
So far I've think of something like this
busLineLonger([busStops(A,B)|R],N,[_|_]):-
N#>B,
busLineLonger(R,N,A).
Here's how you could do it using meta-predicates,
reified test predicates,
and lambda expressions.
:- use_module(library(lambda)).
First, we define the reified test predicate (>)/3 like this:
>(X,Y,Truth) :- (X > Y -> Truth=true ; Truth=false).
Next, we define three different implementations of busLineLonger/3 (named busLineLonger1/3, busLineLonger2/3, and busLineLonger3/3) in terms of the following meta-predicates: maplist/3, tfilter/3, tfiltermap/4, and tchoose/3. Of course, in the end we will only need one---but that shouldn't keep us from exploring the various options we have!
#1: based on tfilter/3 and maplist/3
Do two separate steps:
1. Select items of concern.
2. Project those items to the data of interest.
busLineLonger1(Ls0,N,IDs) :-
tfilter(\busStops(_,L)^(L>N), Ls0,Ls1),
maplist(\busStops(Id,_)^Id^true, Ls1, IDs).
#2: based on tfiltermap/4
Here, we use exactly the same lambda expressions as before, but we pass
them both to meta-predicate tfiltermap/4. Doing so can help reduce
save some resources.
busLineLonger2(Ls,N,IDs) :-
tfiltermap(\busStops(_,L)^(L>N), \busStops(Id,_)^Id^true, Ls,IDs).
Here's how tfiltermap/4 can be implemented:
:- meta_predicate tfiltermap(2,2,?,?).
tfiltermap(Filter_2,Map_2,Xs,Ys) :-
list_tfilter_map_list(Xs,Filter_2,Map_2,Ys).
:- meta_predicate list_tfilter_map_list(?,2,2,?).
list_tfilter_map_list([],_,_,[]).
list_tfilter_map_list([X|Xs],Filter_2,Map_2,Ys1) :-
if_(call(Filter_2,X), (call(Map_2,X,Y),Ys1=[Y|Ys0]), Ys1=Ys0),
list_tfilter_map_list(Xs,Filter_2,Map_2,Ys0).
#3: based on tchoose/3
Here we do not use two separate lambda expressions, but a combined one.
busLineLonger3(Ls,N,IDs) :-
tchoose(\busStops(Id,L)^Id^(L>N), Ls,IDs).
Here's how tchoose/3 can be implemented:
:- meta_predicate tchoose(3,?,?).
tchoose(P_3,Xs,Ys) :-
list_tchoose_list(Xs,P_3,Ys).
:- meta_predicate list_tchoose_list(?,3,?).
list_tchoose_list([],_,[]).
list_tchoose_list([X|Xs],P_3,Ys1) :-
if_(call(P_3,X,Y), Ys1=[Y|Ys0], Ys1=Ys0),
list_tchoose_list(Xs,P_3,Ys0).
Let's see them in action!
?- Xs = [busStops(1,7),busStops(2,4),busStops(3,6)], busLineLonger1(Xs,5,Zs).
Xs = [busStops(1, 7), busStops(2, 4), busStops(3, 6)],
Zs = [1, 3].
?- Xs = [busStops(1,7),busStops(2,4),busStops(3,6)], busLineLonger2(Xs,5,Zs).
Xs = [busStops(1, 7), busStops(2, 4), busStops(3, 6)],
Zs = [1, 3].
?- Xs = [busStops(1,7),busStops(2,4),busStops(3,6)], busLineLonger3(Xs,5,Zs).
Xs = [busStops(1, 7), busStops(2, 4), busStops(3, 6)],
Zs = [1, 3].
Done!
So... what's the bottom line?
Many meta-predicates are versatile and can be used in a lot of sitations similar to the one here.
Implementing these meta-predicates is a one time effort that is amortized quickly.
Many meta-predicates handle the "recursive part", which enables you to focus on actual work.
Often, with meta-predicates (as with regular ones), "there's more than one way to do things".
Depending on the concrete circumstances, using a particular meta-predicate may be better than using another one, and vice versa.
For this question, I think, implementation #3 (the one using tchoose/3) is best.
Some things to fix in your code:
3rd argument is [_|_], that is the result are free variables... doesn't make sense. You need two cases: one in which the B is greater than N and you include the result; the other in which B is less or equal than N, and you don't include that result.
base case is missing. what's the result when bus list is empty?
A possible solution:
busLineLonger([],_,[]).
busLineLonger([busStops(A,B)|R],N,[A|S]) :- B>N, busLineLonger(R,N,S).
busLineLonger([busStops(_,B)|R],N,S) :- B=<N, busLineLonger(R,N,S).
?- busLineLonger([busStops(1,7),busStops(2,4),busStops(3,6)],5,WHICH).
WHICH = [1, 3]

What paradigm is this?

I have a question regarding different paradigms, I have this code example in Prolog
fib(0, 0).
fib(1, 1).
fib(V, VF) :­-
    B is V ­- 1, C is V ­- 2,
    fib(B, BF), fib(C, CF),
    VF is BF + CF.
can someone please tell me what paradigm this is and why it is that?
Thank you in advance!
Let me first make the program easier to understand and also more general by using true arithmetic relations between integers instead of low-level arithmetic:
:- use_module(library(clpfd)).
fib(0, 0).
fib(1, 1).
fib(V, VF) :-
V #> 1,
B #= V - 1,
C #= V - 2,
VF #= BF + CF,
fib(B, BF),
fib(C, CF).
Notice that since we are stating the solution in terms of true relations, we can also freely move the goals.
The following queries now make it pretty clear why this is called logic programming:
First, you can ask: Is there any solution?
?- fib(X, Y).
X = Y, Y = 0 .
Yes, there is!
Then, you can ask for example: What is the 20-th Fibonacci number?
?- fib(20, Y).
Y = 6765 .
Further, you can ask: Which Fibonacci number(s) equal 233?
?- fib(X, 233).
X = 13 .
Further, you can ask: Is it true that the 10th Fibonacci number is 54?
?- fib(10, 54).
false.
No, it is not true.
Thus, since we can ask logical questions and describe solutions by stating what holds in terms of logical relations, it is called logic programming.

SWI-Prolog Creating/Printing lists, Recursion etc

I'm trying to teach myself some Prolog, however right now i'm really struggling just adapting to the declarative style having never done declarative programming before.
I'm attempting to get my program to come up with a two positive integer numbers, A & B, where A + B =< 50 and B > A. Obviously there are lots of solutions (e.g. A = 5 & B = 12 or A = 15 & B = 17) and i want my program to print all the different solutions.
I honestly don't really know where to begin and would appreciate some guidance or some example code of how to do something as explained above.
Cheers!
Looks like a good problem to use constraint logic programming:
:- use_module(library(clpfd)).
model(A, B) :-
A #> 0, B #> 0,
A + B #=< 50,
B #> A.
(I assume you want only positive integer solutions, otherwise there will be infinite number of them). Look how the model code directly reflects the problem statement.
After you have the model you can use it to find all solutions:
?- findall(_, (model(A, B), label([A, B]), writeln([A, B])), _).
[1,2]
[1,3]
[1,4]
[1,5]
[1,6]
... skipped many lines ...
[24,25]
[24,26]
true.
A more traditional Prolog solution without constraint programming (with the same results):
model2(A, B) :-
between(1, 50, A),
between(1, 50, B),
A + B =< 50,
B > A.
?- findall(_, (model2(A, B), writeln([A, B])), _).
You could do something like this:
combos(A,B) :-
between(1,50,A) ,
between(1,50,B) ,
S is A+B ,
S =< 50
.
This, on backtracking, will successively find all the solutions.
Use findall/3 to collect the results into a list:
findall(A+B,combos(A,B),X).

Resources