sudoku solver in prolog without clpfd - prolog

I have an AI project in which I should make a sudoku solver in Prolog but without using the clpfd package. How should I write the code and is there any way to print whenever a variable gets a value?

Without clpfd, you have to write a classic generate-and-test search. The nice thing about clpfd is that the constraints limit the search space. You can emulate this without using clpfd though. Let's simplify the task a bit so I can illustrate. How can you find X and Y values that solve both of these equations: X + Y = 10, 2*X + Y - 1 = 15?
First, encode your two equations:
eq1(X,Y) :- 10 is X + Y.
eq2(X,Y) :- 15 is 2*X + Y - 1.
Now create your search space in a solver predicate:
solution(X, Y) :-
between(1, 10, X), between(1, 10, Y),
eq1(X,Y),
eq2(X,Y).
Now you can run it and see:
?- solution(X,Y).
X = 6,
Y = 4 ;
false.
This is less efficient than it would be with clpfd because clpfd would notice things about the equations that would help it constrain the search space:
?- [library(clpfd)].
true.
?- X + Y #= 10, 2*X + Y - 1 #= 15.
2*X+Y#=16,
X+Y#=10.
?- X + Y #= 10, 2*X + Y - 1 #= 15, X in 1..10.
X = 6,
Y = 4.
See, it has already figured out that there is only one solution and I didn't have to constrain Y at all. That's very impressive! But you can still use Prolog without clpfd, it's just worse. :) In this example, we probably tried all 10x10=100 possible combinations to find this one solution. Less efficient. But not impossible.
So, what are the constraints you have to figure out for sudoku? Probably something like this:
unique(Row) :- sort(Row, Sorted), length(Row, Length), length(Sorted, Length).
all_digits(Row) :- forall(between(1,9,X), memberchk(X, Row)).
And so forth.
Edit: Combinatorial complexity estimation
Suppose we do a totally unprincipled search: that is, we even try obviously wrong cases like a grid of all 9s. We have 9x9=81 cells and 9 possible values (1-9). This yields 9^81 = a very large number, unlikely to be checked in your lifetime. And most of those grids are going to be fruitless permutations.
Suppose you constrain your search so that each row is a permutation of 1-9. There are 9! permutations of 1-9; with nine of those, you can multiply that outcome by nine, so there should be 9!^9. This is still awful! clpfd is probably able to further winnow this down by combining the 3x3 grid constraints; I'm not sure how I would go about doing that manually, other than in a semi-procedural way, choosing a 3x3 grid permutation and then passing each 3x1 row of that on to the next 3x3 grid selection.
It's worth noting that most of the optimization in classic Prolog programs comes down to either making the generate step generate better-qualified candidates or making the test step less expensive. A more obvious implementation can still be useful for checking a more complex implementation.
Thanks to #mat for checking my math and recommending this excellent article on the combinatorial problem of Sudoku.

Related

Get a value from residual goals

If I have X #> 3. Prolog will give the residual goal X in 4..sup.. How can I assign X one of the possible values from 4 to sup? Any random value will suffice.
In SWI-Prolog,you can get random value assign with using secret option random_value(Seed).
see this:How does `random_variable `random_value` work in SWI-Prolog's labeling/2?
:- use_module(library(clpfd)).
random_labeling_test(A):-
A in 1..5,
labeling([random_value(332)],[A]).
?- random_labeling_test(A).
A = 5 ;
A = 1 ;
A = 2 ;
A = 4 ;
A = 3.
332 is meaningless.Set random seed into here.current milliseconds is often used .
I'm not sure this option is safe.
But in your case,this cannot work because upper bounds is infinite.It is reasonable.
In ECLiPSe, labeling variable selection and assigning value selection is completly controllable with using indomain and delete.
see this:http://eclipseclp.org/doc/tutorial/tutorial088.html
One naive way to solve this is to use a predicate like this:
enumeration(Z) :-
length(_, N),
enumeration_(N, Z).
enumeration_(N, N).
enumeration_(N0, N) :- N #= -N0.
You can now solve your task as follows:
?- X #> 3, enumeration(X).
X = 4 ;
X = 5 ;
X = 6 ;
X = 7 ;
X = 8 .
Pros:
a quite simple solution
portable to different Prolog systems.
Con:
potentially quite slow.
Example:
?- X #> 2^100, enumeration(X).
[waiting...]
To make this more efficient, you need to take into account the actual domains of variables.
There are at least two ways to do this:
(a) Use your solver's reflection predicates
Reflection predicates let you reason about the actual domains of variables by making them available as Prolog terms.
For example, where available, you can use fd_inf/2 to obtain the infimum of a constrained variable's domain:
?- X #> 3, fd_inf(X, Inf).
Inf = 4,
X in 4..sup.
You can use this as a starting point for the enumeration. I leave this as a challenge.
See your Prolog system's manual for more information about its reflection predicates.
(b) Inspect the residual goals
Alternatively, you can inspect the residual goals as Prolog terms. This is also a reflection mechanism, though one that only needs a single predicate for all kinds of different constraint solvers.
For example, where available, you can use copy_term/3 to obtain the residual goals as a list of Prolog goals:
?- X #> 3, copy_term(X, X, Gs).
Gs = [clpfd:(X in 4..sup)],
X in 4..sup.
From these goals, it is again straight-forward to deduce the infimum of X's domain.
Note that the top-level can use this same mechanism to actually produce the residual goals.

Optimisation in swi prolog

Say I want to find argmax(x,y,z) -1/2(20x^2+32xy +16y^2)+2x+2y.
subject to:
x>=0, y>=0,z>=0 and -x-y+z =0.
I know the partial derivatives being set to 0 is :
-20x-16y+2=0 and -16x-16y+2 =0
so we could have x= 0 and y =1/8 and z=1/8.
How would I do this in Swi-prolog? I see that there is library simplex for linear solving, but this is a quadratic problem but the partial derivatives are not. (I am a bit confused!)
This is what I have:
:- use_module(library(simplex)).
my_constraints(S):-
gen_state(S0),
constraint([-20*x, -16*y] = 0, S0, S1),
constraint([-16*x,-16*y] = 0, S1,S2),
constraint([x] >= 0,S2,S3),
constraint([y] >= 0,S3,S4),
constraint([z] >= 0,S4,S5),
constraint([-x-y+z] = 0,S5,S).
?- my_constraints(S), variable_value(S,x,Val1),variable_value(S,y,Val2).
false.
There are several issues here. First, just to get this out of the way: library(simplex) can only handle linear constraints. So yes, it cannot—at least not directly—be used to solve your actual problem.
But library(simplex) is often useful regardless, and so I want to quickly point out the following:
variable_value/3 only works on the solved tableau. This means that you must have invoked maximize/3 first.
For example:
?- my_constraints(S), maximize([x,y], S, Max), variable_value(Max, x, X).
S = ...,
Max = ...,
X = 0.
Note that you must change the final goal of my_constraint/1 to constraint([-1*x, -1*y,z] = 0, S5, S) to conform to the syntax required by this library.
That being said, let us now get to the core of the issue: There are well-known ways to iteratively solve quadratic optimization problems, using a series of linear programs and reasoning about gradients to get closer to a solution. Thus, library(simplex) can indirectly still be used to solve your problem.
In particular, check out the method of steepest ascent available from miscellaneous programs. It includes a small symbolic derivative calculator written in Prolog. Yes, it's "symbolic" ;-)
Plugging in your task, I get:
?- maximize(- 0.5*(20*x(1)^2 + 32*x(1)*x(2) + 16*x(2)^2) + 2*x(1) + 2*x(2),
[[-1,0,0],
[0,-1,0],
[0,0,-1],
[-1,-1,1],
[1,1,-1]],
[0,0,0,0,0],
[0,0,0], Max).
Max = [4.298588509886033e-17, 0.125, 0.12500000000000006] ;
false.
Which is, up to the unbearable nastiness of floating point arithmetic, something that I hope you can work with.

Prolog Use of Cuts

I am re-writing the following function in Prolog:
V1:
f(X,Y):- X < 2, Y is X+1.
f(X,3):- 2 =< X, X < 5.
f(X,Y):- 5 =< X, Y is 8-X.
As V2:
f(X,Y) :-
X < 2,
Y is X + 1.
f(X,Y) :-
X >= 2,
X < 5,
Y is 3.
f(X,Y) :-
X >= 5,
Y is 8-X.
I then wanted to experiment with cuts. For green cuts (V3):
f(X,Y) :-
X < 2, !,
Y is X + 1.
f(X,Y) :-
X >= 2,
X < 5, !,
Y is 3.
f(X,Y) :-
X >= 5,
Y is 8-X.
For red cuts (V4):
f(X,Y) :-
X < 2, !,
Y is X + 1.
f(X,Y) :-
X < 5, !,
Y is 3.
f(X,Y) :-
Y is 8-X.
However, I don't understand their advantage, as deleting the cuts would allow the same behaviour of the code... Any help?
All your versions V1..V4 are observationally equivalent, so you got some reasoning right. Still, there are differences.
Avoiding superfluous choice points
In many implementations, V1 and V2 might be particularly less efficient, for, internally, they "leave open a choice point". This is so because such Prologs do not look any further to the other rules. So each goal f(1,X) consumes a bit of memory that can be freed only on backtracking (or using !). Here is a simple way to try this out yourself:
loop(Goal) :-
Goal,
loop(Goal).
Here is what I get in SWI:
?- time(loop(f1(1,2))).
% 5,991,554 inferences, 81.282 CPU in 81.443 seconds (100% CPU, 73713 Lips)
ERROR: Out of local stack
?- time(loop(f2(1,2))).
% 5,991,553 inferences, 85.032 CPU in 85.212 seconds (100% CPU, 70462 Lips)
ERROR: Out of local stack
Whereas V3 and V4 seem to run indefinitely - at least much longer than 85s. Experiments such as this one are funny for very tiny programs but are not very practical for bigger ones. Fortunately, there is a simple way to tell in many Prologs whether or not a query is executed determinately. To see if your system does this, enter:
?- X = 1.
X = 1.
For your variations:
?- f1(1,2).
true
; % <== Prolog asked for another answer
false. % <== only to conclude that there is none.
?- f2(1,2).
true
; false. % same again
?- f3(1,2).
true. % <== Prolog knows there will be no further answer
?- f4(1,2).
true.
Avoiding recalculations - making cuts red
While V3 avoids superfluous choice points, V4 now even avoids superfluous calculations. So it should be the most efficient. But it comes at the price of fixing the order of the clauses.
However, V3 was only possible, because two necessary conditions for green cuts coincided:
Non-overlapping conditions. That should be obvious to you.
Safe testing of instantiations. This is far from obvious. Please note that the goal X < 2 has an implicit test for a correct instantiation attached! It produces an instantiation error should X be an uninstantiated variable. It is because of this very test that the cut in V3 happens to be a green cut. Without that testing, it would be a red cut.
Note also that V1 and V2 would not be equivalent, if the second rule would be alone! For the goal f(X,5). would fail in V1 but it would produce an error in V2.
As you noted the first version shows green cuts and the second red cuts.
It is not necessary that you will feel the difference between these two versions.
a) one reason can be efficiency, but for toy codes with fast machines you hardly notice it.
b) shuffling the rules should not change code's behavior in case of green cuts, and that's true for the first code. But in the second code, if you put the second clause before the first one than the behavior changes: f(0,3) is true, but initially it was false. Therefore you would feel difference if you shuffle the rules.
Advantage of shuffling is that you don't care about order but content - that's one of the points declarative programing.

Combining two numbers in prolog

Kindly, could you help me in the following:
I am writing a Prolog program that takes two numbers digits then combine them as one number, for example:
Num1: 5
Num2: 1
Then the new number is 51.
Assume V1 is the first number digit and V2 is the second number digit. I want to combine V1 and V2 then multiply the new number with V3, so my question is how I can do it?
calculateR(R, E, V1, V2, V3, V4):-
R is V1 V2 * V3,
E is R * V4.
Your help is appreciated.
Here is another solution that is based on the idea of #aBathologist and that relies on ISO predicates only, and does not dependent on SWI's idiosyncratic modifications and extensions. Nor does it have most probably unwanted solutions like calculateR('0x1',1,1,17). nor calculateR(1.0e+30,0,1,1.0e+300). Nor does it create unnecessary temporary atoms.
So the idea is to restrict the definition to decimal numbers:
digit_digit_number(D1, D2, N) :-
number_chars(D1, [Ch1]),
number_chars(D2, [Ch2]),
number_chars(N, [Ch1,Ch2]).
Here is a version which better clarifies the relational nature of Prolog - using library(clpfd) which is available in many Prolog systems (SICStus, SWI, B, GNU, YAP). It is essentially the same program as the one with (is)/2 except that I added further redundant constraints that permit the system to ensure termination in more general cases, too:
:- use_module(library(clpfd)).
digits_radix_number(Ds, R, N) :-
digits_radix_numberd(Ds, R, 0,N).
digits_radix_numberd([], _, N,N).
digits_radix_numberd([D|Ds], R, N0,N) :-
D #>= 0, D #< R,
R #> 0,
N0 #=< N,
N1 #= D+N0*R,
digits_radix_numberd(Ds, R, N1,N).
Here are some uses:
?- digits_radix_number([1,4,2],10,N).
N = 142.
?- digits_radix_number([1,4,2],R,142).
R = 10.
?- digits_radix_number([1,4,2],R,N).
R in 5..sup, 4+R#=_A, _A*R#=_B, _A in 9..sup, N#>=_A,
N in 47..sup, 2+_B#=N, _B in 45..sup.
That last query asks for all possible radices that represent [1,4,2] as a number. As you can see, not anything can be represented that way. The radix has to be 5 or larger which is not surprising given the digit 4, and the number itself has to be at least 47.
Let's say we want to get a value between 1450..1500, what radix do we need to do that?
?- digits_radix_number([1,4,2],R,N), N in 1450..1500.
R in 33..40, 4+R#=_A, _A*R#=_B, _A in 37..44,
N in 1450..1500, 2+_B#=N, _B in 1448..1498.
Gnah, again gibberish. This answer contains many extra equations that have to hold. Prolog essentially says: Oh yes, there is a solution, provided all this fine print is true. Do the math yourself!
But let's face it: It is better if Prolog gives such hard-to-swallow answer than if it would say Yes.
Fortunately there are ways to remove such extra conditions. One of the simplest is called "labeling", where Prolog will "try out" value after value:
?- digits_radix_number([1,4,2],R,N), N in 1450..1500, labeling([],[N]).
false.
That is clear response now! There is no solution. All these extra conditions where essentially false, like all that fine print in your insurance policy...
Here's another question: Given the radix and the value, what are the required digits?
?- digits_radix_number(D,10,142).
D = [1,4,2]
; D = [0,1,4,2]
; D = [0,0,1,4,2]
; D = [0,0,0,1,4,2]
; D = [0,0,0,0,1,4,2]
; ... .
So that query can never terminate, because 00142 is the same number as 142. Just as 007 is agent number 7.
Here is a straight-forward solution that should work in any Prolog close to ISO:
digits_radix_to_number(Ds, R, N) :-
digits_radix_to_number(Ds, R, 0,N).
digits_radix_to_number([], _, N,N).
digits_radix_to_number([D|Ds], R, N0,N) :-
N1 is D+N0*R,
digits_radix_to_number(Ds, R, N1,N).
?- digits_radix_to_number([1,4,2],10,R).
R = 142.
Edit: In a comment, #false pointed out that this answer is SWI-Prolog specific.
You can achieve your desired goal by treating the numerals as atoms and concatenating them, and then converting the resultant atom into a number.
I'll use atom_concat/3 to combine the two numerals. In this predicate, the third argument with be the combination of atoms in its first and second arguments. E.g.,
?- atom_concat(blingo, dingo, X).
X = blingodingo.
Note that, when you do this with two numerals, the result is an atom not a number. This is indicated by the single quotes enclosing the the result:
?- atom_concat(5, 1, X).
X = '51'.
But 51 \= '51' and we cannot multiply an atom by number. We can use atom_number/2 to convert this atom into a number:
?- atom_number('51', X).
X = 51.
That's all there is to it! Your predicate might look like this:
calculateR(No1, No2, Multiplier, Result) :-
atom_concat(No1, No2, NewNoAtom),
atom_number(NewNoAtom, NewNo),
Result is NewNo * Multiplier.
Usage example:
?- calculateR(5, 1, 3, X).
X = 153.
Of course, you'll need more if you want to prompt the user for input.
I expect #Wouter Beek's answer is more efficient, since it doesn't rely on converting the numbers to and from atoms, but just uses the assumption that each numeral is a single digit to determine the resulting number based on their position. E.g., if 5 is in the 10s place and 1 is in the 1s place, then the combination of 5 and 1 will be 5 * 10 + 1 * 1. The answer I suggest here will work with multiple digit numerals, e.g., in calculateR(12, 345, 3, Result), Result is 1234 * 3. Depending on what you're after this may or may not be a desired result.
If you know the radix of the numbers involved (and the radix is the same for all the numbers involved), then you can use the reverse index of the individual numbers in order to calculate their positional summation.
:- use_module(library(aggregate)).
:- use_module(library(lists)).
digits_to_number(Numbers1, Radix, PositionalSummation):-
reverse(Numbers1, Numbers2),
aggregate_all(
sum(PartOfNumber),
(
nth0(Position, Numbers2, Number),
PartOfNumber is Number * Radix ^ Position
),
PositionalSummation
).
Examples of use:
?- digits_to_number([5,1], 10, N).
N = 51.
?- digits_to_number([5,1], 16, N).
N = 81.
(The code sample is mainly intended to bring the idea across. Notice that I use aggregate_all/3 from SWI-Prolog here. The same could be achieved by using ISO predicates exclusively.)

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