Help with 8-Queens using CHR

Hi,

I’m revisiting CHR and having some trouble figuring out how to do 8-Queens. Up until a few weeks ago, there was a constraint-handling-rules.org website but it appears to be gone now; it had a dead link to a solution but even using archive.org I couldn’t seem to find it. I asked on Stack Overflow but didn’t get any responses there, so I’m asking here in case someone here might have a hint.

Here’s my code:

:- use_module(library(chr)).

:- chr_constraint board(+int), free(+int, +int), queen/0, queen(+int, +int). 
:- chr_constraint attacked(+int, +int), queens(+int), n_queens(+int).

%% initialize the board
board(N) <=> foreach(between(1, N, X), foreach(between(1, N, Y), free(X, Y))).

%% place a queen
queen, free(X, Y) <=> queen(X, Y).
queen(X, _) \ free(X, F) <=> attacked(X, F).
queen(_, Y) \ free(F, Y) <=> attacked(F, Y).
queen(X1, Y1) \ free(X2, Y2) <=> diagonal(X1, Y1, X2, Y2) | attacked(X2, Y2).

%% generate all the necessary queens
queens(0) <=> true.
queens(N) <=> queen, succ(N0, N), queens(N0).

%% ascertain if two points are on the same diagonal
diagonal(X1, Y1, X2, Y2) :-
    abs(X1 - X2) =:= abs(Y1 - Y2).

n_queens(N) <=> board(N), queens(N).

main :-
    n_queens(8).

So this has the obvious problem that it can’t backtrack to find a solution:

queen,
queen,
queen,
queen(4, 5),
queen(5, 7),
queen(6, 4),
queen(7, 6),
queen(8, 8),
...

I’m not sure what the recommended approach is for finding solutions in such cases using CHR rather than CLP or vanilla Prolog but it seems like it would be a helpful technique to understand, especially for CHR outside a Prolog context.

Parenthetically, I asked ChatGPT about this and it gave me back my exact code, and then when I complained about it, it gave me back a CLP answer instead with some bizarre CHR stapled on the end.

Thanks!

1 Like

Can you share which ChatGPT model used and the prompt?


I did the following prompt with model o1-preview (Introducing OpenAI o1)

Using SWI-Prolog with library(chr) for Constraint Handling Rules, create code to solve the N-Queens problem. Explain the code for someone first learning to use CHR.

and here was the thought process and completion.


Thought process

Thought for 58 seconds

Understanding CHR

OK, let me see: Constraint Handling Rules (CHR) in Prolog are used to simplify, propagate, or remove constraints. The N-Queens problem involves placing queens on a chessboard without them attacking each other.

Mapping out constraints

I'm listing constraints: no two queens share a row, column, or diagonal. Using CHR to define these constraints and let Prolog solve them.

Priming the CHR constraints

I’m setting up the CHR library and defining constraints for queen positions. The plan is to generate N queen constraints for each column and enforce them effectively.

Implementing CHR constraints

I’m setting up CHR constraints to manage the n-queens problem. This involves coding the n_queens predicate and using labeling for queen positions.

Charting queen movements

OK, let's think this through. In the N-Queens problem, I created the list Qs, aligning queens by rows in each column. This sets constraints, with queens at (i, Qs[i]) being safe/0.

Crafting the constraints

I'm working through a constraint-seeking predicate for N-Queens, focusing on ensuring no two queens share the same row, column, or diagonal.

Representing constraints

I’m thinking through how to represent queens' positions and their constraints. Using CHR to link variables effectively might work well here, ensuring each queen stays in a unique column.

Crafting constraints

I’m sketching out a Prolog-based N-Queens solver, setting up constraints to ensure no two queens share a row or diagonal. This involves defining queen and neq constraints and detailing rules to respect these constraints.

Crafting constraints

I’m thinking through how to enforce queen safety in CHR, considering inequalities and constraints to prevent queens from attacking each other, leading to clear and efficient rules.

Defining constraints

I'm mapping out different ways to ensure queens don't threaten one another on a chessboard using constraints. CHR seems like the ideal tool here.

Mapping out constraints

I'm working on defining constraints for the N-Queens problem by using Prolog variables and CHR rules. This method leverages CHR for complex constraints, while relying on Prolog's logic programming for symmetry and efficiency.

Mapping constraints

I'm considering constraints for defining queen locations on a CHR constraint language. This can include rules for column and row inequality, as well as diagonal constraints, leveraging finite domain solvers under SWI-Prolog.

Formulating constraints

I’m setting up the N-Queens problem with CHR, defining constraints for placing queens and ensuring they don't attack each other.

Deciding on constraints

I’m framing the problem with CHR constraints: queen/2 and safe/0 to model the N-Queens problem.

Declaring constraints

I’m laying out constraints to ensure queens are placed correctly. No two queens on the same row or diagonal, and then generating possible row assignments.

Developing constraints

I’m working through assigning domains to a set of variables and considering CHR to manage propagation. This could streamline value assignments effectively.

Considering finite domain solver⠀🤔 (handles infinite spaces). Using CHR for constraints feels like a controlled decision, avoiding messy coding challenges.

Formulating constraints

I’m setting up constraints for the N-Queens problem. First, ensuring no two queens share the same row, then preventing them from sharing the same diagonal with specific rules for both cases.

Assessing constraint propagation

I'm navigating the process of constraint propagation for the n queens problem using CHR constraints and constraints propagation. Writing domain constraints in CHR, like: :- chr_constraint var_domain/2.

Leveraging CHR for N-Queens

I'm combining the CHR library for the N-Queens problem, leveraging constraints like queen/2 to set initial and propagation rules for column and row uniqueness, ensuring a valid solution.

Initializing queens

I’m piecing together a predicate to set up queens on a chessboard. The n_queens predicate creates columns and initializes queens with init_queens. Constraints such as no two queens in the same row or diagonal guide the process.

Securing position

I’m crafting rules to prevent two queens from sharing the same row or diagonal by checking column and diagonal positions for conflicts. This helps ensure each queen stands alone.

Clarifying N-Queens with constraints

OK, let me see. The puzzle involves generating valid assignments for a grid, using CHR rules to ensure constraints, and employing backtracking to resolve conflicts for testing.

Setting up the framework

I’m piecing together the CHR module in Prolog to ensure no two queens share rows or diagonals. With n_queens(N, Qs), the solution for the 4-queens problem should become clear.

loading CHR, defining constraints

Completion

Certainly! Let’s create and explain Prolog code using the Constraint Handling Rules (CHR) library to solve the N-Queens problem.

Introduction to Constraint Handling Rules (CHR)

Constraint Handling Rules (CHR) is a declarative language extension for writing constraint solvers. In Prolog, CHR allows us to define custom rules that simplify and propagate constraints during computation.

In the N-Queens problem, we need to place N queens on an N×N chessboard such that no two queens threaten each other. The constraints are:

  1. No two queens share the same row.
  2. No two queens share the same column.
  3. No two queens share the same diagonal.

Since we’ll place one queen per column, we only need to ensure that no two queens share the same row or diagonal.

The Prolog Code Using CHR

% Load the CHR library
:- use_module(library(chr)).

% Declare the CHR constraints
:- chr_constraint queen/2.

% CHR rules to enforce the constraints

% Rule 1: No two queens share the same row
queen(C1, R), queen(C2, R) ==> C1 < C2 | false.

% Rule 2: No two queens share the same diagonal
queen(C1, R1), queen(C2, R2) ==> 
    C1 < C2, 
    abs(R1 - R2) =:= abs(C1 - C2) | false.

% Main predicate to solve the N-Queens problem
n_queens(N, Solution) :-
    numlist(1, N, Columns),
    initialize_queens(Columns, Rows),
    assign_rows(Rows, N),
    Solution = Rows.

% Initialize queens with their columns and row variables
initialize_queens([], []).
initialize_queens([C|Cs], [R|Rs]) :-
    queen(C, R),
    initialize_queens(Cs, Rs).

% Assign possible rows to each queen
assign_rows([], _).
assign_rows([R|Rs], N) :-
    between(1, N, R),
    assign_rows(Rs, N).

Explanation of the Code

1. Loading the CHR Library and Declaring Constraints

:- use_module(library(chr)).
:- chr_constraint queen/2.
  • We load the CHR library using use_module(library(chr)).
  • We declare a CHR constraint queen/2, where queen(Column, Row) represents a queen placed at a specific column and row.

2. Defining CHR Rules to Enforce Constraints

Rule 1: No Two Queens Share the Same Row

queen(C1, R), queen(C2, R) ==> C1 < C2 | false.
  • This rule states that if two queens are in the same row (R), and they are in different columns (C1 and C2), then this configuration is invalid (false).
  • The guard C1 < C2 ensures that the rule checks each pair only once to avoid redundancy.

Rule 2: No Two Queens Share the Same Diagonal

queen(C1, R1), queen(C2, R2) ==> 
    C1 < C2, 
    abs(R1 - R2) =:= abs(C1 - C2) | false.
  • This rule checks if two queens are on the same diagonal. If the absolute difference between their rows equals the absolute difference between their columns, they are on the same diagonal.
  • If they are on the same diagonal, the configuration is invalid (false).

3. Main Predicate to Solve the N-Queens Problem

n_queens(N, Solution) :-
    numlist(1, N, Columns),
    initialize_queens(Columns, Rows),
    assign_rows(Rows, N),
    Solution = Rows.
  • n_queens/2 is the main predicate. It takes the size of the board N and returns a Solution list representing the row positions of the queens.
  • numlist(1, N, Columns) generates a list of column numbers [1, 2, ..., N].
  • initialize_queens(Columns, Rows) initializes the queens with their columns and associates a variable for each row.
  • assign_rows(Rows, N) assigns possible row values to each queen.
  • Solution = Rows binds the list of row positions to the output variable.

4. Initializing Queens

initialize_queens([], []).
initialize_queens([C|Cs], [R|Rs]) :-
    queen(C, R),
    initialize_queens(Cs, Rs).
  • This recursive predicate associates each column number with a row variable by asserting the queen/2 constraint for each queen.

5. Assigning Rows to Each Queen

assign_rows([], _).
assign_rows([R|Rs], N) :-
    between(1, N, R),
    assign_rows(Rs, N).
  • assign_rows/2 assigns a possible row number between 1 and N to each queen.
  • between(1, N, R) generates row numbers from 1 to N.
  • The recursive call continues this process for all queens.

6. How the Program Works

  • Prolog’s backtracking mechanism tries different row assignments for each queen.
  • The CHR rules automatically eliminate any assignment that violates the constraints (same row or diagonal).
  • When a valid configuration is found, the Solution list contains the row positions of the queens for each column.

Example Usage

Let’s solve the 4-Queens problem:

?- n_queens(4, Solution).
Solution = [2, 4, 1, 3] ;
Solution = [3, 1, 4, 2] ;
false.
  • The program finds all solutions where queens are placed on a 4x4 board without threatening each other.
  • Each number in the Solution list represents the row position of the queen in that column.

Summary

  • CHR allows us to define custom constraints and rules to enforce them.
  • In the N-Queens problem, we used CHR to enforce that no two queens are in the same row or diagonal.
  • The Prolog code uses recursive predicates to initialize queens and assign row values.
  • Prolog’s backtracking, combined with CHR constraints, efficiently finds all valid solutions.

This approach demonstrates how CHR can be used to model and solve constraint satisfaction problems like the N-Queens problem in Prolog.



Note:

  • I did not attempt to run the code, was more curious to see the thought process and the code generated. Hopefully this might be of use.
  • I do not use CHR because AFAIK it is not actively maintained for SWI-Prolog (possibly several years old)

Unfortunately, the code doesn’t run:

?- n_queens(8, Sol).
ERROR: Arguments are not sufficiently instantiated
ERROR: In:
ERROR:   [29] abs(_127096-_127098)=:=abs(1-2)
ERROR:   [28] queen___2__3__0__4([suspension(132,active,t,0,...,queen,1,_127162)],2,_127136,suspension(133,inactive,t,0,user: ...,queen,2,_127180)) at /home/dlyons@ad.nrao.edu/Projects/tmp/q82.pl:35
ERROR:   [14] initialize_queens([2,3|...],[_127228|_127230]) at /home/dlyons@ad.nrao.edu/Projects/tmp/q82.pl:27
ERROR:   [12] n_queens(8,_127256) at /home/dlyons@ad.nrao.edu/Projects/tmp/q82.pl:20
ERROR:   [11] toplevel_call(user:user: ...) at /nix/store/icwyy869a2v74ip1m5m8cb0k3xdqydcy-swi-prolog-9.1.21/lib/swipl/boot/toplevel.pl:1321
ERROR: 
ERROR: Note: some frames are missing due to last-call optimization.
ERROR: Re-run your program in debug mode (:- debug.) to get more detail.

Looking at the code, I don’t see how it could possibly work since the row values are getting used in an arithmetic statement in Rule 2, but they’re free variables when they are generated in initialize_queens/2. But anyway, I don’t want to draw undue attention to ChatGPT, my real problem is about CHR, and this doesn’t really shine a light on how to use it.

As for whether or not CHR is maintained, I can’t say anything, except that it does work and I would be surprised if it required significant maintenance, the whole point of it is that it is simple. But if anyone knows why it disappeared from the web recently I would like to know more.

1 Like

In case you want to see the conversation I had, it is here.

1 Like

Very odd that all the CHR links are gone. Thom Fruhwirth has published on the language as recently as last year.

I’m not sure the techniques normally used for N-Queens, but any of them can be coded in CHR. Here’s one method that may be inefficient:

place_n_queens(N) :-
between(1,N, X), place_queen(X, N).

place_queen(I, N) :- between(1,N, Y), queen(X, Y).
I’m not seeing a definition of attacked. But instead you can have

% attacked rule
queen(A,D), queen(B,C) ==> A \== B, D \== C, A-B \== C-D, B-A \== C-D.

With this rule, queen(2,4), queen(3,5) will fail

The backtracking happens outside CHR but you could equally make place_n_queens a rule and then it would be within CHR.

You asked about using this outside prolog. I would write a program like this:

{
   for I in 0..N-1
        place_queens(I, N)
}

place_queens(I, N)
{
   for J in 0..N-1
     if (queen(I,J) fails) next J
     else // if (queen(I, J) succeeds) 
         if place_queens(J+1, N) succeeds, return success
        else remove last queen; next J
   end for
   return fail
}

basically reinventing the backtracking loop. If the CHR gets more complex than just queens, and the embedding doesn’t support backtracking, then I would suggest labeling deductions. Then you can do delete_level_n(N) \ queens_object(N, ) <=> true.

In general it’s hard to do this generally without recreating backtracking. I don’t think Queens is particularly suited to constraint resolution without because there are dead ends in the search tree that can’t easily be avoided.

But if you can find logical deductions not based on trying various possibilities, then you can effectively apply those.

CHR got a little bit behind after ASP appeared, but anyway:

Yeah thats seems the way forward, this will ground the
2nd argument of queen/2. I got it running this way:

:- use_module(library(chr)).

:- chr_constraint solve/0, next_queen/1, queen/2.

solve <=> next_queen(0).

queen(_,R), queen(_,R) ==> true | fail.
queen(C1,R1), queen(C2,R2) ==> abs(C1-C2) =:= abs(R1-R2) | fail.

next_queen(C) <=> C =:= 8 | true.
next_queen(C) <=> between(0,7,R), queen(C,R), D is C+1, next_queen(D).

The above has N=8 hard coded and uses between/3 already
in initialize_queens/2, realized as a tail recursive next_queen/1,

directing the search a little bit more. Seems to work correctly:

?- solve, (between(0,7,X), (between(0,7,Y), 
    (find_chr_constraint(queen(X,Y)) -> write('*'); write(' ')), 
   fail; true), nl, fail; true).
*       
    *   
       *
     *  
  *     
      * 
 *      
   *    

?- aggregate_all(count, solve, C).
C = 92.

Adapted from Listing 3 N-queens in CHR++:

CHR++: An efficient CHR system in C++ with don’t know non-determinism
Vincent Barichard - 15 March 2024
https://www.sciencedirect.com/science/article/am/pii/S0957417423023126