Reputation: 13
I'm trying to create a program which can place the maximum of knight on a n * n chess without any knight eating the other. I managed to find how to do that, however I keep getting the false result instead of the display of the list where is the solution.
:- use_module(library(lists), [member/2]).
:- use_module(contestlib, [for/3]).
genere(0,[]).
genere(N,[N|L]) :-
N>0,
N1 is N-1,
genere(N1,L).
generePos(N,[(Lig,Col)]) :-
genere(N,L),
member(Lig,L),
member(Col,L).
genereEchiquier(N,PlacedKnights) :-
findall((X,Y),(for(X,1,N),for(Y,1,N)),PlacedKnights).
knights(N) :-
genereEchiquier(N,PlacedKnights),
generePos(N,P1),
knighta(P1,PlacedKnights).
knighta([(X,Y)|_],[]) :-
write("No solution, next sol").
knighta([(X,Y)|_],[_|PlacedKnights]) :-
( is_attacked(X,Y,PlacedKnights)
-> knights(P1,PlacedKnights)
; write([(X,Y)|PlacedKnights)!
).
is_attacked(X,Y,PlacedKnights) :-
( NX is X - 1, NY is Y - 2
; NX is X - 1, NY is Y + 2
; NX is X + 1, NY is Y - 2
; NX is X + 1, NY is Y + 2
; NX is X - 2, NY is Y - 1
; NX is X - 2, NY is Y + 1
; NX is X + 2, NY is Y - 1
; NX is X + 2, NY is Y + 1
),
member((NX,NY),PlacedKnights).
when I run the program in debug mode, the line knighta(P1,PlacedKnights)
. doesn't take the program to knighta/2
: here
knighta([(X,Y)|_],[_|PlacedKnights])
I have no idea why.
Upvotes: 1
Views: 186
Reputation: 477641
First of all, there are some problems with your code:
]
instead of !
;knights
where it should be knighta
; andmember
before the constraints in is_attached
.Perhaps you should consider a total redesign.
First of all, you could use the following as an is_attacked
predicate:
is_attacked(X,Y,PlacedKnights) :-
member((NX,NY),PlacedKnights),
is_attacked(X,Y,NX,NY).
is_attacked(XA,YA,XB,YB) :-
DX is abs(XA-XB),
DY is abs(YA-YB),
is_attacked(DX,DY).
is_attacked(1,2).
is_attacked(2,1).
You thus iterate over all already placed knights, and you calculate the difference and check if it is a (2,1)
or (1,2)
difference.
Next you could use the following predicate to generate all possible configurations:
generateSolution(R,_,R).
generateSolution(Q,N,R) :-
for(X,1,N),
for(Y,1,N),
\+ member((X,Y),Q),
\+ is_attacked(X,Y,Q),
generateSolution([(X,Y)|Q],N,R).
Where generateSolution(L,N,R)
is a predicate with L
the already placed knights, N
the size of the board and R
any configuration with the already given knights that is correct (note this is not necessary the maximum number of knights).
But that's not that efficient: you don't perform symmetry breaking and thus generate a lot of duplicates:
?- generateSolution([],4,R),length(R,4).
R = [ (1, 4), (1, 3), (1, 2), (1, 1)] ; <- duplicate of
R = [ (2, 2), (1, 3), (1, 2), (1, 1)] ;
R = [ (4, 1), (1, 3), (1, 2), (1, 1)] ;
R = [ (4, 2), (1, 3), (1, 2), (1, 1)] ;
R = [ (4, 3), (1, 3), (1, 2), (1, 1)] ;
R = [ (4, 4), (1, 3), (1, 2), (1, 1)] ;
R = [ (1, 3), (1, 4), (1, 2), (1, 1)] ; <- this one
R = [ (2, 1), (1, 4), (1, 2), (1, 1)] ;
R = [ (3, 4), (1, 4), (1, 2), (1, 1)] ;
R = [ (4, 1), (1, 4), (1, 2), (1, 1)] ;
R = [ (4, 2), (1, 4), (1, 2), (1, 1)] ;
R = [ (4, 3), (1, 4), (1, 2), (1, 1)] ;
R = [ (4, 4), (1, 4), (1, 2), (1, 1)] ;
R = [ (1, 4), (2, 1), (1, 2), (1, 1)] ;
R = [ (2, 2), (2, 1), (1, 2), (1, 1)] ;
R = [ (3, 4), (2, 1), (1, 2), (1, 1)] ;
You can improve this by enforcing a constraint that says you can only increase the (X,Y)
coordinates:
% Any solution is a solution.
generateSolution(R,_,R).
% If no knight is placed on the board, select one with arbitrary `X` and `Y`.
generateSolution([],N,R) :-
for(X,1,N),
for(Y,1,N),
generateSolution([(X,Y)],N,R).
% If already placed one, fetch that solution, and propose a position (X,Y) with the same X and larger Y
generateSolution([(XL,YL)|T],N,R) :-
YL1 is YL+1,
for(Y,YL1,N),
\+ is_attacked(XL,Y,[(XL,YL)|T]),
generateSolution([(XL,Y),(XL,YL)|T],N,R).
% Or generate one with a larger X
generateSolution([(XL,YL)|T],N,R) :-
XL1 is XL+1,
for(X,XL1,N),
for(Y,1,N),
\+ is_attacked(X,Y,[(XL,YL)|T]),
generateSolution([(X,Y),(XL,YL)|T],N,R).
Here, or Y
must be larger than the previous Y
, or X
must be larger. The query thus no longer considers duplicates:
?- generateSolution([],4,R),length(R,4).
R = [ (1, 4), (1, 3), (1, 2), (1, 1)] ;
R = [ (2, 1), (1, 3), (1, 2), (1, 1)] ;
R = [ (2, 2), (1, 3), (1, 2), (1, 1)] ;
R = [ (3, 4), (1, 3), (1, 2), (1, 1)] ;
R = [ (4, 1), (1, 3), (1, 2), (1, 1)] ;
R = [ (4, 2), (1, 3), (1, 2), (1, 1)] ;
R = [ (4, 3), (1, 3), (1, 2), (1, 1)] ;
R = [ (4, 4), (1, 3), (1, 2), (1, 1)] ;
R = [ (2, 1), (1, 4), (1, 2), (1, 1)] ;
R = [ (2, 2), (1, 4), (1, 2), (1, 1)] ;
R = [ (3, 4), (1, 4), (1, 2), (1, 1)] ;
R = [ (4, 1), (1, 4), (1, 2), (1, 1)] ;
R = [ (4, 2), (1, 4), (1, 2), (1, 1)] ;
R = [ (4, 3), (1, 4), (1, 2), (1, 1)] ;
R = [ (4, 4), (1, 4), (1, 2), (1, 1)] ;
R = [ (2, 2), (2, 1), (1, 2), (1, 1)] ;
R = [ (3, 4), (2, 1), (1, 2), (1, 1)] ;
R = [ (4, 1), (2, 1), (1, 2), (1, 1)] ;
R = [ (4, 2), (2, 1), (1, 2), (1, 1)] ;
R = [ (4, 3), (2, 1), (1, 2), (1, 1)] ;
R = [ (4, 4), (2, 1), (1, 2), (1, 1)] ;
R = [ (3, 4), (2, 2), (1, 2), (1, 1)] ;
R = [ (4, 1), (2, 2), (1, 2), (1, 1)] ;
Now in order to find the maximum number of knights, you can bootstrap:
bootstrap(N,Sol) :-
once(bootstrap(N,[],0,Sol)).
bootstrap(N,_,I,S) :-
once((generateSolution([],N,R),length(R,K),K > I)),
!,
bootstrap(N,R,K,S).
bootstrap(_,S,_,S).
The predicate works as follows: as first solution, you use []
(the empty list which always succeeds). Next you start searching for a configuration with more knights:
once((generateSolution([],N,R),length(R,K),K > I)),
Once such solution R
with number of knights K
is found, you take the new solution as the current solution, set the number of knights and start searching for a solution with more knights. If eventually that fails, you return the last current solution.
EXAMPLE:
?- bootstrap(1,S),write(S).
[ (1,1)]
S = [ (1, 1)].
?- bootstrap(2,S),write(S).
[ (2,2), (2,1), (1,2), (1,1)]
S = [ (2, 2), (2, 1), (1, 2), (1, 1)].
?- bootstrap(3,S),write(S).
[ (3,3), (3,1), (2,2), (1,3), (1,1)]
S = [ (3, 3), (3, 1), (2, 2), (1, 3), (1, 1)].
?- bootstrap(4,S),write(S).
[ (4,4), (4,3), (4,2), (4,1), (1,4), (1,3), (1,2), (1,1)]
S = [ (4, 4), (4, 3), (4, 2), (4, 1), (1, 4), (1, 3), (1, 2), (1, 1)].
?- bootstrap(5,S),write(S).
[ (5,5), (5,3), (5,1), (4,4), (4,2), (3,5), (3,3), (3,1), (2,4), (2,2), (1,5), (1,3), (1,1)]
S = [ (5, 5), (5, 3), (5, 1), (4, 4), (4, 2), (3, 5), (3, 3), (3, 1), (..., ...)|...].
?- bootstrap(6,S),write(S).
Full code:
bootstrap(N,Sol) :-
once(bootstrap(N,[],0,Sol)).
bootstrap(N,_,I,S) :-
once((generateSolution([],N,R),length(R,K),K > I)),
!,
bootstrap(N,R,K,S).
bootstrap(_,S,_,S).
generateSolution(R,_,R).
generateSolution([],N,R) :-
for(X,1,N),
for(Y,1,N),
generateSolution([(X,Y)],N,R).
generateSolution([(XL,YL)|T],N,R) :-
YL1 is YL+1,
for(Y,YL1,N),
\+ is_attacked(XL,Y,[(XL,YL)|T]),
generateSolution([(XL,Y),(XL,YL)|T],N,R).
generateSolution([(XL,YL)|T],N,R) :-
XL1 is XL+1,
for(X,XL1,N),
for(Y,1,N),
\+ is_attacked(X,Y,[(XL,YL)|T]),
generateSolution([(X,Y),(XL,YL)|T],N,R).
is_attacked(X,Y,PlacedKnights) :-
member((NX,NY),PlacedKnights),
is_attacked(X,Y,NX,NY).
is_attacked(XA,YA,XB,YB) :-
DX is abs(XA-XB),
DY is abs(YA-YB),
is_attacked(DX,DY).
is_attacked(1,2).
is_attacked(2,1).
Note that more clever techniques exist, for instance much time is wasted validating whether a knight is attacked and there are additional symmetry breaking methods as well as ways to prevent returning a solution with a smaller number of knights with generateSolution
. This is only a raw sketch.
A non-backtracking optimal solution
As you can notice, almost all results follow a pattern:
1:
+-+
|x|
+-+
2:
+-+-+
|x|x|
+-+-+
|x|x|
+-+-+
3:
+-+-+-+
|x| |x|
+-+-+-+
| |x| |
+-+-+-+
|x| |x|
+-+-+-+
4:
+-+-+-+-+
|x| |x| |
+-+-+-+-+
| |x| |x|
+-+-+-+-+
|x| |x| |
+-+-+-+-+
| |x| |x|
+-+-+-+-+
The pattern that occurs from the moment N
is greater than or equal to N
is that you place a knight on (0,0)
and every (i,i+2*j)
with i
and j
integers (j
can be less than 0
). This is the guaranteed maximum.
You can thus generate this with:
solution(1,[(1,1)]).
solution(2,[(2,2),(2,1),(1,2),(1,1)]).
solution(N,L) :-
N > 2,
solution([],N,1,1,L).
solution(L,N,I,_,L) :-
I > N,
!.
solution(L,N,I,J,S) :-
JN is J+2,
JN =< N,
!,
solution([(I,J)|L],N,I,JN,S).
solution(L,N,I,J,S) :-
IN is I+1,
JN is (I mod 2)+1,
IN =< N,
!,
solution([(I,J)|L],N,IN,JN,S).
solution(L,N,I,J,[(I,J)|L]).
EXAMPLE:
?- solution(20,L),write(L).
[ (20,20), (20,18), (20,16), (20,14), (20,12), (20,10), (20,8), (20,6), (20,4), (20,2), (19,19), (19,17), (19,15), (19,13), (19,11), (19,9), (19,7), (19,5), (19,3), (19,1), (18,20), (18,18), (18,16), (18,14), (18,12), (18,10), (18,8), (18,6), (18,4), (18,2), (17,19), (17,17), (17,15), (17,13), (17,11), (17,9), (17,7), (17,5), (17,3), (17,1), (16,20), (16,18), (16,16), (16,14), (16,12), (16,10), (16,8), (16,6), (16,4), (16,2), (15,19), (15,17), (15,15), (15,13), (15,11), (15,9), (15,7), (15,5), (15,3), (15,1), (14,20), (14,18), (14,16), (14,14), (14,12), (14,10), (14,8), (14,6), (14,4), (14,2), (13,19), (13,17), (13,15), (13,13), (13,11), (13,9), (13,7), (13,5), (13,3), (13,1), (12,20), (12,18), (12,16), (12,14), (12,12), (12,10), (12,8), (12,6), (12,4), (12,2), (11,19), (11,17), (11,15), (11,13), (11,11), (11,9), (11,7), (11,5), (11,3), (11,1), (10,20), (10,18), (10,16), (10,14), (10,12), (10,10), (10,8), (10,6), (10,4), (10,2), (9,19), (9,17), (9,15), (9,13), (9,11), (9,9), (9,7), (9,5), (9,3), (9,1), (8,20), (8,18), (8,16), (8,14), (8,12), (8,10), (8,8), (8,6), (8,4), (8,2), (7,19), (7,17), (7,15), (7,13), (7,11), (7,9), (7,7), (7,5), (7,3), (7,1), (6,20), (6,18), (6,16), (6,14), (6,12), (6,10), (6,8), (6,6), (6,4), (6,2), (5,19), (5,17), (5,15), (5,13), (5,11), (5,9), (5,7), (5,5), (5,3), (5,1), (4,20), (4,18), (4,16), (4,14), (4,12), (4,10), (4,8), (4,6), (4,4), (4,2), (3,19), (3,17), (3,15), (3,13), (3,11), (3,9), (3,7), (3,5), (3,3), (3,1), (2,20), (2,18), (2,16), (2,14), (2,12), (2,10), (2,8), (2,6), (2,4), (2,2), (1,19), (1,17), (1,15), (1,13), (1,11), (1,9), (1,7), (1,5), (1,3), (1,1)]
L = [ (20, 20), (20, 18), (20, 16), (20, 14), (20, 12), (20, 10), (20, 8), (20, 6), (..., ...)|...].
Or a graphical representation:
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
| |x| |x| |x| |x| |x| |x| |x| |x| |x| |x|
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
|x| |x| |x| |x| |x| |x| |x| |x| |x| |x| |
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
| |x| |x| |x| |x| |x| |x| |x| |x| |x| |x|
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
|x| |x| |x| |x| |x| |x| |x| |x| |x| |x| |
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
| |x| |x| |x| |x| |x| |x| |x| |x| |x| |x|
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
|x| |x| |x| |x| |x| |x| |x| |x| |x| |x| |
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
| |x| |x| |x| |x| |x| |x| |x| |x| |x| |x|
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
|x| |x| |x| |x| |x| |x| |x| |x| |x| |x| |
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
| |x| |x| |x| |x| |x| |x| |x| |x| |x| |x|
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
|x| |x| |x| |x| |x| |x| |x| |x| |x| |x| |
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
| |x| |x| |x| |x| |x| |x| |x| |x| |x| |x|
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
|x| |x| |x| |x| |x| |x| |x| |x| |x| |x| |
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
| |x| |x| |x| |x| |x| |x| |x| |x| |x| |x|
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
|x| |x| |x| |x| |x| |x| |x| |x| |x| |x| |
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
| |x| |x| |x| |x| |x| |x| |x| |x| |x| |x|
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
|x| |x| |x| |x| |x| |x| |x| |x| |x| |x| |
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
| |x| |x| |x| |x| |x| |x| |x| |x| |x| |x|
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
|x| |x| |x| |x| |x| |x| |x| |x| |x| |x| |
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
| |x| |x| |x| |x| |x| |x| |x| |x| |x| |x|
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
|x| |x| |x| |x| |x| |x| |x| |x| |x| |x| |
+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
Upvotes: 1