Tree methods going on infinite loop - prolog

So all of my tree code is not working properly when I instantiate my integer variables. Here's an example of what I mean:
% relates a tree and the numbe of nodes in that tree(order)
tree_order(empty,0).
tree_order(tree(_, Left_Subtree, Right_Subtree), Order) :-
Order #> 0,
Order #= Left_Subtree_Order + Right_Subtree_Order + 1,
tree_order(Left_Subtree, Left_Subtree_Order), tree_order(Right_Subtree, Right_Subtree_Order).
I'm not actually using that but here's my definition of a tree:
% Definition of a Binary Tree
tree(empty).
tree(tree(_, Left_Subtree, Right_Subtree)) :-
tree(Left_Subtree), tree(Right_Subtree).
So if run the following query tree_order(Tree, 2). it gives me a solution then when it backtracks it goes on an infinite loop. It's honestly baffling me, because I've run the program in my head a thousand times and I still can't find an answer.
One possibility is that Prolog is adding infinitely many nodes to the left of the tree and it doesn't realize that it actually leads to the tree having order greater than 2.
But if that's the case, how can I tell prolog to stop adding more than 2 nodes to the tree? I've thought about using CLP but the only methods I know reason about numerical domains and lists but not predicates.
Thanks in advance!

The reason for non-termination of tree_order(T, 2). is the following failure-slice:
tree_order(empty,0) :- false.
tree_order(tree(_, Left_Subtree, Right_Subtree), Order) :-
Order #> 0,
Order #= Left_Subtree_Order + Right_Subtree_Order + 1,
tree_order(Left_Subtree, Left_Subtree_Order), false,
tree_order(Right_Subtree, Right_Subtree_Order).
?- tree_order(T, 2).
loops.
In order to make this terminating, you need to specialize this program somehow. Like by adding T = tree(_,empty,empty) in front of the query.
Or by adding the redundant constraint Right_Subtree_Order #>=0.
Note that strictly speaking, this is no longer an example of finite domains but rather (potentially) infinite domains. Not all clpfd implementations support this. SICStus, Scryer, and SWI do support it. But only in Scryer and SWI does unification of such terms always terminate.

Better to constraint every free variable involved:
/* File: tree_order.pl
Author: Carlo,,,
Created: Oct 19 2021
Purpose: https://stackoverflow.com/q/69623834/874024
*/
:- module(tree_order,
[tree_order/2
]).
:- use_module(library(clpfd)).
% relates a tree and the number of nodes in that tree(order)
tree_order(empty, 0).
tree_order(tree(_, Left_Subtree, Right_Subtree), Order) :-
% Order #> 0, implicit given the following 3 constraints
Left_Subtree_Order #>= 0,
Right_Subtree_Order #>= 0,
Order #= Left_Subtree_Order + Right_Subtree_Order + 1,
tree_order(Left_Subtree, Left_Subtree_Order),
tree_order(Right_Subtree, Right_Subtree_Order).
yields
[debug] ?- tree_order(T,2).
T = tree(_, empty, tree(_, empty, empty)) ;
T = tree(_, tree(_, empty, empty), empty) ;
false.

Related

CLPFD ins operator yields not sufficiently instantiated error

So, my goal is to make a map colourer in Prolog. Here's the map I'm using:
And this are my colouring constraints:
colouring([A,B,C,D,E,F]) :-
maplist( #\=(A), [B,C,D,E] ),
maplist( #\=(B), [C,D,F]),
C #\= D,
maplist( #\=(D), [E,F]),
E #\= F.
Where [A,B,C,D,E,F] is a list of numbers(colors) from 1 to n.
So I want my solver to, given a List of 6 colors and a natural number N, determine the colors and N constraints both ways, in a way that even the most general query could yield results:
regions_ncolors(L,N) :- colouring(L), L ins 1..N, label(L).
Where the most general query is regions_ncolors(L,N).
However, the operator ins doesn't seem to accept a variable N, it instead yields an argument not sufficiently instantiated error. I've tried using this solution instead:
int_cset_(N,Acc,Acc) :- N #= 0.
int_cset_(N,Acc,Cs) :- N_1 #= N-1, int_cset_(N_1,[N|Acc],Cs).
int_cset(N,Cs) :- int_cset_(N,[],Cs).
% most general solver
regions_ncolors(L,N) :- colouring(L), int_cset(N,Cs), subset(L,Cs), label(L).
Where the arguments in int_cset(N,Cs) is a natural number(N) and the counting set Sn = {1,2,...,N}
But this solution is buggy as regions_ncolors(L,N). only returns the same(one) solution for all N, and when I try to add a constraint to N, it goes in an infinite loop.
So what can I do to make the most general query work both ways(for not-instantiated variables)?
Thanks in advance!
Btw, I added a swi-prolog tag in my last post although it was removed by moderation. I don't know if this question is specific to swi-prolog which is why I'm keeping the tag, just in case :)
Your colouring is too specific, you encode the topology of your map into it. Not a problem as is, but it defeats of the purpose of then having a "most general query" solution for just any list.
If you want to avoid the problem of having a free variable instead of a list, you could first instantiate the list with length/2. Compare:
?- L ins 1..3.
ERROR: Arguments are not sufficiently instantiated
ERROR: In:
ERROR: [16] throw(error(instantiation_error,_86828))
ERROR: [10] clpfd:(_86858 ins 1..3) ...
Is that the same problem as you see?
If you first make a list and a corresponding set:
?- length(L, N), L ins 1..N.
L = [],
N = 0 ;
L = [1],
N = 1 ;
L = [_A, _B],
N = 2,
_A in 1..2,
_B in 1..2 ;
L = [_A, _B, _C],
N = 3,
_A in 1..3,
_B in 1..3,
_C in 1..3 .
If you use length/2 like this you will enumerate the possible lists and integer sets completely outside of the CLP(FD) labeling. You can then add more constraints on the variables on the list and if necessary, use labeling.
Does that help you get any further with your problem? I am not sure how it helps for the colouring problem. You would need a different representation of the map topology so that you don't have to manually define it within a predicate like your colouring/1 you have in your question.
There are several issues in your program.
subset/2 is impure
SWI's (by default) built-in predicate subset/2 is not the pure relation you are hoping for. Instead, it expects that both arguments are already sufficiently instantiated. And if not, it takes a guess and sticks to it:
?- colouring(L), subset(L,[1,2,3,4,5]).
L = [1,2,3,4,2,1].
?- colouring(L), subset(L,[1,2,3,4,5]), L = [2|_].
false.
?- L = [2|_], colouring(L), subset(L,[1,2,3,4,5]), L = [2|_].
L = [2,1,3,4,1,2].
With a pure definition it is impossible that adding a further goal as L = [2|_] in the third query makes a failing query succeed.
In general it is a good idea to not interfere with labeling/2 except for the order of variables and the options argument. The internal implementation is often much faster than manual instantiations.
Also, your map is far too simple to expose subset/2s weakness. Not sure what the minimal failing graph is, but here is one such example from
R. Janczewski et al. The smallest hard-to-color graph for algorithm DSATUR, Discrete Mathematics 236 (2001) p.164.
colouring_m13([K1,K2,K3,K6,K5,K7,K4]):-
maplist(#\=(K1), [K2,K3,K4,K7]),
maplist(#\=(K2), [K3,K5,K6]),
maplist(#\=(K3), [K4,K5]),
maplist(#\=(K4), [K5,K7]),
maplist(#\=(K5), [K6,K7]),
maplist(#\=(K6), [K7]).
?- colouring_m13(L), subset(L,[1,2,3,4]).
false. % incomplete
?- L = [3|_], colouring_m13(L), subset(L,[1,2,3,4]).
L = [3,1,2,2,3,1,4].
int_cset/2 never terminates
... (except for some error cases like int_cset(non_integer, _).). As an example consider:
?- int_cset(1,Cs).
Cs = [1]
; loops.
And don't get fooled by the fact that an actual solution was found! It still does not terminate.
#Luis: But how come? I'm getting baffled by this, the same thing is happening on ...
To see this, you need the notion of a failure-slice which helps to identify the responsible part in your program. With some falsework consisting of goals false the responsible part is exposed.
All unnecessary parts have been removed by false. What remains has to be changed somehow.
int_cset_(N,Acc,Acc) :- false, N #= 0.
int_cset_(N,Acc,Cs) :- N1 #= N-1, int_cset_(N1,[N|Acc],Cs), false.
int_cset(N,Cs) :- int_cset_(N,[],Cs), false.
?- int_cset(1, Cs), false.
loops.
Adding the redundant goal N1 #> 0
will avoid unnecessary non-termination.
This alone will not solve your problem since if N is not given, you will still encounter non-termination due to the following failure slice:
regions_ncolors(L,N) :-
colouring(L),
int_cset(N,Cs), false,
subset(L,Cs),
label(L).
In int_cset(N,Cs), Cs occurs for the first time and thus cannot influence termination (there is another reason too, its definition would ignore it as well..) and therefore only N has a chance to induce termination.
The actual solution has been already suggested by #TA_intern using length/2 which liberates one of such mode-infested chores.

Prolog - confused about return results of recursive rule

I'm playing around with recursion in Prolog, and I'm confused. I am trying to write rules that can determine if a number is even or odd. I know that there are other stackoverflow questions about this, but I don't care about having a working solution, I am more interested in knowing why mine doesn't work.
Here are my rules:
even(0).
even(N) :- N>0, N1 is N-1, odd(N1).
odd(N) :- N>0, N1 is N-1, even(N1).
When I query even(0), I get returned 2 results. The first result is true, the 2nd is false. This also happens with odd(1), even(2), odd(3), etc. Why am I getting 2 return results? Shouldn't I just get 1?
When you query even(0), it succeeds as you have seen. But you've also seen it prompts you for more results because it left a choicepoint, which is a place in the logic where Prolog decides it can come back and explore other alternatives for a potentially successful query. Upon going back to the choicepoint and attempting to find more solutions, it does not find more, so it comes back "false" since it found no more solutions. So it did just find one solution, but the choice point caused backtracking after which it found no additional solutions. This is the case with your other successful queries as well.
You'll note that if you make a more general query, it gives an error (example taken from GNU Prolog):
| ?- even(N).
N = 0 ? ;
uncaught exception: error(instantiation_error,(>)/2)
| ?-
This is because you are using specific arithmetic expression operators that require that the variables be instantiated. These are relational operators like (>)/2 and the is/2 operator. You can make the solution more relational by using the CLP(FD) operators which are designed for reasoning with integers:
even(0).
even(N) :-
N #> 0,
N1 #= N-1,
odd(N1).
odd(N) :-
N #> 0,
N1 #= N-1,
even(N1).
Then you get a more general solution, which is more complete and more useful:
| ?- even(N).
N = 0 ? ;
N = 2 ? ;
N = 4 ? ;
N = 6 ? ;
...
| ?- odd(N).
N = 1 ? ;
N = 3 ? ;
N = 5 ? ;
N = 7 ?
...
If you know there is at most one answer, or if you only care about the first possible answer, you can use once/1 (examples taken from SWI Prolog here):
2 ?- even(2).
true ;
false.
3 ?- once(even(2)).
true.
4 ?- even(N).
N = 0 ;
N = 2 ;
N = 4 ;
...
5 ?- once(even(N)).
N = 0.
6 ?-
As expected, once(even(N)) terminates after finding the first solution.
The return values you have are correct. The point is how Prolog is evaluating predicates. When you query i.e.
even(2)
Prolog firstly evaluate that this predicate is Yes / true. When going through next possibility it return No / false, because it cannot find any more.
To check what exactly is performed under the hood go to:
https://swish.swi-prolog.org
on the left side type rules (i.e. odd/even) and on the query window type like 'odd(2)', but just before running click 'solutions'->'debug(trace)'. It will let you go step by step of what Prolog is doing.
Also please take a look at the successor example in tutorial below.
http://www.learnprolognow.org/lpnpage.php?pagetype=html&pageid=lpn-htmlse9
from a link above, try such code for a reversed example:
numeral(0).
numeral(succ(X)) :- numeral(X).
Now evaluating numeral(0) for the first time return succ(0), another time succ(succ(0)) etc.
Each time next evaluation brings another possible solution for a query.
What Prolog does is a "depth-first search", which means Prolog walks through a decision tree until it either finds a solution and succeeds OR it fails. In either case a process called "backtracking" kicks in. Along the way, going through the tree of choices, Prolog keeps track of where it has MULTIPLE possible routes that could potentially satisfy the goal. Such a point in the decision tree is called a "choice point".
This means Prolog will
search ->
succeed or fail ->
go back to the last choice point ->
repeat until all possible paths have been tried
Given your program:
even(0).
even(N) :- N>0, N1 is N-1, odd(N1).
odd(N) :- N>0, N1 is N-1, even(N1).
We can clearly see TWO ways to satisfy even(0).. The first is the fact even(0) and the second is the recursive rule even(N). Prolog reads top to bottom, left to right so the first encounter is even(0). which is true, and the second is even(N). which goes through N-1 making the result N1 = -1, then goes through odd(N) making the result N1 = -2, which in unequal to even(0). so it fails and then calls even(N) again. Your specific version of Prolog likely sees that it is an infinitely recursive predicate and doesn't even try to satisfy it even though it's a valid declarative path , but not a valid procedural path.
If you know that the mode is (+), you can place a cut,
to suppress the unnecessary choice point:
even(0) :- !.
even(N) :- N > 0, N1 is N-1, odd(N1).
odd(N) :- N > 0, N1 is N-1, even(N1).
The above is better than wrapping a query with
once/1 since it allows the Prolog interpreter to
use last call optimization. There is now no more
problem with an extra choice point:
?- even(3).
false.
?- even(4).
true.
But if the mode is not fixed, you have to be more careful
with cuts. Probably write a separate carefully crafted
predicate for each mode.
CLP(FD) itself seems not to help, it cannot avoid the need
to place cuts, but can sometimes avoid the need to code
different variants for different modes.

How can I verify if a coordinate is in a list

I'm generating random coordinates and adding on my list, but first I need verify if that coordinate already exists. I'm trying to use member but when I was debugging I saw that isn't working:
My code is basically this:
% L is a list and Q is a count that define the number of coordinate
% X and Y are the coordinate members
% check if the coordniate already exists
% if exists, R is 0 and if not, R is 1
createCoordinates(L,Q) :-
random(1,10,X),
random(1,10,Y),
convertNumber(X,Z),
checkCoordinate([Z,Y],L,R),
(R is 0 -> print('member'), createCoordinates(L,Q); print('not member'),createCoordinates(L,Q-1).
checkCoordinate(C,L,R) :-
(member(C,L) -> R is 0; R is 1).
% transforms the number N in a letter L
convertNumber(N,L) :-
N is 1, L = 'A';
N is 2, L = 'B';
...
N is 10, L = 'J'.
%call createCoordinates
createCoordinates(L,20).
When I was debugging this was the output:
In this picture I'm in the firts interation and L is empty, so R should be 1 but always is 0, the coordinate always is part of the list.
I have the impression that the member clause is adding the coordinate at my list and does'nt make sense
First off, I would recommend breaking your problem down into smaller pieces. You should have a procedure for making a random coordinate:
random_coordinate([X,Y]) :-
random(1, 10, XN), convertNumber(XN, X),
random(1, 10, Y).
Second, your checkCoordinate/3 is converting Prolog's success/failure into an integer, which is just busy work for Prolog and not really improving life for you. memberchk/2 is completely sufficient to your task (member/2 would work too but is more powerful than necessary). The real problem here is not that member/2 didn't work, it's that you are trying to build up this list parameter on the way out, but you need it to exist on the way in to examine it.
We usually solve this kind of problem in Prolog by adding a third parameter and prepending values to the list on the way through. The base case then equates that list with the outbound list and we protect the whole thing with a lower-arity procedure. In other words, we do this:
random_coordinates(N, Coordinates) :- random_coordinates(N, [], Coordinates).
random_coordinates(0, Result, Result).
random_coordinates(N, CoordinatesSoFar, FinalResult) :- ...
Now that we have two things, memberchk/2 should work the way we need it to:
random_coordinates(N, CoordinatesSoFar, FinalResult) :-
N > 0, succ(N0, N), % count down, will need for recursive call
random_coordinate(Coord),
(memberchk(Coord, CoordinatesSoFar) ->
random_coordinates(N, CoordinatesSoFar, FinalResult)
;
random_coordinates(N0, [Coord|CoordinatesSoFar], FinalResult)
).
And this seems to do what we want:
?- random_coordinates(10, L), write(L), nl.
[[G,7],[G,3],[H,9],[H,8],[A,4],[G,1],[I,9],[H,6],[E,5],[G,8]]
?- random_coordinates(10, L), write(L), nl.
[[F,1],[I,8],[H,4],[I,1],[D,3],[I,6],[E,9],[D,1],[C,5],[F,8]]
Finally, I note you continue to use this syntax: N is 1, .... I caution you that this looks like an error to me because there is no distinction between this and N = 1, and your predicate could be stated somewhat tiresomely just with this:
convertNumber(1, 'A').
convertNumber(2, 'B').
...
My inclination would be to do it computationally with char_code/2 but this construction is actually probably better.
Another hint that you are doing something wrong is that the parameter L to createCoordinates/2 gets passed along in all cases and is not examined in any of them. In Prolog, we often have variables that appear to just be passed around meaninglessly, but they usually change positions or are used multiple times, as in random_coordinates(0, Result, Result); while nothing appears to be happening there, what's actually happening is plumbing: the built-up parameter becomes the result value. Nothing interesting is happening to the variable directly there, but it is being plumbed around. But nothing is happening at all to L in your code, except it is supposedly being checked for a new coordinate. But you're never actually appending anything to it, so there's no reason to expect that anything would wind up in L.
Edit Notice that #lambda.xy.x solves the problem in their answer by prepending the new coordinate in the head of the clause and examining the list only after the recursive call in the body, obviating the need for the second list parameter.
Edit 2 Also take a look at #lambda.xy.x's other solution as it has better time complexity as N approaches 100.
Since i had already written it, here is an alternative solution: The building block is gen_coord_notin/2 which guarantees a fresh solution C with regard to an exclusion list Excl.
gen_coord_notin(C, Excl) :-
random(1,10,X),
random(1,10,Y),
( memberchk(X-Y, Excl) ->
gen_coord_notin(C, Excl)
;
C = X-Y
).
The trick is that we only unify C with the new result, if it is fresh.
Then we only have to fold the generations into N iterations:
gen_coords([], 0).
gen_coords([X|Xs], N) :-
N > 0,
M is N - 1,
gen_coords(Xs, M),
gen_coord_notin(X, Xs).
Remark 1: since coordinates are always 2-tuples, a list representation invites unwanted errors (e.g. writing [X|Y] instead of [X,Y]). Traditionally, an infix operator like - is used to seperate tuples, but it's not any different than using coord(X,Y).
Remark 2: this predicate is inherently non-logical (i.e. calling gen_coords(X, 20) twice will result in different substitutions for X). You might use the meta-level predicates var/1, nonvar/1, ground/1, integer, etc. to guard against non-sensical calls like gen_coord(1-2, [1-1]).
Remark 3: it is also important that the conditional does not have multiple solutions (compare member(X,[A,B]) and memberchk(X,[A,B])). In general, this can be achieved by calling once/1 but there is a specialized predicate memberchk/2 which I used here.
I just realized that the performance of my other solutions is very bad for N close to 100. The reason is that with diminishing possible coordinates, the generate and test approach will take longer and longer. There's an alternative solution which generates all coordinates and picks N random ones:
all_pairs(Ls) :-
findall(X-Y, (between(1,10,X), between(1,10,Y)), Ls).
remove_index(X,[X|Xs],Xs,0).
remove_index(I,[X|Xs],[X|Rest],N) :-
N > 0,
M is N - 1,
remove_index(I,Xs,Rest,M).
n_from_pool(_Pool, [], 0).
n_from_pool(Pool, [C|Cs], N) :-
N > 0,
M is N - 1,
length(Pool, L),
random(0,L,R),
remove_index(C,Pool,NPool,R),
n_from_pool(NPool, Cs, M).
gen_coords2(Xs, N) :-
all_pairs(Pool),
n_from_pool(Pool, Xs, N).
Now the query
?- gen_coords2(Xs, 100).
Xs = [4-6, 5-6, 5-8, 9-6, 3-1, 1-3, 9-4, 6-1, ... - ...|...] ;
false.
succeeds as expected. The error message
?- gen_coords2(Xs, 101).
ERROR: random/1: Domain error: not_less_than_one' expected, found0'
when we try to generate more distinct elements than possible is not nice, but better than non-termination.

Prevent backtracking after first solution to Fibonacci pair

The term fib(N,F) is true when F is the Nth Fibonacci number.
The following Prolog code is generally working for me:
:-use_module(library(clpfd)).
fib(0,0).
fib(1,1).
fib(N,F) :-
N #> 1,
N #=< F + 1,
F #>= N - 1,
F #> 0,
N1 #= N - 1,
N2 #= N - 2,
F1 #=< F,
F2 #=< F,
F #= F1 + F2,
fib(N1,F1),
fib(N2,F2).
When executing this query (in SICStus Prolog), the first (and correct) match is found for N (rather instantly):
| ?- fib(X,377).
X = 14 ?
When proceeding (by entering ";") to see if there are any further matches (which is impossible by definition), it takes an enormous amount of time (compared to the first match) just to always reply with no:
| ?- fib(X,377).
X = 14 ? ;
no
Being rather new to Prolog, I tried to use the Cut-Operator (!) in various ways, but I cannot find a way to prevent the search after the first match. Is it even possible given the above rules? If yes, please let me know how :)
There are two parts to get what you want.
The first is to use
call_semidet/1
which ensures that there is exactly one answer. See links for an
implementation for SICStus, too. In the unlikely event of having more
than one answer, call_semidet/1 produces a safe error. Note that
once/1 and !/0 alone simply cut away whatever there has been.
However, you will not be very happy with call_semidet/1 alone. It
essentially executes a goal twice. Once to see if there is no more
than one answer, and only then again to obtain the first answer. So
you will get your answer much later.
The other part is to speed up your definition such that above will not
be too disturbing to you. The solution suggested by CapelliC changes
the algorithm altogether which is specific to your concrete function
but does not extend to any other function. But it also describes a
different relation.
Essentially, you found the quintessential parts already, you only need
to assemble them a bit differently to make them work. But, let's start
with the basics.
CLPFD as CLP(Z)
What you are doing here is still not that common to many Prolog
programmers. You use finite domain constraints for general integer
arithmetics. That is, you are using CLPFD as a pure substitute to the
moded expression evaluation found in (is)/2, (>)/2 and the
like. So you want to extend the finite domain paradigm which assumes
that we express everything within finite given intervals. In fact, it
would be more appropriate to call this extension CLP(Z).
This extension does not work in every Prolog offering finite
domains. In fact, there is only SICStus, SWI and YAP that correctly
handle the case of infinite intervals. Other systems might fail or
succeed when they rather should succeed or fail - mostly when integers
are getting too large.
Understanding non-termination
The first issue is to understand the actual reason why your original
program did not terminate. To this end, I will use a failure
slice. That
is, I add false goals into your program. The point being: if the
resulting program does not terminate then also the original program
does not terminate. So the minimal failure slice of your (presumed)
original program is:
fiborig(0,0) :- false.
fiborig(1,1) :- false.
fiborig(N,F) :-
N #> 1,
N1 #= N-1,
N2 #= N-2,
F #= F1+F2,
fiborig(N1,F1), false,
fiborig(N2,F2).
There are two sources for non-termination here: One is that for a given
F there are infinitely many values for F1 and F2. That can be
easily handled by observing that F1 #> 0, F2 #>= 0.
The other is more related to Prolog's execution mechanism. To
illustrate it, I will add F2 #= 0. Again, because the resulting
program does not terminate, also the original program will loop.
fiborig(0,0) :- false.
fiborig(1,1) :- false.
fiborig(N,F) :-
N #> 1,
N1 #= N-1,
N2 #= N-2,
F #= F1+F2,
F1 #> 0,
F2 #>= 0,
F2 #= 0,
fiborig(N1,F1), false,
fiborig(N2,F2).
So the actual problem is that the goal that might have 0 as result
is executed too late. Simply exchange the two recursive goals. And add
the redundant constraint F2 #=< F1 for efficiency.
fibmin(0,0).
fibmin(1,1).
fibmin(N,F) :-
N #> 1,
N1 #= N-1,
N2 #= N-2,
F1 #> 0,
F2 #>= 0,
F1 #>= F2,
F #= F1+F2,
fibmin(N2,F2),
fibmin(N1,F1).
On my lame laptop I got the following runtimes for fib(N, 377):
SICStus SWI
answer/total
fiborig: 0.090s/27.220s 1.332s/1071.380s
fibmin: 0.080s/ 0.110s 1.201s/ 1.506s
Take the sum of both to get the runtime for call_semidet/1.
Note that SWI's implementation is written in Prolog only, whereas
SICStus is partly in C, partly in Prolog. So when porting SWI's (actually #mat's) clpfd to
SICStus, it might be comparable in speed.
There are still many things to optimize. Think of indexing, and the
handling of the "counters", N, N1, N2.
Also your original program can be improved quite a bit. For example,
you are unnecessarily posting the constraint F #>= N-1 three times!
If you are only interested in the first solution or know that there is at most one solution, you can use once/1 to commit to that solution:
?- once(fib(X, 377)).
+1 for using CLP(FD) as a declarative alternative to lower-level arithmetic. Your version can be used in all directions, whereas a version based on primitive integer arithmetic cannot.
I played a bit with another definition, I wrote in standard arithmetic and translated to CLP(FD) on purpose for this question.
My plain Prolog definition was
fibo(1, 1,0).
fibo(2, 2,1).
fibo(N, F,A) :- N > 2, M is N -1, fibo(M, A,B), F is A+B.
Once translated, since it take too long in reverse mode (or doesn't terminate, don't know),
I tried to add more constraints (and moving them around) to see where a 'backward' computation terminates:
fibo(1, 1,0).
fibo(2, 2,1).
fibo(N, F,A) :-
N #> 2,
M #= N -1,
M #>= 0, % added
A #>= 0, % added
B #< A, % added - this is key
F #= A+B,
fibo(M, A,B). % moved - this is key
After adding B #< A and moving the recursion at last call, now it works.
?- time(fibo(U,377,Y)).
% 77,005 inferences, 0.032 CPU in 0.033 seconds (99% CPU, 2371149 Lips)
U = 13,
Y = 233 ;
% 37,389 inferences, 0.023 CPU in 0.023 seconds (100% CPU, 1651757 Lips)
false.
edit To account for 0 based sequences, add a fact
fibo(0,0,_).
Maybe this explain the role of the last argument: it's an accumulator.

Trying to count steps through recursion?

This is a cube, the edges of which are directional; It can only go left to right, back to front and top to bottom.
edge(a,b).
edge(a,c).
edge(a,e).
edge(b,d).
edge(b,f).
edge(c,d).
edge(c,g).
edge(d,h).
edge(e,f).
edge(e,g).
edge(f,h).
edge(g,h).
With the method below we can check if we can go from A-H for example: cango(A,H).
move(X,Y):- edge(X,Y).
move(X,Y):- edge(X,Z), move(Z,Y).
With move2, I'm trying to impalement counting of steps required.
move2(X,Y,N):- N is N+1, edge(X,Y).
move2(X,Y,N):- N is N+1, edge(X,Z), move2(Z,Y,N).
How would I implement this?
arithmetic evaluation is carried out as usual in Prolog, but assignment doesn't work as usual. Then you need to introduce a new variable to increment value:
move2(X,Y,N,T):- T is N+1, edge(X,Y).
move2(X,Y,N,T):- M is N+1, edge(X,Z), move2(Z,Y,M,T).
and initialize N to 0 at first call. Such added variables (T in our case) are often called accumulators.
move2(X,Y,1):- edge(X,Y), ! .
move2(X,Y,NN):- edge(X,Z), move2(Z,Y,N), NN is N+1 .
(is)/2 is very sensitive to instantiations in its second argument. That means that you cannot use it in an entirely relational manner. You can ask X is 1+1., you can even ask 2 is 1+1. but you cannot ask: 2 is X+1.
So when you are programming with predicates like (is)/2, you have to imagine what modes a predicate will be used with. Such considerations easily lead to errors, in particular, if you just started. But don't worry, also more proficient programmers still fall prey to such problems.
There is a clean alternative in several Prolog systems: In SICStus, YAP, SWI there is a library(clpfd) which permits you to express relations between integers. Usually this library is used for constraint programming, but you can also use it as a safe and clean replacement for (is)/2 on the integers. Even more so, this library is often very efficiently compiled such that the resulting code is comparable in speed to (is)/2.
?- use_module(library(clpfd)).
true.
?- X #= 1+1.
X = 2.
?- 2 #= 1+1.
true.
?- 2 #= X+1.
X = 1.
So now back to your program, you can simply write:
move2(X,Y,1):- edge(X,Y).
move2(X,Y,N0):- N0 #>= 1, N0 #= N1+1, edge(X,Z), move2(Z,Y,N1).
You get now all distances as required.
But there is more to it ...
To make sure that move2/3 actually terminates, try:
?- move2(A, B, N), false.
false.
Now we can be sure that move2/3 always terminates. Always?
Assume you have added a further edge:
edge(f, f).
Now above query loops. But still you can use your program to your advantage!
Determine the number of nodes:
?- setof(C,A^B^(edge(A,B),member(C,[A,B])),Cs), length(Cs, N).
Cs = [a, b, c, d, e, f, g, h], N = 8.
So the longest path will take just 7 steps!
Now you can ask the query again, but now by constraining N to a value less than or equal to7:
?- 7 #>= N, move2(A,B, N), false.
false.
With this additional constraint, you have again a terminating definition! No more loops.

Resources