Search code examples
prologclpfdn-queens

Understanding CLP(FD) Prolog code of N-queens problem


I am trying to understand N-queens problem's solution as given below:

:- use_module(library(clpfd)).

n_queens(N, Qs) :-
    length(Qs, N),
    Qs ins 1..N,
    safe_queens(Qs).

safe_queens([]).
safe_queens([Q|Qs]) :-
    safe_queens(Qs, Q, 1),
    safe_queens(Qs).

safe_queens([], _, _).
safe_queens([Q|Qs], Q0, D0) :-
    Q0 #\= Q,
    abs(Q0 - Q) #\= D0,
    D1 #= D0 + 1,
    safe_queens(Qs, Q0, D1).

I am not able to understand the below snippet:

safe_queens([]).
safe_queens([Q|Qs]) :-
    safe_queens(Qs, Q, 1),
    safe_queens(Qs).

safe_queens([], _, _).
safe_queens([Q|Qs], Q0, D0) :-
    Q0 #\= Q,
    abs(Q0 - Q) #\= D0,
    D1 #= D0 + 1,
    safe_queens(Qs, Q0, D1).

Please help me to understand. Any help would be greatly appreciated.


Solution

  • Since you did not give any example queries, start with some example queries to determine the parameters and output format. Normally to determine the parameters and output format for unknown code requires looking at the code for the structure of the arguments and then trying sample queries. Additionally note that this code uses the Constraint Logic Programming library clpfd; when I read that I literally stop thinking syntactic unification and start thinking constraints. I think of it as a separate system embedded within Prolog and not additional predicates. You will notice that in this answer that constraint is used very often and predicate or rule is quite absent even though this is Prolog.

    Since the N-Queens problem is so well known as a logic problem a quick Google search (clpfd n queens) turns up SWI-Prolog Example: Eight queens puzzle. Note the addition of the keyword clpfd it is crucial for understanding this variation of the code; there are many solutions in other programming langues.

    This gives an example query n_queens(8, Qs), label(Qs) for which label/1 returns values for the system generated variables. This also tells us that the first argument is a positive integer and the second argument is a list of length of the first argument. Also by having worked with this problem before, the first argument is the dimensional size of the board, so 1 is 1x1 board, 8 is an 8x8 board, etc., and the number of queens that will be on the board.
    The next thing that helps is to know what the valid solutions are or at least a count of them for a set of parameters.

    The Wikipedia article for Eight queens puzzle provides that in the counting solutions section. This shows that for a board of 1x1 there is one solution, no solutions for a board of 2x2, or 3x3, two solutions for 4x4 and so on.

    For a 1x1 board there is one solution.

    ?- n_queens(1,Qs),label(Qs).
    Qs = [1].
    

    For a 2x2 board there is no solution.

    ?- n_queens(2,Qs),label(Qs).
    false.
    

    For a 4x4 board there are two solutions.

    ?- n_queens(4,Qs),label(Qs).
    Qs = [2, 4, 1, 3] ;
    Qs = [3, 1, 4, 2] ;
    false.
    


    Qs = [2, 4, 1, 3]
    

    enter image description here

    To interpret the results the positions in the list correspond with the columns on the board and the values with a row on the board, so for the first value in the list (2) it reads a queen in row 2, column 1, for the second value in the list (4) it reads a queen in row 4, column 2

    Qs = [3, 1, 4, 2]
    

    enter image description here

    Note: Images generated using Chess Diagram Setup

    If we run the query with the values as a variables the result is an endless parade of the valid answers.

    ?- n_queens(N,Qs),label(Qs).
    N = 0,
    Qs = [] ;
    N = 1,
    Qs = [1] ;
    N = 4,
    Qs = [2, 4, 1, 3] ;
    N = 4,
    Qs = [3, 1, 4, 2] ;
    N = 5,
    Qs = [1, 3, 5, 2, 4] ;
    N = 5,
    Qs = [1, 4, 2, 5, 3] ;
    N = 5,
    Qs = [2, 4, 1, 3, 5] ;
    N = 5,
    Qs = [2, 5, 3, 1, 4] ;
    N = 5,
    Qs = [3, 1, 4, 2, 5] ;
    N = 5,
    Qs = [3, 5, 2, 4, 1] ;
    N = 5,
    Qs = [4, 1, 3, 5, 2] 
    ...
    

    Now that we know the code runs and gives valid solutions we can start to dissect it.
    Normally SWI-Prolog trace/0 or SWI-PRolog GUI-tracer started with gtrace/0 would be a tool of choice but having used that on clpfd before I know that is not a tool of first choice with Constraint Logic Programming. Try it and and you will see why.

    On with the dissection.

    ?- n_queens(1,Qs).
    Qs = [1].
    
    ?- n_queens(2,Qs).
    Qs = [_1942, _1948],
    _1942 in 1..2,
    abs(_1942-_1948)#\=1,
    _1942#\=_1948,
    _1948 in 1..2.
    

    This is something of interest.
    To make this easier to understand, swap out the system generated variables with user friendly variables and give a human reading to the meaning of the statement.

    ?- n_queens(2,Qs).
    Qs = [A, B],
    A in 1..2,
    abs(A-B)#\=1,
    A#\=B,
    B in 1..2.
    

    Note that with CLP(FD) operators with # in them are typically constraints, e.g. #\= and #= are read like the normal operators less the #

    `A in 1..2`    reads the value for `A` must be in the range `1..2`
    `abs(A-B)#\=1` reads the difference of the values between `A` and `B` must not equal 1
    `A#\=B`        reads the value of `A` must not equal the value of `B`
    `B in 1..2`    reads the value of `B` must be in `1..2`
    

    So these are just a set of constraints. If you try to solve the constraints by hand you will find that there is no solution, e.g.

    0,_  invalid by `A in 1..2`
    _,0  invalid by `B in 1..2`
    3,_  invalid by `A in 1..2`
    _,3  invalid by `B in 1..2`
    1,1  invalid by `A#\=B` 
    1,2  invalid by `abs(A-B)#\=1`
    2,1  invalid by `abs(A-B)#\=1`
    2,2  invalid by `A#\=B` 
    

    Doing the same for a 4x4 board

    ?- n_queens(4,Qs).
    Qs = [_5398, _5404, _5410, _5416],
    _5398 in 1..4,
    abs(_5398-_5416)#\=3,
    _5398#\=_5416,
    abs(_5398-_5410)#\=2,
    _5398#\=_5410,
    abs(_5398-_5404)#\=1,
    _5398#\=_5404,
    _5416 in 1..4,
    abs(_5410-_5416)#\=1,
    _5410#\=_5416,
    abs(_5404-_5416)#\=2,
    _5404#\=_5416,
    _5410 in 1..4,
    abs(_5404-_5410)#\=1,
    _5404#\=_5410,
    _5404 in 1..4.
    


    ?- n_queens(4,Qs).
    Qs = [A, B, C, D],
    A in 1..4,     reads the value for `A` must be in the range `1..4`
    abs(A-D)#\=3,  reads the difference of the values between `A` and `D` must not equal 3
    A#\=D,         reads the value of `A` must not equal the value of `D`
    abs(A-C)#\=2,  reads the difference of the values between `A` and `C` must not equal 2
    A#\=C,         reads the value of `A` must not equal the value of `C`
    abs(A-B)#\=1,  reads the difference of the values between `A` and `B` must not equal 1
    A#\=B,         reads the value of `A` must not equal the value of `B`
    D in 1..4,     reads the value for `D` must be in the range `1..4`
    abs(C-D)#\=1,  reads the difference of the values between `C` and `D` must not equal 1
    C#\=D,         reads the value of `C` must not equal the value of `D`
    abs(B-D)#\=2,  reads the difference of the values between `B` and `D` must not equal 2
    B#\=D,         reads the value of `B` must not equal the value of `D`
    C in 1..4,     reads the value for `C` must be in the range `1..4`
    abs(B-C)#\=1,  reads the difference of the values between `B` and `C` must not equal 1
    B#\=C,         reads the value of `B` must not equal the value of `C`
    B in 1..4.     reads the value for `B` must be in the range `1..4`
    

    That is a bit to take in but this being logic we can rearrange the statements and the meaning will be the same.

    So grouping like statements, sorting by variable, then ordering groups by simplicity gives

    `A in 1..4`    reads the value for `A` must be in the range `1..4`
    `B in 1..4`    reads the value for `B` must be in the range `1..4`   
    `D in 1..4`    reads the value for `D` must be in the range `1..4`
    `C in 1..4`    reads the value for `C` must be in the range `1..4` 
    `A#\=B`        reads the value of `A` must not equal the value of `B`
    `A#\=C`        reads the value of `A` must not equal the value of `C`
    `A#\=D`        reads the value of `A` must not equal the value of `D`
    `B#\=C`        reads the value of `B` must not equal the value of `C`
    `B#\=D`        reads the value of `B` must not equal the value of `D`
    `C#\=D`        reads the value of `C` must not equal the value of `D`
    `abs(A-B)#\=1` reads the difference of the values between `A` and `B` must not equal 1
    `abs(A-C)#\=2` reads the difference of the values between `A` and `C` must not equal 2
    `abs(A-D)#\=3` reads the difference of the values between `A` and `D` must not equal 3
    `abs(B-C)#\=1` reads the difference of the values between `B` and `C` must not equal 1
    `abs(B-D)#\=2` reads the difference of the values between `B` and `D` must not equal 2
    `abs(C-D)#\=1` reads the difference of the values between `C` and `D` must not equal 1
    

    Now to explain the constraints and show how they relate to queens on a square board; note I say square board and not chess board because a chess board is 8x8 and this code works with different dimensional square boards.


    A in 1..4

    Means that the A queen has to be placed in a position on the 4x4 board. When working with constraint problems you often find that what we as humans take for granted or think of a common sense need to be given as specific constraints, this is a point in case. Also learning that adding rules for common sense is sometimes one of the hardest task when creating AI solutions. While I can not find a reference, when the creators of Cyc were adding rules, the concept of time took a lot of time to get right (no pun intended). The remainder of the constraints like A in 1..4 just ensure that no queen is placed in a position off the board.


    A#\=B

    To better understand this constraint lets do a picture with a 4x4 board and white queens as a valid position and the black queen as an invalid position as defined by the constraint.

    enter image description here

    So A is the white queen in row 1 and B is the black queen in row 1. Since A can not equal B this says that if queen A is in row 1 then queen B can not be in row 1. As the rule is used with variables it means that for any row the A queen is in the B queen can not be in that row. The remainder of the constraints like A#\=B just ensure that no two queens can be in the same row.

    Think of this constraint as the horizontal attack for a queen.


    abs(A-B)#\=1

    To better understand this constraint lets do a picture with a 4x4 board and white queens as a valid position and the black queen as an invalid position as defined by the constraint.

    There are four positions for A 1,2,3,4 but since the rule is symmetric horizontally (1 is the same a 4, and 2 is the same as 3) I will only do two of them.

    When A is 1.

    enter image description here

    Since A is 1, B can not be 2.

    1-2 = -1
    ABS(-1) = 1
    1 can not equal 1.
    

    When A is 2.

    enter image description here

    Since A is 2, B can not be 1.

    2 - 1 = 1
    ABS(1) = 1
    1 can not equal 1.
    

    Since A is 2, B can not be 3.

    2 - 3 = -1
    ABS(-1) = 1
    1 can not equal 1.
    

    If the constraint using queen A and queen D is examined

    abs(A-D)#\=3

    When A is 1.

    enter image description here

    Since A is 1, D can not be 4.

    1-4 = -3
    ABS(-3) = 3
    3 can not equal 1.
    

    When A is 2.

    Since A is 2, D can be 1.

    2-1 = 1
    ABS(1) = 1
    1 can not equal 3.
    

    Since A is 2, D can be 2.

    2-2 = 0
    ABS(0) = 0
    0 can not equal 3.
    

    Since A is 2, D can be 3.

    2-3 = -1
    ABS(-1) = 1
    1 can not equal 3.
    

    Since A is 2, D can be 4.

    2-4 = -2
    ABS(-2) = 2
    2 can not equal 3.
    

    Think of this constraint as the diagonal attack for a queen.


    But wait a minute, a queen can move horizontally, vertically and diagonally, where is the constraint for moving vertically?

    While this does not appear as a constraint in the output from the example query, there is a constraint. So far we have constraints that limit the positions of the queens to being on the board, the horizontal attack, and the diagonal attack as distinct constraints, however the structure of the data, the list of length N is also a constraint, ([A,B,C,D]) and constrains the A queen to the first column, the B queen to the second column and so on. Again this is one of points of learning to code in AI is that how we think as humans does not always directly translate into how to solve a problem with a computer. So while this code uses constraints to solve a problem, it also uses a data structure.

    Think of the list as the column attack for a queen.

    No two queens can be in the same column and that is limited by the fact that no two values can be in a scalar variable.

    enter image description here


    At this point many of you will recognize the remainder of the code as a helper and recursive predicate safe_queens/1 and as a recursive predicate safe_queens/3.


    safe_queens([], _, _).
    safe_queens([Q|Qs], Q0, D0) :-
        Q0 #\= Q,
        abs(Q0 - Q) #\= D0,
        D1 #= D0 + 1,
        safe_queens(Qs, Q0, D1).
    

    This is a standard recursive call to process a list, e.g.

    safe_queens([], _, _).
    safe_queens([H|T], _, _) :-
        % Process head of list (H)
        safe_queens(T, _, _). % Process tail of list (T)
    

    These two statements

    Q0 #\= Q
    abs(Q0 - Q) #\= D0
    

    are explained above

    and

    D1 #= D0 + 1
    

    sets D1 to D0 + 1

    If we modify the predicate as such

    permutations([], _, _).
    permutations([Q|Qs], Q0, D0) :-
        write(Q0),write('#\\='),writeln(Q),
        write('abs('),write(Q0),write('-'),write(Q),write(')#\\='),writeln(D0),
        D1 is D0 + 1,
        permutations(Qs, Q0, D1).
    

    and run these queries we see that it generates some of the constraints

    ?- permutations(['B','C','D'],'A',1).
    A#\=B
    abs(A-B)#\=1
    A#\=C
    abs(A-C)#\=2
    A#\=D
    abs(A-D)#\=3
    true.
    
    ?- permutations(['C','D'],'B',1).
    B#\=C
    abs(B-C)#\=1
    B#\=D
    abs(B-D)#\=2
    true.
    
    ?- permutations(['D'],'C',1).
    C#\=D
    abs(C-D)#\=1
    true.
    

    safe_queens([]).
    safe_queens([Q|Qs]) :-
        safe_queens(Qs, Q, 1),
        safe_queens(Qs).
    

    This is a standard recursive call to process a list, e.g.

    safe_queens([]).
    safe_queens([H|T]) :-
        % Process head of list (H)
        safe_queens(T). % Process tail of list (T)
    

    and also a helper for safe_queens/3 because this statement

        safe_queens(Qs, Q, 1)
    

    initializes the third argument for safe_queens/3 to 1

    If we modify the predicate as such

    generate_args([]).
    generate_args([Q|Qs]) :-
        write('Qs: '),write(Qs),write(', Q: '),write(Q),writeln(', 1'),
        generate_args(Qs).
    

    and run this query we see that it generates the arguments needed for safe_queens/3

    ?- generate_args(['A','B','C','D']).
    Qs: [B,C,D], Q: A, 1
    Qs: [C,D], Q: B, 1
    Qs: [D], Q: C, 1
    Qs: [], Q: D, 1
    true.
    

    However in your question you did not ask about the first predicate

    n_queens(N, Qs) :-
        length(Qs, N),
        Qs ins 1..N,
        safe_queens(Qs).
    

    which has

    length(Qs,N)
    

    that generates the list of length N with unbound variables

    [A,B,C,D]
    

    enter image description here

    and has the crucial constraint statement

    Qs ins 1..N
    

    that generates the constraints like

    A in 1..4
    

    enter image description here


    Now the crucial difference appended to the query

    labels(Qs)
    

    If you use the SWI-Prolog GUI-tracer and run the code up to the end of n_queens/2 you will see in the debugger a list of constraints but not a solution

    enter image description here

    that is because those predicates generate constraints that are maintained internally, it is not until labels/1 is called that the constraints are solved to generate a result.