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

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.

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]
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]
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.
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.
Since A is 1, B can not be 2.
1-2 = -1
ABS(-1) = 1
1 can not equal 1.
When A is 2.
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.
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.
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]
and has the crucial constraint statement
Qs ins 1..N
that generates the constraints like
A in 1..4
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
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.

Related

Prolog list of list n number with condition

I'm studying prolog language and i have an issue regarding this problem.
I've already created a program that, given a number N, returns a list with elements between 0 and N:
list2val(N,L):- list2val(0,N,L).
list2val(N,N,[N]).
list2val(C,N,[C|T]):-
C<N,
N1 is C+1,
list2val(N1,N,T).
?- list2val(5,X).
X = [0,1,2,3,4,5]
Now i'm trying to give an extension that, given a list, returns a list of lists in which every list is list2val only if the next number is greater than current number. In this case:
?- newFuction([1,5,2,3,9],L).
L = [[0,1],[0,1,2,],[0,1,2,3]]
My code is this, but somethings is wrong:
array(X):- array(X,_L).
array([],_L).
array([H|[T|Ts]],L1):-
H<T,
list2val(H,L2),
array([T|Ts],[L1|[L2]]).
array([T|Ts],L1).
Maybe could be too much difficult to understand but using a list L = [1,5,2,3,9] i do those steps:
check 1<5 so i create a 1 list2val until 1..in this case [0,1]
check 5<2 i dont create nothing.
check 2<3 i create list2val of 2 ...[0,1,2]
and so on...
I don't want use a standard predicates, by implement with standard terms.
A solution for your problem could be:
list2val(N,L):- list2val(0,N,L).
list2val(N,N,[N]):- !.
list2val(C,N,[C|T]):-
C<N,
N1 is C+1,
list2val(N1,N,T).
simulate([_],[]).
simulate([A,B|T],[H|T1]):-
( A < B ->
list2val(A,H),
simulate([B|T],T1);
simulate([B|T],[H|T1])
).
Using a predicate like simulate/2, you can solve your problem: it compares two numbers of the list and then create a new list in case the condition is satisfied.
?- simulate([1,5,2,3,9],LO).
LO = [[0, 1], [0, 1, 2], [0, 1, 2, 3]]
false

Prolog Sudoku Solver, Solve any quadratic Sudoku, elements not distinct

Solving any quadratic Sudoku, so Sudoku of sizes 4,9,16,25... without the need of hard-coding those "blocks", the sub-units of your normal Sudoku field.
Using SWI-Prolog and the clp(FD) library.
Sudokus given in a format like this (list of lists):
[[_,1,3,_],
[2,_,_,_],
[_,_,_,3],
[_,2,1,_]]
Program called using:
solve_sudoku([[_,1,3,_],[2,_,_,_],[_,_,_,3],[_,2,1,_]],L).
L = [[4, 1, 3, 2], [2, 3, 4, 1], [1, 4, 2, 3], [3, 2, 1, 4]]
Top-level from this link.
sudoku(Rows) :-
length(Rows,N),
D is integer(sqrt(N)),
append(Rows,Vs),Vs ins 1..N,
maplist(all_distinct,Rows),
transpose(Rows,Columns),
maplist(all_distinct,Columns),
check_blocks(Rows,D),
maplist(label,Rows).
After checking that the rows and columns have no repetitions, we need to check the blocks, which are D by D squares.
The procedure check_blocks/2 takes D rows at a time and passes them to block_columns/4.
check_blocks(Rows,D) :-
length(BlockRows,D), append(BlockRows,Rest,Rows),
block_columns(BlockRows,D,[],[]),
check_blocks(Rest,D).
check_blocks([],_).
Now we have D rows, which are assumed to each contain some number (ie D) of D columns. But we need to get hold of the first D columns of all the rows in order to check the block.
So the first clause in block_columns/4 loops over all the rows and splits them into the prefix (D columns) and the rest. When Rows is empty, Bs is the current block, and Rs the rest of the columns in each row.
block_columns([Row|Rows],D,Bs,Rs) :-
length(Cols,D), append(Cols,Rest,Row),
block_columns(Rows,D,[Cols|Bs],[Rest|Rs]).
block_columns([],D,Bs,Rs) :-
flatten(Bs,Ns), all_distinct(Ns),
flatten(Rs,Xs),
( Xs = [] ->
true
; block_columns(Rs,D,[],[]) ).
The second clause checks the block, and then starts over again. When we have reached the end of the columns, Rs will not be empty but contain D empty lists, so we have to flatten it before checking for termination.

What does this wildcard do in this prolog scenario?

I've come across this code:
connectRow(_,_,0).
connectRow([spot(_,R,_,_)|Spots],R,K) :- K1 is K-1, connectRow(Spots,R,K1).
/*c*/
connectRows([]).
connectRows(Spots) :-
connectRow(Spots,_,9),
skip(Spots,9,Spots1),
connectRows(Spots1).
How does the wildcard in the connectRow(Spots,_,9) work? How does it know which values to check and how does it know that it checked all the possible values?
Edit: I think I understand why this works but I'd like it if someone could verify this for me:
When I "call" the connectRow with the wildcard it matches the wildcard with the "R" in the connectRow predicate. Could this be it?
The _ is just like any other variable, except that each one you see is treated as a different variable and Prolog won't show you what it unifies with. There's no special behavior there; if it confuses you about the behavior, just invent a completely new variable and put it in there to see what it does.
Let's talk about how Prolog deals with variables. Here's an experiment you can follow along with that should undermine unhelpful preconceived notions if you happen to have them.
?- length([2,17,4], X)
X = 3.
A lot of Prolog looks like this and it's easy to fall into the trap of thinking that there are designated "out" variables that work like return values and designated "in" variables that work like parameters. After all:
?- length([2,17,4], 3).
true.
?- length([2,17,4], 5).
false.
Here we begin to see that something interesting is happening. A faulty intuition would be that Prolog is somehow keeping track of the input and output variables and "checking" in this case. That's not what's happening though, because unification is more general than that. Observe:
?- length(X, 3).
X = [_G2184, _G2187, _G2190].
We've now turned the traditional parameter/return value on its head: Prolog knows that X is a list three items long, but doesn't know what the items actually are. Believe it or not, this technique is frequently used to generate variables when you know how many you need but you don't need to have them individually named.
?- length(X, Y).
X = [],
Y = 0 ;
X = [_G2196],
Y = 1 ;
X = [_G2196, _G2199],
Y = 2 ;
X = [_G2196, _G2199, _G2202],
Y = 3
It happens that the definition of length is very general and Prolog can use it to generate lists along with their lengths. This kind of behavior is part of what makes Prolog so good at "generate and test" solutions. You define your problem logically and Prolog should be able to generate logically sound values to test.
All of this variation springs from a pretty simple definition of length:
length([], 0).
length([_|Rest], N1) :-
length(Rest, N0),
succ(N0, N1).
The key is to not read this like a procedure for calculating length but instead to see it as a logical relation between lists and numbers. The definition is inductive, relating the empty list to 0 and a list with some items to 1 + the length of the remainder of the list. The engine that makes this work is called unification.
In the first case, length([2,17,4], X), the value [17,4] is unified with Rest, N0 with 2 and N1 with 3. The process is recursive. In the final case, X is unified with [] and Y with 0, which leads naturally to the next case where we have some item and Y is 1, and the fact that the variable representing the item in the list doesn't have anything in particular to unify with doesn't matter because the value of that variable is never used.
Looking at your problem we see the same sort of recursive structure. The predicates are quite complex, so let's take them in pieces.
connectRow(_, _, 0).
This says connectRow(X, Y, 0) is true, regardless of X and Y. This is the base case.
connectRow([spot(_, R, _, _)|Spots], R, K) :-
This rule is matching a list of spots of a particular structure, presuming the first spot's second value (R) matches the second parameter.
K1 is K-1, connectRow(Spots, R, K1).
The body of this clause is essentially recurring on decrementing K, the third parameter.
It's clear now that this is basically going to generate a list that looks like [spot(_, R, _, _), spot(_, R, _, _), ... spot(_, R, _, _)] with length = K and no particular values in the other three positions for spot. And indeed that's what we see when we test it:
?- connectRow(X, Y, 0).
true ;
(infinite loop)^CAction (h for help) ? abort
% Execution Aborted
?- connectRow(X, Y, 2).
X = [spot(_G906, Y, _G908, _G909), spot(_G914, Y, _G916, _G917)|_G912] ;
(infinite loop)^CAction (h for help) ? abort
So there seem to be a few bugs here; if I were sure these were the whole story I would say:
The base case should use the empty list rather than matching anything
We should stipulate in the inductive case that K > 0
We should use clpfd if we want to be able to generate all possibilities
Making the changes we get slightly different behavior:
:- use_module(library(clpfd)).
connectRow([], _, 0).
connectRow([spot(_, R, _, _)|Spots], R, K) :-
K #> 0, K1 #= K-1, connectRow(Spots, R, K1).
?- connectRow(X, Y, 0).
X = [] ;
false.
?- connectRow(X, Y, 1).
X = [spot(_G906, Y, _G908, _G909)] ;
false.
?- connectRow(X, Y, Z).
X = [],
Z = 0 ;
X = [spot(_G918, Y, _G920, _G921)],
Z = 1 ;
X = [spot(_G918, Y, _G920, _G921), spot(_G1218, Y, _G1220, _G1221)],
Z = 2
You'll note that in the result we have Y standing in our spot structures, but we have weird looking automatically generated variables in the other positions, such as _G918. As it happens, we could use _ instead of Y and see a similar effect:
?- connectRow(X, _, Z).
X = [],
Z = 0 ;
X = [spot(_G1269, _G1184, _G1271, _G1272)],
Z = 1 ;
X = [spot(_G1269, _G1184, _G1271, _G1272), spot(_G1561, _G1184, _G1563, _G1564)],
Z = 2
All of these strange looking variables are there because we used _. Note that all of the spot structures have the exact same generated variable in the second position, because Prolog was told it had to unify the second parameter of connectRow with the second position of spot. It's true everywhere because R is "passed along" to the next call to connectRow, recursively.
Hopefully this helps explain what's going on with the _ in your example, and also Prolog unification in general.
Edit: Unifying something with R
To answer your question below, you can unify R with a value directly, or by binding it to a variable and using the variable. For instance, we can bind it directly:
?- connectRow(X, 'Hello, world!', 2).
X = [spot(_G275, 'Hello, world!', _G277, _G278), spot(_G289, 'Hello, world!', _G291, _G292)]
We can also bind it and then assign it later:
?- connectRow(X, R, 2), R='Neato'.
X = [spot(_G21, 'Neato', _G23, _G24), spot(_G29, 'Neato', _G31, _G32)],
R = 'Neato'
There's nothing special about saying R=<foo>; it unifies both sides of the expression, but both sides can be expressions rather than variables:
?- V = [2,3], [X,Y,Z] = [1|V].
V = [2, 3],
X = 1,
Y = 2,
Z = 3.
So you can use R in another predicate just as well:
?- connectRow(X, R, 2), append([1,2], [3,4], R).
X = [spot(_G33, [1, 2, 3, 4], _G35, _G36), spot(_G41, [1, 2, 3, 4], _G43, _G44)],
R = [1, 2, 3, 4] ;
Note that this creates opportunities for backtracking and generating other solutions. For instance:
?- connectRow(X, R, 2), length(R, _).
X = [spot(_G22, [], _G24, _G25), spot(_G30, [], _G32, _G33)],
R = [] ;
X = [spot(_G22, [_G35], _G24, _G25), spot(_G30, [_G35], _G32, _G33)],
R = [_G35] ;
X = [spot(_G22, [_G35, _G38], _G24, _G25), spot(_G30, [_G35, _G38], _G32, _G33)],
R = [_G35, _G38] ;
Hope this helps!

Prolog - List of sequence from f0 to fN

The question require me to write a predicate seqList(N, L), which is satisfied when L is the list [f0, . . . , fN].
Where the fN = fN-1 + fN-2 + fN-3
My code is to compare the head of a list given, and will return true or false when compared.
seqList(_,[]).
seqList(N,[H|T]) :-
N1 is N - 1,
seq(N,H),
seqList(N1,T).
However, it only valid when the value is reversed,
e.g. seqList(3,[1,1,0,0]) will return true, but the list should return me true for
seqList(3,[0,0,1,1]). Is there any way for me to reverse the list and verifies it correctly?
It seems that you want to generate N elements of a sequence f such that f(N) = f(N-1) + f(N-2) + f(N-3) where f(X) is the X-th element of the sequence list, 0-based. The three starting elements must be pre-set as part of the specification as well. You seem to be starting with [0,0,1, ...].
Using the approach from Lazy lists in Prolog?:
seqList(N,L):- N >= 3, !,
L=[0,0,1|X], N3 is N-3, take(N3, seq(0,0,1), X-[], _).
next( seq(A,B,C), D, seq(B,C,D) ):- D is A+B+C.
Now all these functions can be fused and inlined, to arrive at one recursive definition.
But you can do it directly. You just need to write down the question, to get the solution back.
question(N,L):-
Since you start with 0,0,1, ... write it down:
L = [0, 0, 1 | X],
since the three elements are given, we only need to find out N-3 more. Write it down:
N3 is N-3,
you've now reduced the problem somewhat. You now need to find N-3 elements and put them into the X list. Use a worker predicate for that. It also must know the three preceding numbers at each step:
worker( N3, 0, 0, 1, X).
So just write down what the worker must know:
worker(N, A, B, C, X):-
if N is 0, we must stop. X then is an empty list. Write it down.
N = 0, X = [] .
Add another clause, for when N is greater than 0.
worker(N, A, B, C, X):-
N > 0,
We know that the next element is the sum of the three preceding numbers. Write that down.
D is A + B + C,
the next element in the list is the top element of our argument list (the last parameter). Write it down:
X = [D | X2 ],
now there are one less elements to add. Write it down:
N2 is N - 1,
To find the rest of the list, the three last numbers are B, C, and D. Then the rest is found by worker in exactly the same way:
worker( N2, B, C, D, X2).
That's it. The question predicate is your solution. Rename it to your liking.

Single cycle permutations

Let's take a permutation of numbers {1,2,3,4} which has only one cycle in it. For example it can be: (2,3,4,1). I was wondering, how can I generate all such permutations using Prolog?
I know how to generate all permutations using select.
But I can't come up with an idea for how to generate only the one-cycle (i.e. single cycle) permutations.
Could someone give me a small prompt or advice?
My comment was intended as a hint for producing directly the single cycle permutations, rather than generating all permutations and filtering out the ones that consist of a single cycle.
We should perhaps clarify that two representations of permutations are frequently used. xyz writes "I know how [to] generate all permutation[s]," presumably meaning something like the code I gave in this 2006 forum post. Here all permutations are represented according to the way a list rearranges the items in some "standard order" list.
Obviously there are N! permutations of all kinds. How many of these are single cycle permutations? That question is easily answered by contemplating the other form useful for permutations, namely as a product of disjoint cycles. We need to distinguish between a cycle like (1,2,3,4) and the identity permutation [1,2,3,4]. Indeed the cycle (1,2,3,4) maps 1 to 2, 2 to 3, 3 to 4, and 4 back to 1, so rather than the identity permutation it would be [2,3,4,1] in its list representation.
Now a cycle loops back on itself, so it is arbitrary where we choose to begin the cycle notation. If we start at 1, for example, then the cycle is determined by the ordering of the following N-1 items. This shows there are (N-1)! permutations of N things that form a single cycle (necessarily of length N). Thus we can generate all single cycle permutations in cycle form easily enough, and the problem then reduces to converting from that cycle form to the list form of a permutation. [Note that in part Mog tackled the conversion going in the other direction: given a permutation as list, ferret out a cycle contained in that permutation (and see if it is full length).]
Here's my code for generating all the one-cycle list permutations of a given "standard order" list, oneCycle(Identity,Permuted):
oneCycle([H|T],P) :-
permute(T,S),
oneCycle2permute([H|S],[H|T],P).
permute([ ],[ ]) :- !.
permute(L,[H|T]) :-
omit(H,L,Z),
permute(Z,T).
omit(H,[H|T],T).
omit(X,[H|T],[H|Z]) :-
omit(X,T,Z).
oneCycle2permute(_,[ ],[ ]) :- !.
oneCycle2permute(C,[I|Is],[P|Ps]) :-
mapCycle(C,I,P),
oneCycle2permute(C,Is,Ps).
mapCycle([X],X,X) :- !.
mapCycle([H|T],X,Y) :-
mapCycleAux(H,T,X,Y).
mapCycleAux(Y,[X],X,Y) :- !.
mapCycleAux(X,[Y|_],X,Y) :- !.
mapCycleAux(_,[X,Y|_],X,Y) :- !.
mapCycleAux(H,[_|T],X,Y) :-
mapCycleAux(H,T,X,Y).
Couldn't you use the function for generating all permutations, and filter out the ones that aren't 'one-cycle permutations'? (Since I'm not at all clear on what 'one-cycle permutations' are, I'm afraid I can't help with writing that filter.)
one-cycle([H|T], Permutation) :-
permutation([H|T], Permutation),
cycle(H, [H], [H|T], Permutation, Cycle),
length(Cycle, CycleLength),
length([H|T], ListLength),
CycleLength =:= ListLength.
The cycle/5 predicate builds the cycle corresponding to the first argument you pass it. the second argument is an accumulator, initialized to [FirstArgument], the third and fourth one are the original List and Permutation, the last one is the result (the list containing the elements of the cycle).
cycle(Current, Acc, List, Permutation, Cycle) :-
The call to corresponds/4 retrieves the item that took the place of the first argument in the permutation :
corresponds(Current, List, Permutation, R),
If this item is in the cycle we're building, it means we're done building the cycle, so we unify Cycle and the accumulator (Acc).
( member(R, Acc)
-> Cycle = Acc
If not, we go on by calling recursively our predicate with the corresponding item we found and we add it to the accumulator, so that our building cycle now holds it :
; cycle(R, [R|Acc], List, Permutation, Cycle)).
corresponds(N, [N|_], [R|_], R) :-
!.
corresponds(N, [_|L], [_|P], R) :-
corresponds(N, L, P, R).
Usage :
?- one-cycle([1, 2, 3, 4], P).
P = [2, 3, 4, 1] ;
P = [3, 1, 4, 2] ;
P = [3, 4, 2, 1] ;
P = [2, 4, 1, 3] ;
P = [4, 1, 2, 3] ;
P = [4, 3, 1, 2] ;
false.
Thanks to the discussion in the answer by hardmath I was able to understand what it was all about.
It seems the solution is quite simply to replace the input list's tail with its permutation to form a cycle description, then transform that into its list representation by paring up each element with its next and sorting on the first component to get the list of the second components as the result list:
single_cycled_permutation([A|B], R) :-
permutation(B, P),
cycle_pairs(A, A, P, CP),
sort( CP, SCP),
maplist( pair, SCP, _, R).
pair( X-Y, X, Y).
cycle_pairs( A, X, [Y|Z], [X-Y|W]) :-
cycle_pairs(A, Y, Z , W ).
cycle_pairs( A, X, [ ], [X-A] ).
To easier see the cycles simply remove the last goal in single_cycled_permutation:
single_cycled_pairs([A|B], SCP) :-
permutation(B, P),
cycle_pairs(A, A, P, CP),
sort( CP, SCP).
Testing:
21 ?- forall( single_cycled_pairs([1,2,3,4], SCP),
(maplist(pair,SCP,_,R), write((SCP,R)), nl)).
[1-2,2-3,3-4,4-1],[2,3,4,1]
[1-2,2-4,3-1,4-3],[2,4,1,3]
[1-3,2-4,3-2,4-1],[3,4,2,1]
[1-3,2-1,3-4,4-2],[3,1,4,2]
[1-4,2-3,3-1,4-2],[4,3,1,2]
[1-4,2-1,3-2,4-3],[4,1,2,3]
true.
See also:
Cyclic permutation
Cycles and fixed points

Resources