To compare the Equality and Print the Equal value - prolog

I want to compare 2 values X and C1 as you can see in code, X is reversed value of C if both values are equal then it should print the compared value please tell me how to do this. It is to print Palindrome Numbers like... 1,11,22,33,44,55,66,77,88,99,101....
go(N):-
write(0),nl,
go(0,N).
go(_,0):- !.
go(A,C):-
A1 is A,
C1 is A1 + 1,
/* write(C1),nl,*/
rev(C1,X),
/* write(X),nl,*/
/* To compare the Value of X and C1 and print if compared value is true*/
NewC is C-1,
go(C1,NewC).
rev(Q,E):-
name(Q, Q1),
reverse(Q1,E1),
name(E,E1).

Describing palindrome numbers is actually a nice task for CLP(FD) and DCGs. First let's describe what the digits of a palindrome number look like:
:- use_module(library(clpfd)).
palindromedigits(Digits) :- % Digits are palindrome digits if
Digits ins 0..9, % they are between 0 and 9
Digits = [H|_], % and the first digit...
H #\= 0, % ... is different from 0
phrase(palindrome, Digits). % and they form a palindrome
palindrome --> % a palindrome is
[]. % an empty list
palindrome --> % or
[_]. % a list with a single element
palindrome --> % or
[A], % an element A
palindrome, % followed by a palindrome
[A]. % followed by an element A
To test if a number is a palindrome, you could turn it into a list of digits and palindromedigits/1 has to hold for that list. To generate such numbers, you could use length/2 to describe lists of all possible lengths, palindromedigits/1 again has to hold for those lists and the digits have to be multiplied by their respective powers of ten and summed up. Since leading zeros are excluded by palindromedigits/1, you'd have to add a fact for 0, if you want to include it in the palindrome numbers. That might look something like this:
palindromenumber(0). % 0 is a palindromenumber
palindromenumber(PN) :- % rule for testing numbers
number(PN), % succeeds if PN is a number
number_codes(PN,C), % C is a list of codes corresponding to the digits
maplist(plus(48),Digits,C), % codes and digits are off by 48
palindromedigits(Digits). % Digits is a palindrome
palindromenumber(PN) :- % rule for generating numbers
var(PN), % succeeds if PN is a variable
length(Digits,_), % Digits is a list of length 0,1,2,...
palindromedigits(Digits), % Digits is a palindrome
digits_number_(Digits,PN,1,0), % Digits correspond to the number PN
label(Digits). % labels the list Digits with actual numbers
Note that the codes corresponding to the digits are off by 48, hence the goal with maplist/3, e.g.:
?- number_codes(123,C), maplist(plus(48),Digits,C).
C = [49, 50, 51], % <- the codes
Digits = [1, 2, 3]. % <- the actual digits
The predicate digits_number_/4 is fairly straight forward. It is called with 1 as the initial power of ten and 0 as the initial accumulator for the number. The digits are multiplied with the power of ten corresponding to their position in the number and subsequently added to the accumulator. If the list of digits is empty, the accumulator holds the number corresponding to the list of digits.
digits_number_([],PN,_,PN).
digits_number_([D|Ds],PN,P,Acc) :-
Acc1 #= Acc + D*B,
P10 #= P*10,
digits_number_(Ds,PN,P10,Acc1).
Note that it doesn't matter that the digits are multiplied with the powers in reverse order, because it's a palindrome number.
Now you can query for palindrome numbers:
?- palindromenumber(PN).
PN = 0 ;
PN = 1 ;
PN = 2 ;
.
.
.
PN = 33 ;
PN = 44 ;
PN = 55 ;
.
.
.
PN = 666 ;
PN = 676 ;
PN = 686 ;
.
.
.
PN = 7667 ;
PN = 7777 ;
PN = 7887
.
.
.
Or you can test if a number is a palindrome:
?- palindromenumber(121).
true ;
false.
?- palindromenumber(123).
false.
?- palindromenumber(12321).
true ;
false.
EDIT
To address the question in your comment, you can do that by describing a relation between such a sequence and it's length. So you'll have a predicate with arity two instead of arity one. Let's give it a nice descriptive name, say firstN_palindromicnumbers/2. The actual realation is described by a predicate with an additional argument that holds the current candidate to be examined. Since you want to start the sequence with 1, that will be the argument firstN_palindromicnumbers_/3 will be called with:
firstN_palindromicnumbers(N,PNs) :-
firstN_palindromicnumbers_(N,PNs,1). % sequence starts with 1
The argument that holds the candidates will be increased by 1 through the recursions, while the first argument, N, will be decreased every time a candidate turns out to be an actual palindromic number. So the predicate eventually ends up with N being 0, an empty list and a candidate we don't care for. That will be the base case. Otherwise the head of the list is the smallest palindromic number in the (remainder of the) sequence. You can reuse the goals number_codes/2 and maplist/3 from above to describe a list of digits corresponding to the current candidate and the DCG palindrome//0 to state that the digits have to be a palindrome. The other goals from the predicate palindromedigits/1 won't be needed, since the candidates will be 1,2,3,..., thus consisting of (at least one) digit(s) from 0 to 9 without leading zeros. You can express this in Prolog like so:
firstN_palindromicnumbers_(0,[],_C). % base case
firstN_palindromicnumbers_(N1,[C0|PNs],C0) :- % case: C0 is a palindrome
N1 #> 0, % sequence is not of desired length yet
number_codes(C0,Codes),
maplist(plus(48),Digits,Codes),
phrase(palindrome, Digits), % digits form a palindrome
N0 #= N1-1, % sequence of length N1-1 has to be described yet
C1 #= C0+1, % C1 is the next candidate
firstN_palindromicnumbers_(N0,PNs,C1). % PNs is the rest of the sequence
firstN_palindromicnumbers_(N1,PNs,C0) :- % case: C0 ain't a palindrome
N1 #> 0, % sequence is not of desired length yet
number_codes(C0,Codes),
maplist(plus(48),Digits,Codes),
\+ phrase(palindrome, Digits), % digits don't form a palindrome
C1 #= C0+1, % C1 is the next candidate
firstN_palindromicnumbers_(N1,PNs,C1). % PNs is the rest of the sequence
Now you can query the predicate for a sequence of palindromic numbers of given length (Note that with SWI-Prolog you might have to hit w to see the entire list):
?- firstN_palindromicnumbers(15,PNs).
PNs = [1, 2, 3, 4, 5, 6, 7, 8, 9|...] [write] % <- hit the w key
PNs = [1, 2, 3, 4, 5, 6, 7, 8, 9, 11, 22, 33, 44, 55, 66] ;
false.
?- firstN_palindromicnumbers(25,PNs).
PNs = [1, 2, 3, 4, 5, 6, 7, 8, 9, 11, 22, 33, 44, 55, 66, 77, 88, 99, 101, 111, 121, 131, 141, 151, 161] ;
false.
You can also use the predicate to check if a given list is the sequence of the first N palindrommic numbers:
?- firstN_palindromicnumbers(N,[1,2,3,4,5]).
N = 5 ;
false.
?- firstN_palindromicnumbers(N,[0|_]).
false.
?- firstN_palindromicnumbers(N,[1,2,3,4,11]).
false.
And the most general query yields the expected answers as well:
?- firstN_palindromicnumbers(N,PNs).
N = 0,
PNs = [] ;
N = 1,
PNs = [1] ;
N = 2,
PNs = [1, 2] ;
N = 3,
PNs = [1, 2, 3] ;
.
.
.

Related

using greedy algorithm search in lists

Given a list of positive integer Items whose elements are guaranteed to be in sorted ascending order, and a positive integer Goal, and Output is a list of three elements [A,B,C] taken from items that together add up to goal. The Output must occur inside the items list in that order (ascending order).
ex:
?- threeSum([3,8,9,10,12,14],27,Output).
Output=[8,9,10];
Output=[3,10,14].
someone helped me to reach this to this code
but it gives me singleton variables:[Input,Items] ,it didnt work
although iam not quite sure if this is a greedy algorithm search or not ?
threeSum(Input,Goal,[A,B,C]):-
permutation(Items, [A,B,C|Rest]),
msort([A,B,C],[A,B,C]),
msort(Rest,Rest),
sum_list([A,B,C],Goal).
A clpfd approach:
:- use_module(library(clpfd)).
threeSum(Input, Goal, [A,B,C]) :-
Input = [First|Rest],
foldl([N,M,T]>>(T = N\/M), Rest, First, Domain),
[A,B,C] ins Domain,
all_different([A,B,C]),
chain([A,B,C], #>=),
Goal #= A + B + C,
labeling([max(A), max(B), max(C)], [A,B,C]).
Which has a bit of wrangling to turn the list of numbers into a domain, then says [A,B,C] must be in the list of numbers, must be different numbers, must be in descending order, must sum to the goal, and the clpfd solver should strive to maximise the values of A then B then C. (This probably won't work if the list can contain multiple of the same value like [5,5,5,3,2]).
e.g.
?- threeSum([3,8,9,10,12,14], 27, Output).
Output = [14, 10, 3] ;
Output = [10, 9, 8]
nums_goal_answer(Input, Goal, [A,B,C]) :-
length(Input, InputLen),
reverse(Input, RInput), % 'greedy' interpreted as 'prefer larger values first'.
% and larger values are at the end.
between( 1, InputLen, N1),
between(N1, InputLen, N2), % three nested for-loops equivalent.
between(N2, InputLen, N3),
\+ N1 = N2, % can't pick the same thing more than once.
\+ N2 = N3,
nth1(N1, RInput, A, _),
nth1(N2, RInput, B, _),
nth1(N3, RInput, C, _),
sum_list([A,B,C], Goal).
someone helped me to reach this to this code but it gives me singleton variables:[Input,Items], it didnt work
The warning is because the code never looks at the numbers in the Input list. Without doing that, how could it ever work?
although iam not quite sure if this is a greedy algorithm
is it taking the biggest things first? I don't think permutation will do that.
Using DCG:
:- use_module(library(dcg/basics)).
three_sum_as_dcg(Total, Lst, LstThree) :-
phrase(three_sum_dcg(3, Total), Lst, LstThree).
% When finished, remove the remainder, rather than add to LstThree
three_sum_dcg(0, 0) --> remainder(_).
three_sum_dcg(NumsLeft, Total), [N] -->
% Use this element
[N],
{ three_sum_informed_search(NumsLeft, Total, N),
succ(NumsLeft0, NumsLeft),
Total0 is Total - N
},
three_sum_dcg(NumsLeft0, Total0).
three_sum_dcg(NumsLeft, Total) -->
% Skip this element
[N],
{ three_sum_informed_search(NumsLeft, Total, N) },
three_sum_dcg(NumsLeft, Total).
three_sum_informed_search(NumsLeft, Total, N) :-
NumsLeft > 0,
% "Informed" search calc due to list nums not decreasing
Total >= (N * NumsLeft).
Result in swi-prolog (note the efficiency):
?- numlist(1, 1000000, L), time(findall(L3, three_sum_as_dcg(12, L, L3), L3s)).
% 546 inferences, 0.000 CPU in 0.000 seconds (97% CPU, 4740036 Lips)
L3s = [[1,2,9],[1,3,8],[1,4,7],[1,5,6],[2,3,7],[2,4,6],[3,4,5]].
Restating the problem statement:
Given that I have
A [source] list of positive integers, whose elements are guaranteed to be sorted in ascending order, and
a positive integer indicating the target value.
I want to find
an ordered subset of elements of the source list that sum to the target value
The simplest way is often the easiest (and the most general):
sum_of( _ , 0 , [] ) . % nothing adds up to nothing.
sum_of( [X|Xs] , S , [X|Ys] ) :- % otherwise...
S > 0 , % - if the target sum S is positive,
X =< S , % - and the head of the list is less than or equal to the target sum
S1 is S-X , % - remove that amount from the target sum, and
sum_of(Xs,S1,Ys) . % - recurse down with the new target sum
sum_of( [_|Xs] , S , Ys ) :- % then, on backtracking...
S > 0 , % - assuming that the target sum is positive,
sum_of(Xs,S,Ys). % - recurse down again, discarding the head of the list
This will find whatever combinations of however many list elements sum to the target value. It will find them from left to right, so
sum_of( [1,2,3,4,5,6,7,8,9], 10, L ).
will, on backtracking successively find
L = [ 1, 2, 3, 4 ]
L = [ 1, 2, 7 ]
L = [ 1, 3, 6 ]
L = [ 1, 4, 5 ]
L = [ 1, 9 ]
L = [ 2, 3, 5 ]
L = [ 2, 8 ]
L = [ 3, 7 ]
L = [ 4, 6 ]
If you want to change the order so it finds the largest values first, simply reverse the order of clauses 2 and 3 in sum_of/3:
sum_of( _ , 0 , [] ) .
sum_of( [_|Xs] , S , Ys ) :-
S > 0 ,
sum_of(Xs,S,Ys) .
sum_of( [X|Xs] , S , [X|Ys] ) :-
S > 0 ,
X =< S ,
S1 is S-X ,
sum_of(Xs,S1,Ys) .
Now it will return the same set of solutions, just in the reverse order, starting with [4,6] and finishing with [1,2,3,4].
Once you have solved the general problem, it's a simple matter of restricting it to a specified number of elements, for instance:
sum_of_n_elements(Xs,N,S,Ys) :- length(Ys,N), sum_of(Xs,S,Ys).
And to get just the 3-element subsets that sum to the target value:
sum_of_3_elements(Xs,S,Ys) :- sum_of_n_elements(Xs,3,S,Ys) .
https://swish.swi-prolog.org/p/XKjdstla.pl

How to count nth prime in prolog

I'm quite new to prolog and I am trying to write a predicate which gives the value of nth prime number and it looks like nth_prime(N, Prime) .
I have already done the function that counts if the number is prime or not
div(X, Y):- 0 is X mod Y.
div(X, Y):- X>Y+1, Y1 is Y+1, div(X, Y1).
prime(2):- true.
prime(X):- X<2, false.
prime(X):- not(div(X, 2)).
I don't understand what is my next step, and how I should count which prime belong to N.
Your code is a bit unusual for prolog but (with the exception of prime(1)) it works.
Here is a solution for your predicate:
nextprime(N,N):-
prime(N),
!.
nextprime(P, Prime):-
PP is P+1,
nextprime(PP,Prime).
nthprime(1, 2).
nthprime(N, Prime):-
N>1,
NN is N-1,
nthprime(NN, PrevPrime),
PP is PrevPrime+1,
nextprime(PP, Prime).
?- nthprime(1,P).
P = 2 ;
false.
?- nthprime(2,P).
P = 3 ;
false.
?- nthprime(3,P).
P = 5 ;
false.
It works as follows: It is known that the first prime number is 2 (nthprime(1, 2).). For every other number N larger than 1, get the previous prime number (nthprime(NN, PrevPrime)), add 1 until you hit a prime number. The add 1 part is done through a help predicate nextprime/2: for a given number P it will check if this number is a prime. If yes, it returns this number, otherwise it will call itself for the next higher number (nextprime(PP,Prime)) and forwards the output. The bang ! is called a cut which cuts the other choice branches. So if you once hit a prime, you can not go back and try the other path.
To test it you can ask ?- nthprime(N,P). for a given N. Or to check multiple answers at once, let's introdice a helperpredicate nthprimeList/2 which calls nthprime/2 for every item in the firstlist and puts the "output" into a list:
nthprimeList([],[]).
nthprimeList([N|TN],[P|TP]):-
nthprime(N,P),
nthprimeList(TN,TP).
?- nthprimeList([1,2,3,4,5,6,7,8,9],[P1,P2,P3,P4,P5,P6,P7,P8,P9]).
P1 = 2,
P2 = 3,
P3 = 5,
P4 = 7,
P5 = 11,
P6 = 13,
P7 = 17,
P8 = 19,
P9 = 23;
false.
Using your definitions, we define the following to count up and test all numbers from 2 and up, one after another:
nth_prime(N, Prime):-
nth_prime(N, Prime, 1, 2). % 2 is the candidate for 1st prime
nth_prime(N, P, I, Q):- % Q is I-th prime candidate
prime(Q)
-> ( I = N, P = Q
; I1 is I+1, Q1 is Q+1, nth_prime(N, P, I1, Q1)
)
; Q1 is Q+1, nth_prime(N, P, I, Q1).
Testing:
30 ?- nth_prime(N,P).
N = 1,
P = 2 ;
N = 2,
P = 3 ;
N = 3,
P = 5 ;
N = 4,
P = 7 ;
N = 5,
P = 11 .
31 ?- nth_prime(N,P), N>24.
N = 25,
P = 97 ;
N = 26,
P = 101 ;
N = 27,
P = 103 .
32 ?- nth_prime(N,P), N>99.
N = 100,
P = 541 ;
N = 101,
P = 547 ;
N = 102,
P = 557 .

How to sum up multiple lists in Prolog

This is a problem suma( [ [ 1, 2, 3, 4 ], [ 2, 3, 4, 5 ], [ 3, 4, 5, 6 ] ], X ), and i need to get this result X = [ 10, 14, 18 ]. I don't have any idea how to figure this out. Please help
maplist/3 and foldl/4 and yall notation (the last one available in SWI-Prolog) are your friends.
suma(ListOfLists,ListOfSums) :-
maplist(
([Sublist,Sum]>>
(foldl(
[AccumIn,X,AccOut]>>(AccOut is AccumIn + X),
Sublist,
0,
Sum))),
ListOfLists,
ListOfSums).
Thus:
?- suma( [ [ 1, 2, 3, 4 ], [ 2, 3, 4, 5 ], [ 3, 4, 5, 6 ] ], X ).
X = [10, 14, 18].
This is less logic programming than functional programming, but if one has a Swiss Army Knife, one might as well use it!
maplist/3: Calls the goal that is on argument position 0 for every pair [Sublist,Sum] where Sublist is an element of the list on argument position 1 (i.e. ListOfLists) and Sum is an element of the list on argument position 2 (i.e. ListOfSums), both elements being at the same position in their respective lists.
The goal called takes [Sublist,Sum] and calls foldl/4, which "folds-left" the list Sublist using the goal on argument position 0, starting with value 0 and resulting in value Sum.
The folding operation is simply arithmetic addition via [AccumIn,X,AccOut]>>(AccOut is AccumIn + X).
This can be more extensively written as:
suma(ListOfLists,ListOfSums) :-
maplist(
p2, % will be called with 2 parameters
ListOfLists,
ListOfSums).
p2(Sublist,Sum) :-
foldl(
p3, % will be called with 3 parameters
Sublist,
0,
Sum).
p3(AccumIn,X,AccOut) :-
AccOut is AccumIn + X.
We can run some plunit test cases for good measure (actually, the problem to solve should be stated with the below, TDD and all that):
:- begin_tests(sum_over_sublists).
test("empty list of lists",true(R == [])) :-
suma([],R).
test("all sublists contain one value",true(R == [1,2,3])) :-
suma([[1],[2],[3]],R).
test("one sublist is empty",true(R == [1,0,3])) :-
suma([[1],[],[3]],R).
test("standard case #1",true(R == [6,15,24])) :-
suma([[1,2,3],[4,5,6],[7,8,9]],R).
test("standard case #2",true(R == [10,14,18])) :-
suma([[1,2,3,4],[2,3,4,5],[3,4,5,6]],R).
:- end_tests(sum_over_sublists).
And so:
?- run_tests.
% PL-Unit: sum_over_sublists ..... done
% All 5 tests passed
true.
%! sum(Xs,SUM)
%
% calculate the total sum of the items in list `Xs` .
sum(Xs,SUM)
:-
sum(Xs,0,SUM)
.
sum([],SUM0,SUM0) .
sum([X0|Xs],SUM0,SUM)
:-
SUM1 is SUM0 + X0 ,
sum(Xs,SUM1,SUM)
.
/*
?- sum([1,2,3,4],SUM).
SUM = 10.
?- sum([2,3,4,5],SUM).
SUM = 14.
?- sum([3,4,5,6],SUM).
SUM = 18.
*/
%! suma(Xss0,SUM)
%
% calculate the total sum of the items in list of lists `Xss` .
suma([],0) .
suma([Xs0|Xss0],SUM)
:-
sum(Xs0,SUM0) ,
suma(Xss0,SUM1) ,
SUM is SUM0 + SUM1
.
/*
?- suma([[1,2,3,4],[2,3,4,5]],SUM).
SUM = 24.
?- suma([[1,2,3,4],[2,3,4,5],[3,4,5,6]],SUM).
SUM = 42.
*/

First N Fibonacci Numbers in Prolog

I want to generate the 1st N fibonacci numbers in Prolog. That means whenever I will give N = 5, it should print : 0,1,1,2,3, But whenever I run it suppose with N =5 then it gives output as : 1,2,1,3,1,2,5.
Below is my program:
fib(0,0).
fib(1,1).
fib(F,N) :-
N>1,
N1 is N-1,
N2 is N-2,
fib(F1,N1),
fib(F2,N2),
F is F1+F2,
format('~w, ',[F]).
Just so we're all on the same page, this is what happens when running your code with N = 5:
?- fib(Fib, 5).
1, 2, 1, 3, 1, 2, 5,
Fib = 5 ;
false.
You are trying to print results rather than computing a data structure (a list) of the results. This is almost always not the way to go in Prolog.
(As an aside, the usual order of arguments in Prolog is "inputs" first, then "outputs". I believe most Prolog programmers would expect this predicate to be fib(N, Fib) rather than fib(Fib, N). We'll continue with your version, but it is confusing!)
One of the problems with printing intermediate results is that it can be difficult to understand which results are printed, and in which order. We can change your printing goal to be a bit more explicit about that is going on:
format('computed fib(~w, ~w)~n',[F, N]).
This gives:
?- fib(Fib, 5).
computed fib(1, 2)
computed fib(2, 3)
computed fib(1, 2)
computed fib(3, 4)
computed fib(1, 2)
computed fib(2, 3)
computed fib(5, 5)
Fib = 5 ;
false.
As you can see, this "naive" Fibonacci computation computes intermediate results several times, which is why you get more outputs than you expected. For example (in functional notation), computing fib(4) will compute fib(2) and fib(3), but computing fib(5) will also compute fib(3) separately.
If you remove the printing, your predicate does work correctly, for example:
?- fib(Fib, 4).
Fib = 3 .
?- fib(Fib, 5).
Fib = 5 .
?- fib(Fib, 6).
Fib = 8 .
?- fib(Fib, 7).
Fib = 13 .
There are several ways of getting the results into a list if you really want. For example, using some predicates from the SWI-Prolog library:
?- numlist(1, 20, Ns), maplist(fib, Fibs, Ns).
Ns = [1, 2, 3, 4, 5, 6, 7, 8, 9|...],
Fibs = [1, 1, 2, 3, 5, 8, 13, 21, 34|...] ;
false.
There are several problems with this: Do you really want a list? Prolog's backtracking for computing results one after the other is often superior to computing a list of results "all at once". More importantly, this naive Fibonacci implementation is very very inefficient. The above goal takes over a second on my machine.
From "Approach 3" on this answer, completely reviewed here:
At
rosettacode.org,
under Fibonacci/Prolog, the following quite interesting solution is
given. It uses a "lazy list", which is an open list (a list where the
termination (the "fin") is not [] but an unbound variable), where a
"frozen goal" is attached to the list-terminating unbound variable using
the predicate
freeze/2.
The frozen goal is run (a "coroutine") whenever the value of that
unbound variable is needed.
Proceed "bottom-up" with a "lazy list" as cache. The "lazy list"
is an open list that has a frozen goal to compute the next list
entry on its "fin".
Retrieving a member of the list using nth0(N,Cache,F) causes unification of the unbound "fin" with a new listbox [|]. This
thaws the goal on the "fin", which then computes the next
Fibonacci number, unifies it with arg1 of the listbox and then
sets up a new frozen goal on arg2 of the listbox, the
% new "fin" of the lazy list.
It is not directly evident why this works with nth0/3, so a replacement predicate retrieve/3 which also prints debugging messages has been provided.
Example:
?- debug(fib_bll).
?- fib_bottomup_lazylist_cache(10,F,Cache).
% At this point, the cache just contains [0,1|_]: [0,1|_28196]
% At K = 0, N = 10, No unfreeze at this point
% At K = 1, N = 10, No unfreeze at this point
% At K = 2, N = 10, Will call unification with a listbox that will unfreeze the goal
% Unfrozen: FA = 0, FB = 1, FIN has been unified to [1|_28628]
% At K = 3, N = 10, Will call unification with a listbox that will unfreeze the goal
% Unfrozen: FA = 1, FB = 1, FIN has been unified to [2|_28910]
% At K = 4, N = 10, Will call unification with a listbox that will unfreeze the goal
% Unfrozen: FA = 1, FB = 2, FIN has been unified to [3|_29192]
% At K = 5, N = 10, Will call unification with a listbox that will unfreeze the goal
% Unfrozen: FA = 2, FB = 3, FIN has been unified to [5|_29474]
% At K = 6, N = 10, Will call unification with a listbox that will unfreeze the goal
% Unfrozen: FA = 3, FB = 5, FIN has been unified to [8|_29756]
% At K = 7, N = 10, Will call unification with a listbox that will unfreeze the goal
% Unfrozen: FA = 5, FB = 8, FIN has been unified to [13|_30038]
% At K = 8, N = 10, Will call unification with a listbox that will unfreeze the goal
% Unfrozen: FA = 8, FB = 13, FIN has been unified to [21|_30320]
% At K = 9, N = 10, Will call unification with a listbox that will unfreeze the goal
% Unfrozen: FA = 13, FB = 21, FIN has been unified to [34|_30602]
% At K = 10, N = 10, Will call unification with a listbox that will unfreeze the goal
% Unfrozen: FA = 21, FB = 34, FIN has been unified to [55|_30884]
% Unfrozen: FA = 21, FB = 34, FIN has been unified to [55|_30884]
% F = 55,
% Cache = [0,1,1,2,3,5,8,13,21,34,55|_31458],
% freeze(_31458,fibonacci_algorithms:bll_frozen(34,55,_31458)).
Note that for call to retrieve/3, where K==N, the same debug
message is issued twice. This is because
retrieve_3(K,N,[_|More],F) is attempted first, leading to
thawing, but then a rollback is issued due to K<N, and the
frozen goal is reinstated. The second clause
retrieve_3(N,N,[F|_],F) is then attempted, leading to the same
thawing. Side-effects in Prolog: interesting.
This approach allows you to widen the cache on request, too.
For example,
This approach allows you to widen the cache on request, too. For
example, if I want fib(10) first, but then also fib(13) I can just reuse the cache, lengthening it:
?-
fibb_bottomup_lazylist_cache(10,Fib10,Cache),nth0(13,Cache,Fib13).
Fib10 = 55,
Cache = [0,1,1,2,3,5,8,13,21,34,55,89,144,233|_55906],
Fib13 = 233,
freeze(_55906,fibonacci_algorithms:bll_frozen(144,233,_55906)).
Note the residual goal being printed out.
% Carve the constants fib(0) and fib(1) out of the code.
const(fib0,0).
const(fib1,1).
% :- debug(fib_bll). % Uncomment to allow debugging printout
fib_bottomup_lazylist_cache(N,F,Cache) :-
const(fib0,F0),
const(fib1,F1),
Cache=[F0,F1|Fin],
freeze(
Fin,
bll_frozen(F0,F1,Fin)),
debug(fib_bll,"At this point, the cache just contains [0,1|_]: ~q",Cache),
% nth0(N,Cache,F).
retrieve(N,Cache,F).
bll_frozen(FA,FB,FIN) :-
FC is FA + FB,
FIN=[FC|NewFIN],
debug(fib_bll,"Unfrozen: FA = ~d, FB = ~d, FIN has been unified to ~q",[FA,FB,FIN]),
freeze(
NewFIN,
bll_frozen(FB,FC,NewFIN)).
% A replacement for nth0/3 to show what's going on
retrieve(N,Cache,F) :-
retrieve_2(0,N,Cache,F).
retrieve_2(K,N,Cache,F) :-
(var(Cache)
-> debug(fib_bll,"At K = ~d, N = ~d, Will call unification with a listbox that will unfreeze the goal",[K,N])
; debug(fib_bll,"At K = ~d, N = ~d, No unfreeze at this point",[K,N])),
retrieve_3(K,N,Cache,F).
retrieve_3(K,N,[_|More],F) :-
K < N,
!,
Kp is K+1,
retrieve_2(Kp,N,More,F).
retrieve_3(N,N,[F|_],F).

clpfd - generate the list of all integers between 5 and 10

I'm working with SWI-Prolog to get clpfd generate the list of all distinct integers between 5 and 10:
q1(Answer) :-
length(Xs, Answer),
Xs ins 0..20,
chain(Xs, #<),
maplist(q1constraints, Xs).
q1constraints(X) :-
X #>= 5,
X #=< 10.
Kind of works, but generates a solution for each of the lengths 0, 1, ... 6 and then hangs seeking a solution of length 7:
?- q1(Answer).
Answer = 0 ;
Answer = 1 ;
Answer = 2 ;
Answer = 3 ;
Answer = 4 ;
Answer = 5 ;
Answer = 6 ;
<hangs>
Is there a good way to generate the list of all integers that satisfy the desired constraints?
Your question is not that clear to me. But I will try:
?- length(Xs,6), Xs ins 5..10, chain(Xs,#<), Xs = [5|_], last(Xs, 10).
Xs = [5,6,7,8,9,10].
Note that with these elements, it is necessary to fix the length of the list first. Otherwise:
?- length(Xs,N), Xs ins 5..10, chain(Xs,#<), Xs = [5|_], last(Xs, 10).
Xs = [5,10], N = 2
; Xs = [5,_A,10], N = 3, _A in 6..9
; Xs = [5,_A,_B,10], N = 4, _A#=<_B+ -1, _A in 6..8, _B in 7..9
; Xs = [5,_C,_A,_B,10], N = 5, _A#=<_B+ -1, _C#=<_A+ -1, _A in 7..8, _C in 6..7, _B in 8..9
; Xs = [5,6,7,8,9,10], N = 6
; loops.
In fact, even the (ins)/2 is not needed:
?- length(Xs,6), chain(Xs,#<), Xs = [5|_], last(Xs, 10).
Xs = [5,6,7,8,9,10].
(In newer versions of clpfd called clpz the argument order of chain/2` is reversed adhering to the common argument ordering.)
Here is what your program does:
Generate a list of increasing lengths, starting with an empty list
For each element X in the list, pose a constraint that X is in [0, 20]
For the whole list, pose a constraint that values are strictly increasing in magnitude
For each element in the list, pose an additional constraint that X is in [5, 10].
You then ask for the length of the generated list.
There are 6 values that are in [0, 20] and in [5,10]: 5, 6, 7, 8, 9, 10. For the empty list you generate first, there are no constrained variables; for the list with 1 variable, there would be 6 possible values of the variable, but you don't ask for these values, only for the length of the list; for the list with 2 variables, you will have 5 possible combinations: {5,6}, {6,7}, ..., {9,10}, but again, you don't ask for them, just for the length of the list.
Eventually, you get to list with 7 values. Since there are only 6 values that each element could have, there are no solutions.
So what is your goal here? Maybe you should try and explain better. To get all values between 5 and 10 by backtracking, you could say: between(5, 10, X), or, with CLPFD, X in 5..10, label([X]). If it is neither of these, you need to re-write your question.
If you want the total number of even integers in 5..10 (SPOILER: there are 3 of them!):
?- aggregate(count, X^(X in 5..10, X mod 2 #= 0, indomain(X)), Answer).
Answer = 3.
Breaking it down:
X in 5..10, X mod 2 #= 0 just constrains X to be an even integer between 5 and 10:
?- X in 5..10, X mod 2 #= 0.
X in 6..10,
X mod 2#=0.
indomain(X) does the actual search, succeeding once for each feasible value of X:
?- X in 5..10, X mod 2 #= 0, indomain(X).
X = 6 ;
X = 8 ;
X = 10.
X^(...) existentially quantifies X within the parentheses, limiting its scope. If we instead leave it as a free variable, aggregation will respect it:
?- aggregate(count, (X in 5..10, X mod 2 #= 0, indomain(X)), Answer).
X = 6,
Answer = 1 ;
X = 8,
Answer = 1 ;
X = 10,
Answer = 1.

Resources