Knight's tour: Difference between revisions

275,724 bytes added ,  16 days ago
(Added a back tracking tie breaker)
 
(176 intermediate revisions by 52 users not shown)
Line 1:
{{task}}
[[File:Knight's_tour_7x7.png|400px||right]]
 
;Task
[[wp:Knight%27s_tour|Problem]]: you have a standard 8x8 chessboard, empty but for a single knight on some square. Your task is to emit a series of legal knight moves that result in the knight visiting every square on the chessboard exactly once. Note that it is ''not'' a requirement that the tour be "closed"; that is, the knight need not end within a single move of its start position.
 
Line 8 ⟶ 11:
Output: move sequence
 
 
;Cf.
;Related tasks
* [[A* search algorithm]]
* [[N-queens problem]]
* [[Solve a Hidato puzzle]]
* [[Solve a Holy Knight's tour]]
* [[Solve a Hopido puzzle]]
* [[Solve a Numbrix puzzle]]
* [[Solve the no connection puzzle]]
<br><br>
 
=={{header|11l}}==
{{trans|Python}}
 
<syntaxhighlight lang="11l">V _kmoves = [(2, 1), (1, 2), (-1, 2), (-2, 1), (-2, -1), (-1, -2), (1, -2), (2, -1)]
 
F chess2index(=chess, boardsize)
‘Convert Algebraic chess notation to internal index format’
chess = chess.lowercase()
V x = chess[0].code - ‘a’.code
V y = boardsize - Int(chess[1..])
R (x, y)
 
F boardstring(board, boardsize)
V r = 0 .< boardsize
V lines = ‘’
L(y) r
lines ‘’= "\n"r.map(x -> (I @board[(x, @y)] {‘#2’.format(@board[(x, @y)])} E ‘ ’)).join(‘,’)
R lines
 
F knightmoves(board, P, boardsize)
V (Px, Py) = P
V kmoves = Set(:_kmoves.map((x, y) -> (@Px + x, @Py + y)))
kmoves = Set(Array(kmoves).filter((x, y) -> x C 0 .< @boardsize & y C 0 .< @boardsize & !@board[(x, y)]))
R kmoves
 
F accessibility(board, P, boardsize)
[(Int, (Int, Int))] access
V brd = copy(board)
L(pos) knightmoves(board, P, boardsize' boardsize)
brd[pos] = -1
access.append((knightmoves(brd, pos, boardsize' boardsize).len, pos))
brd[pos] = 0
R access
 
F knights_tour(start, boardsize, _debug = 0B)
[(Int, Int) = Int] board
L(x) 0 .< boardsize
L(y) 0 .< boardsize
board[(x, y)] = 0
V move = 1
V P = chess2index(start, boardsize)
board[P] = move
move++
I _debug
print(boardstring(board, boardsize' boardsize))
L move <= board.len
P = min(accessibility(board, P, boardsize))[1]
board[P] = move
move++
I _debug
print(boardstring(board, boardsize' boardsize))
input("\n#2 next: ".format(move))
R board
 
L(boardsize, start) [(5, ‘c3’), (8, ‘h8’), (10, ‘e6’)]
print(‘boardsize: ’boardsize)
print(‘Start position: ’start)
V board = knights_tour(start, boardsize)
print(boardstring(board, boardsize' boardsize))
print()</syntaxhighlight>
 
{{out}}
<pre>
boardsize: 5
Start position: c3
 
19,12,17, 6,21
2, 7,20,11,16
13,18, 1,22, 5
8, 3,24,15,10
25,14, 9, 4,23
 
boardsize: 8
Start position: h8
 
38,41,18, 3,22,27,16, 1
19, 4,39,42,17, 2,23,26
40,37,54,21,52,25,28,15
5,20,43,56,59,30,51,24
36,55,58,53,44,63,14,29
9, 6,45,62,57,60,31,50
46,35, 8,11,48,33,64,13
7,10,47,34,61,12,49,32
 
boardsize: 10
Start position: e6
 
29, 4,57,24,73, 6,95,10,75, 8
58,23,28, 5,94,25,74, 7,100,11
3,30,65,56,27,72,99,96, 9,76
22,59, 2,63,68,93,26,81,12,97
31,64,55,66, 1,82,71,98,77,80
54,21,60,69,62,67,92,79,88,13
49,32,53,46,83,70,87,42,91,78
20,35,48,61,52,45,84,89,14,41
33,50,37,18,47,86,39,16,43,90
36,19,34,51,38,17,44,85,40,15
 
</pre>
 
=={{header|360 Assembly}}==
{{trans|BBC PASIC}}
<syntaxhighlight lang="360asm">* Knight's tour 20/03/2017
KNIGHT CSECT
USING KNIGHT,R13 base registers
B 72(R15) skip savearea
DC 17F'0' savearea
STM R14,R12,12(R13) save previous context
ST R13,4(R15) link backward
ST R15,8(R13) link forward
LR R13,R15 set addressability
MVC PG(20),=CL20'Knight''s tour ..x..'
L R1,NN n
XDECO R1,XDEC edit
MVC PG+14(2),XDEC+10 n
MVC PG+17(2),XDEC+10 n
XPRNT PG,L'PG print buffer
LA R0,1 1
ST R0,X x=1
ST R0,Y y=1
SR R0,R0 0
ST R0,TOTAL total=0
LOOP EQU * do loop
L R1,X x
BCTR R1,0 -1
MH R1,NNH *n
L R0,Y y
BCTR R0,0 -1
AR R1,R0 (x-1)*n+y-1
SLA R1,1 ((x-1)*n+y-1)*2
LA R0,1 1
STH R0,BOARD(R1) board(x,y)=1
L R2,TOTAL total
LA R2,1(R2) total+1
STH R2,DISP(R1) disp(x,y)=total+1
ST R2,TOTAL total=total+1
L R1,X x
L R2,Y y
BAL R14,CHOOSEMV call choosemv(x,y)
C R0,=F'0' until(choosemv(x,y)=0)
BNE LOOP loop
LA R2,KN*KN n*n
IF C,R2,NE,TOTAL THEN if total<>n*n then
XPRNT =C'error!!',7 print error
ENDIF , endif
LA R6,1 i=1
DO WHILE=(C,R6,LE,NN) do i=1 to n
MVC PG,=CL128' ' init buffer
LA R10,PG pgi=0
LA R7,1 j=1
DO WHILE=(C,R7,LE,NN) do j=1 to n
LR R1,R6 i
BCTR R1,0 -1
MH R1,NNH *n
LR R0,R7 j
BCTR R0,0 -1
AR R1,R0 (i-1)*n+j-1
SLA R1,1 ((i-1)*n+j-1)*2
LH R2,DISP(R1) disp(i,j)
XDECO R2,XDEC edit
MVC 0(4,R10),XDEC+8 output
LA R10,4(R10) pgi+=4
LA R7,1(R7) j++
ENDDO , enddo j
XPRNT PG,L'PG print buffer
LA R6,1(R6) i++
ENDDO , enddo i
L R13,4(0,R13) restore previous savearea pointer
LM R14,R12,12(R13) restore previous context
XR R15,R15 return_code=0
BR R14 exit
*------- ---- ----------------------------------------
CHOOSEMV EQU * choosemv(xc,yc)
ST R14,SAVEACMV save return point
ST R1,XC store xc
ST R2,YC store yc
MVC MM,=F'9' m=9
L R1,XC xc
LA R1,1(R1)
L R2,YC yc
LA R2,2(R2)
BAL R14,TRYMV call trymv(xc+1,yc+2)
L R1,XC xc
LA R1,1(R1)
L R2,YC yc
SH R2,=H'2'
BAL R14,TRYMV call trymv(xc+1,yc-2)
L R1,XC xc
BCTR R1,0
L R2,YC yc
LA R2,2(R2)
BAL R14,TRYMV call trymv(xc-1,yc+2)
L R1,XC xc
BCTR R1,0
L R2,YC yc
SH R2,=H'2'
BAL R14,TRYMV call trymv(xc-1,yc-2)
L R1,XC xc
LA R1,2(R1)
L R2,YC yc
LA R2,1(R2)
BAL R14,TRYMV call trymv(xc+2,yc+1)
L R1,XC xc
LA R1,2(R1)
L R2,YC yc
BCTR R2,0
BAL R14,TRYMV call trymv(xc+2,yc-1)
L R1,XC xc
SH R1,=H'2'
L R2,YC yc
LA R2,1(R2)
BAL R14,TRYMV call trymv(xc-2,yc+1)
L R1,XC xc
SH R1,=H'2'
L R2,YC yc
BCTR R2,0
BAL R14,TRYMV call trymv(xc-2,yc-1)
L R4,MM m
IF C,R4,EQ,=F'9' THEN if m=9 then
LA R0,0 return(0)
ELSE , else
MVC X,NEWX x=newx
MVC Y,NEWY y=newy
LA R0,1 return(1)
ENDIF , endif
L R14,SAVEACMV restore return point
BR R14 return
SAVEACMV DS A return point
*------- ---- ----------------------------------------
TRYMV EQU * trymv(xt,yt)
ST R14,SAVEATMV save return point
ST R1,XT store xt
ST R2,YT store yt
SR R10,R10 n=0
BAL R14,VALIDMV
IF LTR,R0,Z,R0 THEN if validmv(xt,yt)=0 then
LA R0,0 return(0)
B RETURTMV
ENDIF , endif
L R1,XT
LA R1,1(R1) xt+1
L R2,YT
LA R2,2(R2) yt+2
BAL R14,VALIDMV
IF C,R0,EQ,=F'1' THEN if validmv(xt+1,yt+2)=1 then
LA R10,1(R10) n=n+1;
ENDIF , endif
L R1,XT
LA R1,1(R1) xt+1
L R2,YT
SH R2,=H'2' yt-2
BAL R14,VALIDMV
IF C,R0,EQ,=F'1' THEN if validmv(xt+1,yt-2)=1 then
LA R10,1(R10) n=n+1;
ENDIF , endif
L R1,XT
BCTR R1,0 xt-1
L R2,YT
LA R2,2(R2) yt+2
BAL R14,VALIDMV
IF C,R0,EQ,=F'1' THEN if validmv(xt-1,yt+2)=1 then
LA R10,1(R10) n=n+1;
ENDIF , endif
L R1,XT
BCTR R1,0 xt-1
L R2,YT
SH R2,=H'2' yt-2
BAL R14,VALIDMV
IF C,R0,EQ,=F'1' THEN if validmv(xt-1,yt-2)=1 then
LA R10,1(R10) n=n+1;
ENDIF , endif
L R1,XT
LA R1,2(R1) xt+2
L R2,YT
LA R2,1(R2) yt+1
BAL R14,VALIDMV
IF C,R0,EQ,=F'1' THEN if validmv(xt+2,yt+1)=1 then
LA R10,1(R10) n=n+1;
ENDIF , endif
L R1,XT
LA R1,2(R1) xt+2
L R2,YT
BCTR R2,0 yt-1
BAL R14,VALIDMV
IF C,R0,EQ,=F'1' THEN if validmv(xt+2,yt-1)=1 then
LA R10,1(R10) n=n+1;
ENDIF , endif
L R1,XT
SH R1,=H'2' xt-2
L R2,YT
LA R2,1(R2) yt+1
BAL R14,VALIDMV
IF C,R0,EQ,=F'1' THEN if validmv(xt-2,yt+1)=1 then
LA R10,1(R10) n=n+1;
ENDIF , endif
L R1,XT
SH R1,=H'2' xt-2
L R2,YT
BCTR R2,0 yt-1
BAL R14,VALIDMV
IF C,R0,EQ,=F'1' THEN if validmv(xt-2,yt-1)=1 then
LA R10,1(R10) n=n+1;
ENDIF , endif
IF C,R10,LT,MM THEN if n<m then
ST R10,MM m=n
MVC NEWX,XT newx=xt
MVC NEWY,YT newy=yt
ENDIF , endif
RETURTMV L R14,SAVEATMV restore return point
BR R14 return
SAVEATMV DS A return point
*------- ---- ----------------------------------------
VALIDMV EQU * validmv(xv,yv)
C R1,=F'1' if xv<1 then
BL RET0
C R1,NN if xv>nn then
BH RET0
C R2,=F'1' if yv<1 then
BL RET0
C R2,NN if yv>nn then
BNH OK
RET0 SR R0,R0 return(0)
B RETURVMV
OK LR R3,R1 xv
BCTR R3,0
MH R3,NNH *n
LR R0,R2 yv
BCTR R0,0
AR R3,R0
SLA R3,1
LH R4,BOARD(R3) board(xv,yv)
IF LTR,R4,Z,R4 THEN if board(xv,yv)=0 then
LA R0,1 return(1)
ELSE , else
SR R0,R0 return(0)
ENDIF , endif
RETURVMV BR R14 return
* ---- ----------------------------------------
KN EQU 8 n compile-time
NN DC A(KN) n fullword
NNH DC AL2(KN) n halfword
BOARD DC (KN*KN)H'0' dim board(n,n) init 0
DISP DC (KN*KN)H'0' dim disp(n,n) init 0
X DS F
Y DS F
TOTAL DS F
XC DS F
YC DS F
MM DS F
NEWX DS F
NEWY DS F
XT DS F
YT DS F
XDEC DS CL12
PG DC CL128' ' buffer
YREGS
END KNIGHT</syntaxhighlight>
{{out}}
<pre>
Knight's tour 8x 8
1 4 57 20 47 6 49 22
34 19 2 5 58 21 46 7
3 56 35 60 37 48 23 50
18 33 38 55 52 59 8 45
39 14 53 36 61 44 51 24
32 17 40 43 54 27 62 9
13 42 15 30 11 64 25 28
16 31 12 41 26 29 10 63
</pre>
 
=={{header|Ada}}==
 
First, we specify a naive implementation the package Knights_Tour with naive backtracking. It is a bit more general than required for this task, by providing a mechanism '''not''' to visit certain coordinates. This mechanism is actually useful for the task [[Solve a Holy Knight's tour#Ada]], which also uses the package Knights_Tour.
First, we specify a naive implementation with naive backtracking:
 
<langsyntaxhighlight Adalang="ada">generic
Size: Integer;
package Knights_Tour is
 
subtype Index is Integer range 1 .. Size;
type Tour is array (Index, Index) of Natural;
Empty: Tour := (others => (others => 0));
 
function Get_Tour(Start_X, Start_Y: Index) return Tour;
function Get_Tour(Start_X, Start_Y: Index; Scene: Tour := Empty) return Tour;
-- finds tour via backtracking
-- either no tour has been found, (Get_Tour(Xi.e., Y)=0 for all X, YGet_Tour inreturns Index)Scene
-- or the Result(X,Y)=K if and only if I,J is visited at the K-th move
-- for all X, Y, Scene(X,Y) must be either 0 or Natural'Last,
 
-- where Scene(X,Y)=Natural'Last means "don't visit coordiates (X,Y)!"
procedure Tour_IO(The_Tour: Tour);
function Count_Moves(Board: Tour) return Natural;
-- counts the number of possible moves, i.e., the number of 0's on the board
procedure Tour_IO(The_Tour: Tour; Width: Natural := 4);
-- writes The_Tour to the output using Ada.Text_IO;
 
end Knights_Tour;</langsyntaxhighlight>
 
Here is the implementation:
 
<langsyntaxhighlight Adalang="ada">with Ada.Text_IO, Ada.Integer_Text_IO;
 
package body Knights_Tour is
 
Visited: Tour;
-- Visited(I, J)=0: Not yet visited
-- Visited(I, J)=K: Visited during the k-th move
 
type Pair is array(1..2) of Integer;
type Pair_Array is array (Positive range <>) of Pair;
 
Pairs: constant Pair_Array (1..8)
:= ((-2,1),(-1,2),(1,2),(2,1),(2,-1),(1,-2),(-1,-2),(-2,-1));
-- possible places for the night to go (relative to visitthe ifcurrent Doneposition)
 
function Get_TourCount_Moves(Start_X, Start_YBoard: IndexTour) return TourNatural is
N: Natural := 0;
begin
for I in Index loop
for J in Index loop
if Board(I,J) < Natural'Last then
N := N + 1;
end if;
end loop;
end loop;
return N;
end Count_Moves;
function Get_Tour(Start_X, Start_Y: Index; Scene: Tour := Empty)
return Tour is
Done: Boolean;
Move_Count: Natural := Count_Moves(Scene);
Visited: Tour;
 
-- Visited(I, J) = 0: not yet visited
-- Visited(I, J) = K: visited at the k-th move
-- Visited(I, J) = Integer'Last: never visit
procedure Visit(X, Y: Index; Move_Number: Positive; Found: out Boolean) is
XX, YY: Integer;
Line 56 ⟶ 461:
Found := False;
Visited(X, Y) := Move_Number;
if Move_Number = Integer(Index'Last * Index'Last)Move_Count then
Found := True;
else
Line 73 ⟶ 478:
end if;
end Visit;
 
Done: Boolean;
begin
Visited := (others => (others => 0))Scene;
Visit(Start_X, Start_Y, 1, Done);
if not Done then
Visited := (others => (others => 0))Scene;
end if;
return Visited;
end Get_Tour;
 
procedure Tour_IO(The_Tour: Tour; Width: Natural := 4) is
begin
if The_Tour(1, 1) /= 0 then
for I in Index loop
for J in Index loop
if Ada.Integer_Text_IO.Put(The_Tour(I, J), 4);< Integer'Last then
Ada.Integer_Text_IO.Put(The_Tour(I, J), Width);
else
for W in 1 .. Width-1 loop
Ada.Text_IO.Put(" ");
end loop;
Ada.Text_IO.Put("-"); -- deliberately not visited
end if;
end loop;
Ada.Text_IO.New_Line;
end loop;
else
Ada.Text_IO.Put_Line("No Solution");
end if;
end Tour_IO;
 
end Knights_Tour;</langsyntaxhighlight>
 
Here is the main program:
 
<langsyntaxhighlight Adalang="ada">with Knights_Tour, Ada.Command_Line;
 
procedure Test_Knight is
Line 112 ⟶ 519:
begin
KT.Tour_IO(KT.Get_Tour(1, 1));
end Test_Knight;</langsyntaxhighlight>
 
For small sizes, this already works well (< 1 sec for size 8). Sample output:
Line 125 ⟶ 532:
50 43 30 61 14 63 28 7</pre>
 
For larger sizes we'll use Warnsdorff's heuristic (without any thoughtful tie breaking). We extendenhance the specification byadding a function Warnsdorff_Get_Tour. This enhancement of the package Knights_Tour will also be used for the task [[Solve a Holy Knight's tour#Ada]]. The specification of Warnsdorff_Get_Tour is the following.
<syntaxhighlight lang="ada">
 
<lang Ada> function Warnsdorff_Get_Tour(Start_X, Start_Y: Index); returnScene: Tour; := Empty)
return Tour;
-- uses Warnsdorff heurisitic to find a tour faster
-- same interface as Get_Tour</langsyntaxhighlight>
and the implementation by
<lang Ada> function Warnsdorff_Get_Tour(Start_X, Start_Y: Index) return Tour is
Done: Boolean;
 
Its implementation is as follows.
 
<syntaxhighlight lang="ada"> function Warnsdorff_Get_Tour(Start_X, Start_Y: Index; Scene: Tour := Empty)
return Tour is
Done: Boolean;
Visited: Tour; -- see comments from Get_Tour above
Move_Count: Natural := Count_Moves(Scene);
function Neighbors(X, Y: Index) return Natural is
Result: Natural := 0;
Line 145 ⟶ 558:
return Result;
end Neighbors;
 
procedure Sort(Options: in out Pair_Array) is
N_Bors: array(Options'Range) of Natural;
Line 170 ⟶ 583:
end loop;
end Sort;
 
procedure Visit(X, Y: Index; Move: Positive; Found: out Boolean) is
Next_Count: Natural range 0 .. 8 := 0;
Line 178 ⟶ 591:
Found := False;
Visited(X, Y) := Move;
if Move = Integer(Index'Last * Index'Last)Move_Count then
Found := True;
else
Line 191 ⟶ 604:
end if;
end loop;
 
Sort(Next_Steps(1 .. Next_Count));
 
for N in 1 .. Next_Count loop
Visit(Next_Steps(N)(1), Next_Steps(N)(2), Move+1, Found);
Line 200 ⟶ 613:
end if;
end loop;
 
-- if we didn't return above, we have to undo our move
Visited(X, Y) := 0;
end if;
end Visit;
 
begin
Visited := (others => (others => 0))Scene;
Visit(Start_X, Start_Y, 1, Done);
if not Done then
Visited := (others => (others => 0))Scene;
end if;
return Visited;
end Warnsdorff_Get_Tour;</langsyntaxhighlight>
 
The modification for the main program is trivial:
<langsyntaxhighlight Adalang="ada">with Knights_Tour, Ada.Command_Line;
 
procedure Test_Fast is
Line 226 ⟶ 639:
begin
KT.Tour_IO(KT.Warnsdorff_Get_Tour(1, 1));
end Test_Fast;</langsyntaxhighlight>
 
This works still well for somewhat larger sizes:
Line 254 ⟶ 667:
383 34 97 92 391 32 405 90 393 30 547 88 471 28 505 86 469 26 465 84 369 24 429 82
96 381 384 33 386 91 392 31 406 89 472 29 506 87 470 27 504 85 468 25 430 83 368 23</pre>
 
=={{header|ALGOL 68}}==
{{works with|ALGOL 68G|Any - tested with release 2.8.win32}}
<syntaxhighlight lang="algol68"># Non-recursive Knight's Tour with Warnsdorff's algorithm #
# If there are multiple choices, backtrack if the first choice doesn't #
# find a solution #
 
# the size of the board #
INT board size = 8;
 
 
# directions for moves #
INT nne = 1, nee = 2, see = 3, sse = 4, ssw = 5, sww = 6, nww = 7, nnw = 8;
 
INT lowest move = nne;
INT highest move = nnw;
 
# the vertical position changes of the moves #
# nne, nee, see, sse, ssw, sww, nww, nnw #
[]INT offset v = ( -2, -1, 1, 2, 2, 1, -1, -2 );
# the horizontal position changes of the moves #
# nne, nee, see, sse, ssw, sww, nww, nnw #
[]INT offset h = ( 1, 2, 2, 1, -1, -2, -2, -1 );
 
 
MODE SQUARE = STRUCT( INT move # the number of the move that caused #
# the knight to reach this square #
, INT direction # the direction of the move that #
# brought the knight here - one of #
# nne, nee, see, sse, ssw, sww, nww #
# or nnw - used for backtracking #
# zero for the first move #
);
 
# the board #
[ board size, board size ]SQUARE board;
 
# initialises the board so there are no used squares #
PROC initialise board = VOID:
FOR row FROM 1 LWB board TO 1 UPB board
DO
FOR col FROM 2 LWB board TO 2 UPB board
DO
board[ row, col ] := ( 0, 0 )
OD
OD; # initialise board #
 
 
INT iterations := 0;
INT backtracks := 0;
 
# prints the board #
PROC print tour = VOID:
BEGIN
 
print( ( " a b c d e f g h", newline ) );
print( ( " +--------------------------------", newline ) );
 
FOR row FROM 1 UPB board BY -1 TO 1 LWB board
DO
print( ( whole( row, -3 ) ) );
print( ( "|" ) );
 
FOR col FROM 2 LWB board TO 2 UPB board
DO
print( ( " " ) );
print( ( whole( move OF board[ row, col ], -3 ) ) )
OD;
print( ( newline ) )
OD
 
END; # print tour #
 
 
# determines whether a move to the specified row and column is possible #
PROC can move to = ( INT row, INT col )BOOL:
IF row > 1 UPB board
OR row < 1 LWB board
OR col > 2 UPB board
OR col < 2 LWB board
THEN
# the position is not on the board #
FALSE
ELSE
# the move is legal, check the square is unoccupied #
move OF board[ row, col ] = 0
FI;
 
 
# used to hold counts of the number of moves that could be made in each #
# direction from the current square #
[ lowest move : highest move ]INT possible move count;
 
 
# sets the elements of possible move count to the number of moves that #
# could be made in each direction from the specified row and col #
PROC count moves in each direction from = ( INT row, INT col )VOID:
FOR move direction FROM lowest move TO highest move
DO
 
INT new row = row + offset v[ move direction ];
INT new col = col + offset h[ move direction ];
 
IF NOT can move to( new row, new col )
THEN
# can't move to this square #
possible move count[ move direction ] := -1
ELSE
# a move in this direction is possible #
# - count the number of moves that could be made from it #
 
possible move count[ move direction ] := 0;
 
FOR subsequent move FROM lowest move TO highest move
DO
IF can move to( new row + offset v[ subsequent move ]
, new col + offset h[ subsequent move ]
)
THEN
# have a possible subsequent move #
possible move count[ move direction ] +:= 1
FI
OD
FI
 
OD;
 
 
 
# update the board to the first knight's tour found starting from #
# "start row" and "start col". #
# return TRUE if one was found, FALSE otherwise #
PROC find tour = ( INT start row, INT start col )BOOL:
BEGIN
 
initialise board;
 
BOOL result := TRUE;
 
INT move number := 1;
INT row := start row;
INT col := start col;
 
# the tour will be complete when we have made as many moves #
# as there squares on the board #
INT final move = ( ( ( 1 UPB board ) + 1 ) - 1 LWB board )
* ( ( ( 2 UPB board ) + 1 ) - 2 LWB board )
;
 
# the first move is to place the knight on the starting square #
board[ row, col ] := ( move number, lowest move - 1 );
# start off with an unknown direction for the best move #
INT best direction := lowest move - 1;
 
# attempt to find a sequence of moves that will reach each square once #
WHILE
move number < final move AND result
DO
 
iterations +:= 1;
 
# count the number of moves possible from each possible move #
# from this square #
count moves in each direction from( row, col );
 
# find the direction with the lowest number of subsequent moves #
 
IF best direction < lowest move
THEN
# must find the best direction to move in #
 
INT lowest move count := highest move + 1;
 
FOR move direction FROM lowest move TO highest move
DO
IF possible move count[ move direction ] >= 0
AND possible move count[ move direction ] < lowest move count
THEN
# have a move with fewer possible subsequent moves #
best direction := move direction;
lowest move count := possible move count[ move direction ]
FI
OD
 
ELSE
# following a backtrack - find an alternative with the same #
# lowest number of possible moves - if there are any #
# if there aren't, we will backtrack again #
 
INT lowest move count := possible move count[ best direction ];
 
WHILE
best direction +:= 1;
IF best direction > highest move
THEN
# no more possible moves with the lowest number of #
# subsequent moves #
FALSE
ELSE
# keep looking if the number of moves from this square #
# isn't the lowest #
possible move count[ best direction ] /= lowest move count
FI
DO
SKIP
OD
 
FI;
 
IF best direction <= highest move
AND best direction >= lowest move
THEN
# we found a best possible move #
 
INT new row = row + offset v[ best direction ];
INT new col = col + offset h[ best direction ];
 
row := new row;
col := new col;
move number +:= 1;
board[ row, col ] := ( move number, best direction );
 
best direction := lowest move - 1
 
ELSE
# no more moves from this position - backtrack #
 
IF move number = 1
THEN
# at the starting position - no solution #
result := FALSE
 
ELSE
# not at the starting position - undo the latest move #
 
backtracks +:= 1;
 
move number -:= 1;
 
INT curr row := row;
INT curr col := col;
 
best direction := direction OF board[ curr row, curr col ];
 
row -:= offset v[ best direction ];
col -:= offset h[ best direction ];
 
# reset the square we just backtracked from #
board[ curr row, curr col ] := ( 0, 0 )
 
FI
 
FI
 
OD;
 
result
END; # find tour #
 
 
main:(
 
# get the starting position #
 
CHAR row;
CHAR col;
 
WHILE
print( ( "Enter starting row(1-8) and col(a-h): " ) );
read ( ( row, col, newline ) );
row < "1" OR row > "8" OR col < "a" OR col > "h"
DO
SKIP
OD;
 
# calculate the tour from that position, if possible #
 
IF find tour( ABS row - ABS "0", ( ABS col - ABS "a" ) + 1 )
THEN
# found a solution #
print tour
ELSE
# couldn't find a solution #
print( ( "Solution not found - iterations: ", iterations
, ", backtracks: ", backtracks
, newline
)
)
FI
 
)</syntaxhighlight>
{{out}}
<pre>
Enter starting row(1-8) and col(a-h): 5d
a b c d e f g h
+--------------------------------
8| 51 18 53 20 41 44 3 6
7| 54 21 50 45 2 5 40 43
6| 17 52 19 58 49 42 7 4
5| 22 55 64 1 46 57 48 39
4| 33 16 23 56 59 38 29 8
3| 24 13 34 63 30 47 60 37
2| 15 32 11 26 35 62 9 28
1| 12 25 14 31 10 27 36 61
</pre>
 
=={{header|ATS}}==
<syntaxhighlight lang="ats">(*
Find Knight’s Tours.
 
Using Warnsdorff’s heuristic, find multiple solutions.
Optionally accept only closed tours.
 
Compile with:
patscc -O3 -DATS_MEMALLOC_GCBDW -o knights_tour knights_tour.dats -lgc
 
Usage: ./knights_tour [START_POSITION [MAX_TOURS [closed]]]
Examples:
./knights_tour (prints one tour starting from a1)
./knights_tour c5
./knights_tour c5 2000
./knights_tour c5 2000 closed
*)
 
#define ATS_DYNLOADFLAG 0 (* No initialization is needed. *)
 
#include "share/atspre_define.hats"
#include "share/atspre_staload.hats"
 
#define EMPTY_SQUARE ~1
macdef nil_move = @(~1, ~1)
 
fn
int_right_justified
{i : int}
{n : int | 0 <= n; n < 100}
(i : int i,
n : int n) :
string =
let
var buffer : @[char][100] = @[char][100] ('\0')
val _ = $extfcall (int, "snprintf", buffer, 100, "%*i", n, i)
in
strnptr2string (string1_copy ($UNSAFE.cast{string n} buffer))
end
 
typedef move_t (i : int,
j : int) =
@(int i, int j)
typedef move_t =
[i, j : int]
move_t (i, j)
 
fn
move_t_is_nil (move : move_t) :<>
bool =
let
val @(i, j) = move
val @(i_nil, j_nil) = nil_move
in
(i = i_nil && j = j_nil)
end
 
fn
move_t_fprint (f : FILEref,
move : move_t) :
void =
let
val @(i, j) = move
val letter = char2i 'a' + j - 1
val digit = char2i '0' + i
in
fileref_putc (f, letter);
fileref_putc (f, digit);
end
 
vtypedef chessboard_vt (t : t@ype,
n_ranks : int,
n_files : int,
p : addr) =
@{
pf_board = @[t][n_ranks * n_files] @ p |
n_ranks = uint n_ranks,
n_files = uint n_files,
n_squares = uint (n_ranks * n_files),
p_board = ptr p
}
vtypedef chessboard_vt (t : t@ype,
n_ranks : int,
n_files : int) =
[p : addr]
chessboard_vt (t, n_ranks, n_files, p)
vtypedef chessboard_vt (t : t@ype) =
[n_ranks, n_files : int]
chessboard_vt (t, n_ranks, n_files)
 
fn {t : t@ype}
chessboard_vt_make
{n_ranks, n_files : pos}
(n_ranks : uint n_ranks,
n_files : uint n_files,
fill : t) :
chessboard_vt (t, n_ranks, n_files) =
let
val size = u2sz (n_ranks * n_files)
val @(pf, pfgc | p) = array_ptr_alloc<t> (size)
val _ = array_initize_elt<t> (!p, size, fill)
prval _ = mfree_gc_v_elim pfgc (* Let the memory leak. *)
in
@{
pf_board = pf |
n_ranks = n_ranks,
n_files = n_files,
n_squares = n_ranks * n_files,
p_board = p
}
end
 
fn {t : t@ype}
chessboard_vt_get
{n_ranks, n_files : pos}
{i, j : int}
(chessboard : !chessboard_vt (t, n_ranks, n_files),
i : int i,
j : int j) :
t =
let
val index = (i - 1) + (u2i (chessboard.n_ranks) * (j - 1))
val _ = assertloc (0 <= index)
val _ = assertloc (index < u2i (chessboard.n_squares))
in
array_get_at (!(chessboard.p_board), index)
end
 
fn {t : t@ype}
chessboard_vt_set
{n_ranks, n_files : pos}
{i, j : int}
(chessboard : !chessboard_vt (t, n_ranks, n_files),
i : int i,
j : int j,
value : t) :
void =
let
val index = (i - 1) + (u2i (chessboard.n_ranks) * (j - 1))
val _ = assertloc (0 <= index)
val _ = assertloc (index < u2i (chessboard.n_squares))
in
array_set_at (!(chessboard.p_board), index, value)
end
 
extern fn {t : t@ype}
find_nth_position$equal (x : t,
y : t) :
bool
 
fn {t : t@ype}
find_nth_position
{n_ranks, n_files : pos}
(chessboard : !chessboard_vt (t, n_ranks, n_files),
n : t) :
[i, j : int]
move_t (i, j) =
let
val n_ranks = chessboard.n_ranks
val n_files = chessboard.n_files
 
fun
outer_loop {i : pos | i <= n_ranks + 1} .<n_ranks + 1 - i>.
(chessboard : !chessboard_vt (t, n_ranks, n_files),
i : int i) :
[i, j : int]
move_t (i, j) =
let
fun
inner_loop {j : pos | j <= n_files + 1} .<n_files + 1 - j>.
(chessboard : !chessboard_vt (t, n_ranks, n_files),
j : int j) :
[j : int]
int j =
if u2i n_files < j then
j
else
let
val v = chessboard_vt_get<t> (chessboard, i, j)
in
if find_nth_position$equal<t> (n, v) then
j
else
inner_loop (chessboard, succ j)
end
in
if u2i n_ranks < i then
nil_move
else
let
val j = inner_loop (chessboard, 1)
in
if j <= u2i n_files then
@(i, j)
else
outer_loop (chessboard, succ i)
end
end
in
outer_loop (chessboard, 1)
end
 
implement
find_nth_position$equal<int> (x, y) =
x = y
 
fn
knights_tour_is_closed
{n_ranks, n_files : pos}
(chessboard : !chessboard_vt (int, n_ranks, n_files)) :
bool =
let
val n_squares = chessboard.n_squares
val @(i1, j1) = find_nth_position<int> (chessboard, 1)
val @(i2, j2) = find_nth_position<int> (chessboard, u2i n_squares)
val i_diff = abs (i1 - i2)
val j_diff = abs (j1 - j2)
in
(i_diff = 1 && j_diff = 2) || (i_diff = 2 && j_diff = 1)
end
 
fn
knights_tour_board_fprint
{n_ranks, n_files : pos}
(f : FILEref,
chessboard : !chessboard_vt (int, n_ranks, n_files)) :
void =
{
val n_ranks = chessboard.n_ranks
val n_files = chessboard.n_files
 
fun
outer_loop {i : int | 0 <= i; i <= n_ranks} .<i>.
(chessboard : !chessboard_vt (int, n_ranks, n_files),
i : int i) :
void =
if 0 < i then
{
val _ = fileref_puts (f, " ")
val _ =
let
var j : [j : int] int j
in
for (j := 1; j <= u2i n_files; j := succ j)
fileref_puts (f, "+----")
end
val _ = fileref_puts (f, "+\n")
val _ = fileref_puts (f, int_right_justified (i, 2))
val _ = fileref_puts (f, " ")
 
fun
inner_loop {j : int | 1 <= j; j <= n_files + 1}
(chessboard : !chessboard_vt (int, n_ranks,
n_files),
j : int j) :
void =
if j <= u2i n_files then
{
val v = chessboard_vt_get<int> (chessboard, i, j)
val v = g1ofg0 v
val _ = fileref_puts (f, " | ")
val _ =
if v = EMPTY_SQUARE then
fileref_puts (f, " ")
else
fileref_puts (f, int_right_justified (g1ofg0 v, 2))
val _ = inner_loop (chessboard, succ j)
}
 
val _ = inner_loop (chessboard, 1)
val _ = fileref_puts (f, " |\n")
 
val _ = outer_loop (chessboard, pred i)
}
val _ = outer_loop (chessboard, u2i n_ranks)
val _ = fileref_puts (f, " ")
val _ =
let
var j : [j : int] int j
in
for (j := 1; j <= u2i n_files; j := succ j)
fileref_puts (f, "+----")
end
val _ = fileref_puts (f, "+\n")
val _ = fileref_puts (f, " ")
val _ =
let
var j : [j : int] int j
in
for (j := 1; j <= u2i n_files; j := succ j)
let
val letter = char2i 'a' + j - 1
in
fileref_puts (f, " ");
fileref_putc (f, letter)
end
end
}
 
fn
knights_tour_moves_fprint
{n_ranks, n_files : pos}
(f : FILEref,
chessboard : !chessboard_vt (int, n_ranks, n_files)) :
void =
{
prval _ = mul_pos_pos_pos (mul_make {n_ranks, n_files} ())
 
val n_ranks = chessboard.n_ranks
val n_files = chessboard.n_files
val n_squares = chessboard.n_squares
 
val @(pf, pfgc | p_positions) =
array_ptr_alloc<move_t> (u2sz n_squares)
val _ = array_initize_elt<move_t> (!p_positions, u2sz n_squares,
nil_move)
 
macdef positions = !p_positions
 
fun
loop {k : int | 0 <= k; k <= n_ranks * n_files}
.<n_ranks * n_files - k>.
(positions : &(@[move_t][n_ranks * n_files]),
chessboard : !chessboard_vt (int, n_ranks, n_files),
k : int k) :
void =
if k < u2i n_squares then
{
val i = u2i ((i2u k) mod n_ranks) + 1
val j = u2i ((i2u k) / n_ranks) + 1
val v = chessboard_vt_get<int> (chessboard, i, j)
val v = g1ofg0 v
val _ = assertloc (1 <= v)
val _ = assertloc (v <= u2i n_squares)
val _ = positions[v - 1] := @(i, j)
val _ = loop (positions, chessboard, succ k)
}
val _ = loop (positions, chessboard, 0)
 
fun
loop {k : int | 0 <= k; k < n_ranks * n_files}
.<n_ranks * n_files - k>.
(positions : &(@[move_t][n_ranks * n_files]),
k : int k) :
void =
if k < u2i (pred n_squares) then
{
val _ = move_t_fprint (f, positions[k])
val line_end = (((i2u (k + 1)) mod n_files) = 0U)
val _ =
fileref_puts (f, (if line_end then " ->\n" else " -> "))
val _ = loop (positions, succ k)
}
val _ = loop (positions, 0)
val _ = move_t_fprint (f, positions[pred n_squares])
val _ =
if knights_tour_is_closed (chessboard) then
fileref_puts (f, " -> cycle")
 
val _ = array_ptr_free (pf, pfgc | p_positions)
}
 
typedef knights_moves_t =
@(move_t, move_t, move_t, move_t,
move_t, move_t, move_t, move_t)
 
fn
possible_moves {n_ranks, n_files : pos}
{i, j : int}
(chessboard : !chessboard_vt (int, n_ranks, n_files),
i : int i,
j : int j) :
knights_moves_t =
let
fn
try_move {istride, jstride : int}
(chessboard : !chessboard_vt (int, n_ranks, n_files),
istride : int istride,
jstride : int jstride) :
move_t =
let
val i1 = i + istride
val j1 = j + jstride
in
if i1 < 1 then
nil_move
else if u2i (chessboard.n_ranks) < i1 then
nil_move
else if j1 < 1 then
nil_move
else if u2i (chessboard.n_files) < j1 then
nil_move
else
let
val v = chessboard_vt_get (chessboard, i1, j1) : int
in
if v <> EMPTY_SQUARE then
nil_move
else
@(i1, j1)
end
end
 
val move0 = try_move (chessboard, 1, 2)
val move1 = try_move (chessboard, 2, 1)
val move2 = try_move (chessboard, 1, ~2)
val move3 = try_move (chessboard, 2, ~1)
val move4 = try_move (chessboard, ~1, 2)
val move5 = try_move (chessboard, ~2, 1)
val move6 = try_move (chessboard, ~1, ~2)
val move7 = try_move (chessboard, ~2, ~1)
in
@(move0, move1, move2, move3, move4, move5, move6, move7)
end
 
fn
count_following_moves
{n_ranks, n_files : pos}
{i, j : int}
{n_position : int}
(chessboard : !chessboard_vt (int, n_ranks, n_files),
move : move_t (i, j),
n_position : int n_position) :
uint =
if move_t_is_nil move then
0U
else
let
fn
succ_if_move_is_not_nil
{i, j : int}
(w : uint,
move : move_t (i, j)) :<>
uint =
if move_t_is_nil move then
w
else
succ w
 
val @(i, j) = move
val _ = chessboard_vt_set<int> (chessboard, i, j,
succ n_position)
val following_moves = possible_moves (chessboard, i, j)
 
val w = 0U
val w = succ_if_move_is_not_nil (w, following_moves.0)
val w = succ_if_move_is_not_nil (w, following_moves.1)
val w = succ_if_move_is_not_nil (w, following_moves.2)
val w = succ_if_move_is_not_nil (w, following_moves.3)
val w = succ_if_move_is_not_nil (w, following_moves.4)
val w = succ_if_move_is_not_nil (w, following_moves.5)
val w = succ_if_move_is_not_nil (w, following_moves.6)
val w = succ_if_move_is_not_nil (w, following_moves.7)
 
val _ = chessboard_vt_set<int> (chessboard, i, j, EMPTY_SQUARE)
in
w
end
 
fn
pick_w (w0 : uint,
w1 : uint,
w2 : uint,
w3 : uint,
w4 : uint,
w5 : uint,
w6 : uint,
w7 : uint) :<>
uint =
let
fn
next_pick (u : uint,
v : uint) :<>
uint =
if v = 0U then
u
else if u = 0U then
v
else
min (u, v)
 
val w = 0U
val w = next_pick (w, w0)
val w = next_pick (w, w1)
val w = next_pick (w, w2)
val w = next_pick (w, w3)
val w = next_pick (w, w4)
val w = next_pick (w, w5)
val w = next_pick (w, w6)
val w = next_pick (w, w7)
in
w
end
 
fn
next_moves {n_ranks, n_files : pos}
{i, j : int}
{n_position : int}
(chessboard : !chessboard_vt (int, n_ranks, n_files),
i : int i,
j : int j,
n_position : int n_position) :
knights_moves_t =
(* Prune and sort the moves according to Warnsdorff’s heuristic,
keeping only moves that have the minimum number of legal
following moves. *)
let
val moves = possible_moves (chessboard, i, j)
val w0 = count_following_moves (chessboard, moves.0, n_position)
val w1 = count_following_moves (chessboard, moves.1, n_position)
val w2 = count_following_moves (chessboard, moves.2, n_position)
val w3 = count_following_moves (chessboard, moves.3, n_position)
val w4 = count_following_moves (chessboard, moves.4, n_position)
val w5 = count_following_moves (chessboard, moves.5, n_position)
val w6 = count_following_moves (chessboard, moves.6, n_position)
val w7 = count_following_moves (chessboard, moves.7, n_position)
val w = pick_w (w0, w1, w2, w3, w4, w5, w6, w7)
in
if w = 0U then
@(nil_move, nil_move, nil_move, nil_move,
nil_move, nil_move, nil_move, nil_move)
else
@(if w0 = w then moves.0 else nil_move,
if w1 = w then moves.1 else nil_move,
if w2 = w then moves.2 else nil_move,
if w3 = w then moves.3 else nil_move,
if w4 = w then moves.4 else nil_move,
if w5 = w then moves.5 else nil_move,
if w6 = w then moves.6 else nil_move,
if w7 = w then moves.7 else nil_move)
end
 
fn
make_and_fprint_tours
{n_ranks, n_files : int}
{i, j : int}
{max_tours : int}
(f : FILEref,
n_ranks : int n_ranks,
n_files : int n_files,
i : int i,
j : int j,
max_tours : int max_tours,
closed_only : bool) :
void =
{
val n_ranks = max (1, n_ranks)
val n_files = max (1, n_files)
val i = max (1, min (n_ranks, i))
val j = max (1, min (n_files, j))
val max_tours = max (1, max_tours)
 
val n_ranks = i2u n_ranks
val n_files = i2u n_files
 
val i_start = i
val j_start = j
 
var tours_printed : int = 0
 
val chessboard =
chessboard_vt_make<int> (n_ranks, n_files, g1ofg0 EMPTY_SQUARE)
 
fun
explore {n_ranks, n_files : pos}
{i, j : int}
{n_position : int}
(chessboard : !chessboard_vt (int, n_ranks, n_files),
i : int i,
j : int j,
n_position : int n_position,
tours_printed : &int) :
void =
if tours_printed < max_tours then
let
fn
print_board {i1, j1 : int}
(chessboard : !chessboard_vt (int, n_ranks,
n_files),
tours_printed : &int) :
void =
begin
tours_printed := succ tours_printed;
fprintln! (f, "Tour number ", tours_printed);
knights_tour_moves_fprint (f, chessboard);
fprintln! (f);
knights_tour_board_fprint (f, chessboard);
fprintln! (f);
fprintln! (f)
end
 
fn
satisfies_closedness
{i1, j1 : int}
(move : move_t (i1, j1)) :
bool =
if closed_only then
let
val @(i1, j1) = move
val i_diff = abs (i1 - i_start)
val j_diff = abs (j1 - j_start)
in
(i_diff = 1 && j_diff = 2)
|| (i_diff = 2 && j_diff = 1)
end
else
true
 
fn
try_last_move
{i1, j1 : int}
(chessboard : !chessboard_vt (int, n_ranks,
n_files),
move : move_t (i1, j1),
tours_printed : &int) :
void =
if ~move_t_is_nil move && satisfies_closedness move then
let
val @(i1, j1) = move
in
chessboard_vt_set<int> (chessboard, i1, j1,
n_position + 1);
print_board (chessboard, tours_printed);
chessboard_vt_set<int> (chessboard, i1, j1,
EMPTY_SQUARE)
end
fun
explore_inner (chessboard : !chessboard_vt (int, n_ranks,
n_files),
tours_printed : &int) :
void =
if u2i (chessboard.n_squares) - n_position = 1 then
(* Is the last move possible? If so, make it and print
the board. (Only zero or one of the moves can be
non-nil.) *)
let
val moves = possible_moves (chessboard, i, j)
in
try_last_move (chessboard, moves.0, tours_printed);
try_last_move (chessboard, moves.1, tours_printed);
try_last_move (chessboard, moves.2, tours_printed);
try_last_move (chessboard, moves.3, tours_printed);
try_last_move (chessboard, moves.4, tours_printed);
try_last_move (chessboard, moves.5, tours_printed);
try_last_move (chessboard, moves.6, tours_printed);
try_last_move (chessboard, moves.7, tours_printed)
end
else
let
val moves = next_moves (chessboard, i, j, n_position)
macdef explore_move (move) =
begin
if ~move_t_is_nil ,(move) then
explore (chessboard, (,(move)).0, (,(move)).1,
succ n_position, tours_printed)
end
in
explore_move (moves.0);
explore_move (moves.1);
explore_move (moves.2);
explore_move (moves.3);
explore_move (moves.4);
explore_move (moves.5);
explore_move (moves.6);
explore_move (moves.7)
end
in
chessboard_vt_set<int> (chessboard, i, j, n_position);
explore_inner (chessboard, tours_printed);
chessboard_vt_set<int> (chessboard, i, j, EMPTY_SQUARE)
end
 
val _ = explore (chessboard, i, j, 1, tours_printed)
 
val _ = $UNSAFE.castvwtp0{void} chessboard
}
 
fn
algebraic_notation_to_move (s : string) :
move_t =
let
val s = g1ofg0 s
val n = string_length s
in
if n = 2 then
let
val i = g1ofg0 (char2i (s[1]) - char2i ('0'))
val j = g1ofg0 (char2i (s[0]) - char2i ('a') + 1)
in
@(i, j)
end
else
@(1, 1)
end
 
implement
main0 (argc, argv) =
{
val @(i, j) =
begin
if 2 <= argc then
algebraic_notation_to_move (argv[1])
else
@(1, 1)
end : move_t
 
val max_tours =
begin
if 3 <= argc then
$extfcall (int, "atoi", argv[2])
else
1
end : int
val max_tours = g1ofg0 max_tours
 
val closed_only =
begin
if 4 <= argc then
argv[3] = "closed"
else
false
end : bool
 
val _ = make_and_fprint_tours (stdout_ref, 8, 8, i, j, max_tours,
closed_only)
}</syntaxhighlight>
 
{{out}}
$ ./knights_tour c5 2 closed
<pre>Tour number 1
c5 -> a6 -> b8 -> d7 -> f8 -> h7 -> g5 -> h3 ->
g1 -> e2 -> c1 -> a2 -> b4 -> d3 -> e1 -> g2 ->
h4 -> g6 -> h8 -> f7 -> d8 -> b7 -> a5 -> b3 ->
a1 -> c2 -> a3 -> b1 -> d2 -> f3 -> h2 -> f1 ->
g3 -> h1 -> f2 -> e4 -> c3 -> a4 -> b2 -> d1 ->
e3 -> g4 -> h6 -> g8 -> f6 -> h5 -> f4 -> d5 ->
e7 -> c8 -> a7 -> c6 -> e5 -> c4 -> b6 -> a8 ->
c7 -> e8 -> d6 -> b5 -> d4 -> f5 -> g7 -> e6 -> cycle
+----+----+----+----+----+----+----+----+
8 | 56 | 3 | 50 | 21 | 58 | 5 | 44 | 19 |
+----+----+----+----+----+----+----+----+
7 | 51 | 22 | 57 | 4 | 49 | 20 | 63 | 6 |
+----+----+----+----+----+----+----+----+
6 | 2 | 55 | 52 | 59 | 64 | 45 | 18 | 43 |
+----+----+----+----+----+----+----+----+
5 | 23 | 60 | 1 | 48 | 53 | 62 | 7 | 46 |
+----+----+----+----+----+----+----+----+
4 | 38 | 13 | 54 | 61 | 36 | 47 | 42 | 17 |
+----+----+----+----+----+----+----+----+
3 | 27 | 24 | 37 | 14 | 41 | 30 | 33 | 8 |
+----+----+----+----+----+----+----+----+
2 | 12 | 39 | 26 | 29 | 10 | 35 | 16 | 31 |
+----+----+----+----+----+----+----+----+
1 | 25 | 28 | 11 | 40 | 15 | 32 | 9 | 34 |
+----+----+----+----+----+----+----+----+
a b c d e f g h
 
Tour number 2
c5 -> a6 -> b8 -> d7 -> f8 -> h7 -> g5 -> h3 ->
g1 -> e2 -> c1 -> a2 -> b4 -> d3 -> e1 -> g2 ->
h4 -> g6 -> h8 -> f7 -> d8 -> b7 -> a5 -> b3 ->
a1 -> c2 -> a3 -> b1 -> d2 -> f3 -> h2 -> f1 ->
g3 -> h1 -> f2 -> e4 -> c3 -> a4 -> b2 -> d1 ->
e3 -> g4 -> h6 -> g8 -> f6 -> h5 -> f4 -> d5 ->
e7 -> c8 -> a7 -> c6 -> e5 -> c4 -> b6 -> a8 ->
c7 -> b5 -> d6 -> e8 -> g7 -> f5 -> d4 -> e6 -> cycle
+----+----+----+----+----+----+----+----+
8 | 56 | 3 | 50 | 21 | 60 | 5 | 44 | 19 |
+----+----+----+----+----+----+----+----+
7 | 51 | 22 | 57 | 4 | 49 | 20 | 61 | 6 |
+----+----+----+----+----+----+----+----+
6 | 2 | 55 | 52 | 59 | 64 | 45 | 18 | 43 |
+----+----+----+----+----+----+----+----+
5 | 23 | 58 | 1 | 48 | 53 | 62 | 7 | 46 |
+----+----+----+----+----+----+----+----+
4 | 38 | 13 | 54 | 63 | 36 | 47 | 42 | 17 |
+----+----+----+----+----+----+----+----+
3 | 27 | 24 | 37 | 14 | 41 | 30 | 33 | 8 |
+----+----+----+----+----+----+----+----+
2 | 12 | 39 | 26 | 29 | 10 | 35 | 16 | 31 |
+----+----+----+----+----+----+----+----+
1 | 25 | 28 | 11 | 40 | 15 | 32 | 9 | 34 |
+----+----+----+----+----+----+----+----+
a b c d e f g h
</pre>
 
=={{header|AutoHotkey}}==
{{libheader|GDIP}}
<langsyntaxhighlight AutoHotkeylang="autohotkey">#SingleInstance, Force
#NoEnv
SetBatchLines, -1
Line 352 ⟶ 1,858:
If (A_Gui = 1)
PostMessage, 0xA1, 2
}</langsyntaxhighlight>
{{out}}
For start at b3
Line 358 ⟶ 1,864:
... plus an animation.
 
=={{header|BBC BASICAWK}}==
<syntaxhighlight lang="awk">
# syntax: GAWK -f KNIGHTS_TOUR.AWK [-v sr=x] [-v sc=x]
#
# examples:
# GAWK -f KNIGHTS_TOUR.AWK (default)
# GAWK -f KNIGHTS_TOUR.AWK -v sr=1 -v sc=1 start at top left (default)
# GAWK -f KNIGHTS_TOUR.AWK -v sr=1 -v sc=8 start at top right
# GAWK -f KNIGHTS_TOUR.AWK -v sr=8 -v sc=8 start at bottom right
# GAWK -f KNIGHTS_TOUR.AWK -v sr=8 -v sc=1 start at bottom left
#
BEGIN {
N = 8 # board size
if (sr == "") { sr = 1 } # starting row
if (sc == "") { sc = 1 } # starting column
split("2 2 -2 -2 1 1 -1 -1",X," ")
split("1 -1 1 -1 2 -2 2 -2",Y," ")
printf("\n%dx%d board: starting row=%d col=%d\n",N,N,sr,sc)
move(sr,sc,0)
exit(1)
}
function move(x,y,m) {
if (cantMove(x,y)) {
return(0)
}
P[x,y] = ++m
if (m == N ^ 2) {
printBoard()
exit(0)
}
tryBestMove(x,y,m)
}
function cantMove(x,y) {
return( P[x,y] || x<1 || x>N || y<1 || y>N )
}
function tryBestMove(x,y,m, i) {
i = bestMove(x,y)
move(x+X[i],y+Y[i],m)
}
function bestMove(x,y, arg1,arg2,c,i,min,out) {
# Warnsdorff's rule: go to where there are fewest next moves
min = N ^ 2 + 1
for (i in X) {
arg1 = x + X[i]
arg2 = y + Y[i]
if (!cantMove(arg1,arg2)) {
c = countNext(arg1,arg2)
if (c < min) {
min = c
out = i
}
}
}
return(out)
}
function countNext(x,y, i,out) {
for (i in X) {
out += (!cantMove(x+X[i],y+Y[i]))
}
return(out)
}
function printBoard( i,j,leng) {
leng = length(N*N)
for (i=1; i<=N; i++) {
for (j=1; j<=N; j++) {
printf(" %*d",leng,P[i,j])
}
printf("\n")
}
}
</syntaxhighlight>
<p>output:</p>
<pre>
8x8 board: starting row=1 col=1
1 50 15 32 61 28 13 30
16 33 64 55 14 31 60 27
51 2 49 44 57 62 29 12
34 17 56 63 54 47 26 59
3 52 45 48 43 58 11 40
18 35 20 53 46 41 8 25
21 4 37 42 23 6 39 10
36 19 22 5 38 9 24 7
</pre>
 
=={{header|BASIC}}==
==={{header|ANSI BASIC}}===
{{trans|BBC BASIC}}
[[File:Knights_Tour.gif|right]]
{{works with|Decimal BASIC}}
ANSI BASIC does not allow function parameters to be passed by reference, so X and Y were made global variables.
<syntaxhighlight lang="basic">100 DECLARE EXTERNAL FUNCTION choosemove
110 !
120 RANDOMIZE
130 PUBLIC NUMERIC X, Y, TRUE, FALSE
140 LET TRUE = -1
150 LET FALSE = 0
160 !
170 SET WINDOW 1,512,1,512
180 SET AREA COLOR "black"
190 FOR x=0 TO 512-128 STEP 128
200 FOR y=0 TO 512-128 STEP 128
210 PLOT AREA:x+64,y;x+128,y;x+128,y+64;x+64,y+64
220 PLOT AREA:x,y+64;x+64,y+64;x+64,y+128;x,y+128
230 NEXT y
240 NEXT x
250 !
260 SET LINE COLOR "red"
270 SET LINE WIDTH 6
280 !
290 PUBLIC NUMERIC Board(0 TO 7,0 TO 7)
300 LET X = 0
310 LET Y = 0
320 LET Total = 0
330 DO
340 LET Board(X,Y) = TRUE
350 PLOT LINES: X*64+32,Y*64+32;
360 LET Total = Total + 1
370 LOOP UNTIL choosemove(X, Y) = FALSE
380 IF Total <> 64 THEN STOP
390 END
400 !
410 EXTERNAL FUNCTION choosemove(X1, Y1)
420 DECLARE EXTERNAL SUB trymove
430 LET M = 9
440 CALL trymove(X1+1, Y1+2, M, newx, newy)
450 CALL trymove(X1+1, Y1-2, M, newx, newy)
460 CALL trymove(X1-1, Y1+2, M, newx, newy)
470 CALL trymove(X1-1, Y1-2, M, newx, newy)
480 CALL trymove(X1+2, Y1+1, M, newx, newy)
490 CALL trymove(X1+2, Y1-1, M, newx, newy)
500 CALL trymove(X1-2, Y1+1, M, newx, newy)
510 CALL trymove(X1-2, Y1-1, M, newx, newy)
520 IF M=9 THEN
530 LET choosemove = FALSE
540 EXIT FUNCTION
550 END IF
560 LET X = newx
570 LET Y = newy
580 LET choosemove = TRUE
590 END FUNCTION
600 !
610 EXTERNAL SUB trymove(X, Y, M, newx, newy)
620 !
630 DECLARE EXTERNAL FUNCTION validmove
640 IF validmove(X,Y) = 0 THEN EXIT SUB
650 IF validmove(X+1,Y+2) <> 0 THEN LET N = N + 1
660 IF validmove(X+1,Y-2) <> 0 THEN LET N = N + 1
670 IF validmove(X-1,Y+2) <> 0 THEN LET N = N + 1
680 IF validmove(X-1,Y-2) <> 0 THEN LET N = N + 1
690 IF validmove(X+2,Y+1) <> 0 THEN LET N = N + 1
700 IF validmove(X+2,Y-1) <> 0 THEN LET N = N + 1
710 IF validmove(X-2,Y+1) <> 0 THEN LET N = N + 1
720 IF validmove(X-2,Y-1) <> 0 THEN LET N = N + 1
730 IF N>M THEN EXIT SUB
740 IF N=M AND RND<.5 THEN EXIT SUB
750 LET M = N
760 LET newx = X
770 LET newy = Y
780 END SUB
790 !
800 EXTERNAL FUNCTION validmove(X,Y)
810 LET validmove = FALSE
820 IF X<0 OR X>7 OR Y<0 OR Y>7 THEN EXIT FUNCTION
830 IF Board(X,Y)=FALSE THEN LET validmove = TRUE
840 END FUNCTION</syntaxhighlight>
 
==={{header|BBC BASIC}}===
{{works with|BBC BASIC for Windows}}
[[Image:knights_tour_bbc.gif|right]]
<langsyntaxhighlight lang="bbcbasic"> VDU 23,22,256;256;16,16,16,128
VDU 23,23,4;0;0;0;
OFF
Line 420 ⟶ 2,092:
DEF FNvalidmove(X%,Y%)
IF X%<0 OR X%>7 OR Y%<0 OR Y%>7 THEN = FALSE
= NOT(Board%(X%,Y%))</langsyntaxhighlight>
 
=={{header|Bracmat}}==
<langsyntaxhighlight lang="bracmat"> ( knightsTour
= validmoves WarnsdorffSort algebraicNotation init solve
, x y fieldsToVisit
Line 527 ⟶ 2,199:
$ (algebraicNotation$(solve$((!x.!y).!fieldsToVisit)))
)
& out$(knightsTour$a1);</langsyntaxhighlight>
 
<pre>a1 b3 a5 b7 d8 f7 h8 g6 f8 h7 g5 h3 g1 e2 c1 a2 b4 a6 b8 c6 a7 c8 e7 g8 h6 g4 h2 f1 d2 b1 a3 c2 e1 f3 h4 g2 e3 d1 b2 a4 c3 b5 d4 f5 d6 c4 e5 d3 f2 h1 g3 e4 c5 d7 b6 a8 c7 d5 f4 e6 g7 e8 f6 h5</pre>
Line 535 ⟶ 2,207:
 
The following draws on console the progress of the horsie. Specify board size on commandline, or use default 8.
<langsyntaxhighlight lang="c">#include <stdio.h>
#include <stdlib.h>
#include <string.h>
Line 637 ⟶ 2,309:
 
return 0;
}</langsyntaxhighlight>
 
=={{header|C sharp}}==
<syntaxhighlight lang="csharp">using System;
using System.Collections.Generic;
 
namespace prog
{
class MainClass
{
const int N = 8;
readonly static int[,] moves = { {+1,-2},{+2,-1},{+2,+1},{+1,+2},
{-1,+2},{-2,+1},{-2,-1},{-1,-2} };
struct ListMoves
{
public int x, y;
public ListMoves( int _x, int _y ) { x = _x; y = _y; }
}
public static void Main (string[] args)
{
int[,] board = new int[N,N];
board.Initialize();
int x = 0, // starting position
y = 0;
List<ListMoves> list = new List<ListMoves>(N*N);
list.Add( new ListMoves(x,y) );
do
{
if ( Move_Possible( board, x, y ) )
{
int move = board[x,y];
board[x,y]++;
x += moves[move,0];
y += moves[move,1];
list.Add( new ListMoves(x,y) );
}
else
{
if ( board[x,y] >= 8 )
{
board[x,y] = 0;
list.RemoveAt(list.Count-1);
if ( list.Count == 0 )
{
Console.WriteLine( "No solution found." );
return;
}
x = list[list.Count-1].x;
y = list[list.Count-1].y;
}
board[x,y]++;
}
}
while( list.Count < N*N );
int last_x = list[0].x,
last_y = list[0].y;
string letters = "ABCDEFGH";
for( int i=1; i<list.Count; i++ )
{
Console.WriteLine( string.Format("{0,2}: ", i) + letters[last_x] + (last_y+1) + " - " + letters[list[i].x] + (list[i].y+1) );
last_x = list[i].x;
last_y = list[i].y;
}
}
static bool Move_Possible( int[,] board, int cur_x, int cur_y )
{
if ( board[cur_x,cur_y] >= 8 )
return false;
int new_x = cur_x + moves[board[cur_x,cur_y],0],
new_y = cur_y + moves[board[cur_x,cur_y],1];
if ( new_x >= 0 && new_x < N && new_y >= 0 && new_y < N && board[new_x,new_y] == 0 )
return true;
return false;
}
}
}</syntaxhighlight>
 
=={{header|C++}}==
Line 644 ⟶ 2,402:
Uses Warnsdorff's rule and (iterative) backtracking if that fails.
 
<langsyntaxhighlight lang="cpp">#include <iostream>
#include <iomanip>
#include <array>
Line 738 ⟶ 2,496:
continue;
 
++n;
get<2>(order[n]) = i + 1;
++n;
data[y+dy][x+dx] = n + 1;
order[n] = make_tuple(x+dx, y+dy, 0, sortMoves(x+dx, y+dy));
Line 787 ⟶ 2,545:
cout << b3 << endl;
return 0;
}</langsyntaxhighlight>
 
Output:
Line 838 ⟶ 2,596:
1, 62, 3, 68, 65, 60,237, 70, 95, 58,245, 72, 93, 56,311, 74, 91, 54,355, 76, 89, 52,157, 78, 87, 50,147, 80, 85, 48,145
</pre>
=={{header|Common Lisp}}==
{{works with|clisp|2.49}}
This interactive program will ask for a starting case in algebraic notation and, also, whether a closed tour is desired. Each next move is selected according to Warnsdorff's rule; ties are broken at random.
 
The closed tour algorithm is quite crude: just find tours over and over until one happens to be closed by chance.
=={{header|C sharp}}==
<lang csharp>using System;
using System.Collections.Generic;
 
This code is quite verbose: I tried to make it easy for myself and for others to follow and understand. I'm not a Lisp expert, so I probably missed some idiomatic shortcuts I could have used to make it shorter.
namespace prog
 
{
For some reason, the interactive part does not work with SBCL, but it works fine with CLISP.
class MainClass
<syntaxhighlight lang="lisp">;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
{
;;; Solving the knight's tour. ;;;
const int N = 8;
;;; Warnsdorff's rule with random tie break. ;;;
;;; Optionally outputs a closed tour. ;;;
readonly static int[,] moves = { {+1,-2},{+2,-1},{+2,+1},{+1,+2},
;;; Options from interactive prompt. {-1,+2},{-2,+1},{-2,-1},{-1,-2} };;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
struct ListMoves
 
{
(defparameter *side* 8)
public int x, y;
 
public ListMoves( int _x, int _y ) { x = _x; y = _y; }
(defun generate-chessboard (n)
}
(loop for i below n append
(loop for j below n collect (complex i j))))
public static void Main (string[] args)
 
{
(defparameter *chessboard*
int[,] board = new int[N,N];
(generate-chessboard *side*))
board.Initialize();
 
(defun complex->algebraic (n)
int x = 0, // starting position
;; returns a string like "b2"
y = 0;
(concatenate 'string
;; 'a' is char #97: add it to the offset
List<ListMoves> list = new List<ListMoves>(N*N);
(string (character (+ 97 (realpart n))))
list.Add( new ListMoves(x,y) );
;; indices start at 0, but algebraic starts at 1
(string (digit-char (+ 1 (imagpart n))))))
do
 
{
(defun algebraic->complex (string)
if ( Move_Possible( board, x, y ) )
;; takes a string like "e4"
{
(let ((row (char string 0))
int move = board[x,y];
(col (char string 1)))
board[x,y]++;
(complex (- (char-code row) 97)
x += moves[move,0];
(- (digit-char-p col) 1))))
y += moves[move,1];
 
list.Add( new ListMoves(x,y) );
(defconstant *knight-directions*
}
(list
else
(complex 1 2)
{
(complex 2 1)
if ( board[x,y] >= 8 )
(complex 1 -2)
{
(complex 2 -1)
board[x,y] = 0;
(complex -1 2)
list.RemoveAt(list.Count-1);
(complex -2 1)
if ( list.Count == 0 )
(complex -1 -2)
{
(complex -2 -1)))
Console.WriteLine( "No solution found." );
 
return;
(defun find-legal-moves (moves-list)
}
;; 2. the move must not be on a case already visited
x = list[list.Count-1].x;
(remove-if (lambda (m) (member m moves-list))
y = list[list.Count-1].y;
;; 1. the move must be within the chessboard
}
(intersection
board[x,y]++;
(mapcar (lambda (i) (+ (car moves-list) i)) *knight-directions*)
}
*chessboard*)))
}
 
while( list.Count < N*N );
 
;; Select between two moves by Warnsdorff's rule:
int last_x = list[0].x,
;; pick the one with the lowest index or else
last_y = list[0].y;
;; randomly break the tie.
string letters = "ABCDEFGH";
;; Takes a cons in the form (n . #C(x y)).
for( int i=1; i<list.Count; i++ )
;; This will be the sorting rule for picking the next move.
{
(defun w-rule (a b)
Console.WriteLine( string.Format("{0,2}: ", i) + letters[last_x] + (last_y+1) + " - " + letters[list[i].x] + (list[i].y+1) );
(cond ((< (car a) (car b)) t)
((> (car a) (car b)) nil)
last_x = list[i].x;
((= (car a) (car b))
last_y = list[i].y;
(zerop (random 2)))))
}
 
}
;; For every legal move in a given position,
;; look forward one move and return a cons
static bool Move_Possible( int[,] board, int cur_x, int cur_y )
;; in the form (n . #C(x y)) where n is
{
;; how many next free moves follow the first move.
if ( board[cur_x,cur_y] >= 8 )
(defun return-weighted-moves (moves)
return false;
(let ((candidates (find-legal-moves moves)))
(loop for mv in candidates collect
int new_x = cur_x + moves[board[cur_x,cur_y],0],
(cons
new_y = cur_y + moves[board[cur_x,cur_y],1];
(list-length (find-legal-moves (cons mv moves)))
mv))))
if ( new_x >= 0 && new_x < N && new_y >= 0 && new_y < N && board[new_x,new_y] == 0 )
 
return true;
;; Given a list of weighted moves (as above),
;; pick one according to the w-rule
return false;
(defun pick-among-weighted-moves (moves)
}
;; prune dead ends one move early
}
(let ((possible-moves
}</lang>
(remove-if (lambda(m) (zerop (car m))) moves)))
(cdar (sort possible-moves #'w-rule))))
 
(defun make-move (moves-list)
(let ((next-move
(if (< (list-length moves-list) (1- (list-length *chessboard*)))
(pick-among-weighted-moves (return-weighted-moves moves-list))
(car (find-legal-moves moves-list)))))
(cons next-move moves-list)))
 
(defun make-tour (moves-list)
;; takes a list of moves as an argument
(if (null (car moves-list)) ; last move not found: start over
(make-tour (last moves-list))
(if (= (list-length moves-list) (list-length *chessboard*))
moves-list
(make-tour (make-move moves-list)))))
 
(defun make-closed-tour (moves-list)
(let ((tour (make-tour moves-list)))
(if (tour-closed-p tour)
tour
(make-closed-tour moves-list))))
 
(defun tour-closed-p (tour)
;; takes a full tour as an argument
(let ((start (car (last tour)))
(end (car tour)))
;; is the first position a legal move, when
;; viewed from the last move?
(if (member start (find-legal-moves (list end))) ; find-legal-moves takes a list
t nil)))
 
(defun print-tour-linear (tour)
;; takes a tour (moves list) with the last move first
;; and prints it nicely in algebraic notation
(let ((moves (mapcar #'complex->algebraic (reverse tour))))
(format t "~{~A~^ -> ~}" moves)))
 
(defun tour->matrix (tour)
;; takes a tour and makes a row-by-row 2D matrix
;; from top to bottom (for further formatting & printing)
(flet ((index-tour (tour) ; 1st local function
(loop for i below (length tour)
;; starting from index 1, not 0, so add 1;
;; reverse because the last move is still in the car
collect (cons (nth i (reverse tour)) (1+ i))))
(get-row (n tour) ; 2nd local function
;; in every row, the imaginary part (vertical offset) stays the same
(remove-if-not (lambda (e) (= n (imagpart (car e)))) tour)))
(let* ((indexed-tour (index-tour tour))
(ordered-indexed-tour
;; make a list of ordered rows
(loop for i from (1- *side*) downto 0 collect
(sort (get-row i indexed-tour)
(lambda (a b) (< (realpart (car a)) (realpart (car b))))))))
;; clean up, leaving only the indices
(mapcar (lambda (e) (mapcar #'cdr e)) ordered-indexed-tour))))
 
(defun print-tour-matrix (tour)
(mapcar (lambda (row)
(format t "~{~3d~}~&" row)) (tour->matrix tour)))
 
;;; Handling options
 
(defstruct options
closed
start
grid)
 
(defparameter *opts* (make-options))
 
;;; Interactive part
 
(defun prompt()
(format t "Starting case (leave blank for random)? ")
(let ((start (string (read-line))))
(if (member start (mapcar #'complex->algebraic *chessboard*) :test #'equal)
(setf (options-start *opts*) start))
(format t "Require a closed tour (yes or default to no)? ")
(let ((closed (read-line)))
(if (or (equal closed "y") (equal closed "yes"))
(setf (options-closed *opts*) t)))))
 
(defun main ()
(let* ((start
(if (options-start *opts*)
(algebraic->complex (options-start *opts*))
(complex (random *side*) (random *side*))))
(closed (options-closed *opts*))
(tour
(if closed
(make-closed-tour (list start))
(make-tour (list start)))))
(fresh-line)
(if closed (princ "Closed "))
(princ "Knight's tour")
(if (options-start *opts*)
(princ ":")
(princ " (starting on a random case):"))
(fresh-line)
(print-tour-linear tour)
(princ #\newline)
(princ #\newline)
(print-tour-matrix tour)))
 
;;; Good to go: invocation!
 
(prompt)
(main)</syntaxhighlight>
{{out}}
<pre>Starting case (leave blank for random)? a8
Require a closed tour (yes or default to no)? y
 
Closed Knight's tour:
a8 -> c7 -> e8 -> g7 -> h5 -> g3 -> h1 -> f2 -> h3 -> g1 -> e2 -> c1 -> a2 -> b4 -> a6 -> b8 -> d7 -> f8 -> h7 -> g5 -> e6 -> d8 -> b7 -> a5 -> b3 -> a1 -> c2 -> e1 -> g2 -> f4 -> d3 -> c5 -> a4 -> b2 -> d1 -> c3 -> b1 -> a3 -> b5 -> a7 -> c6 -> d4 -> f3 -> h4 -> g6 -> h8 -> f7 -> e5 -> g4 -> h2 -> f1 -> d2 -> e4 -> f6 -> g8 -> h6 -> f5 -> e7 -> d5 -> e3 -> c4 -> d6 -> c8 -> b6
 
1 16 63 22 3 18 55 46
40 23 2 17 58 47 4 19
15 64 41 62 21 54 45 56
24 39 32 59 48 57 20 5
33 14 61 42 53 30 49 44
38 25 36 31 60 43 6 9
13 34 27 52 11 8 29 50
26 37 12 35 28 51 10 7</pre>
 
=={{header|Clojure}}==
Using warnsdorff's rule
<syntaxhighlight lang="clojure">
(defn isin? [x li]
(not= [] (filter #(= x %) li)))
 
(defn options [movements pmoves n]
(let [x (first (last movements)) y (second (last movements))
op (vec (map #(vector (+ x (first %)) (+ y (second %))) pmoves))
vop (filter #(and (>= (first %) 0) (>= (last %) 0)) op)
vop1 (filter #(and (< (first %) n) (< (last %) n)) vop)]
(vec (filter #(not (isin? % movements)) vop1))))
 
(defn next-move [movements pmoves n]
(let [op (options movements pmoves n)
sp (map #(vector % (count (options (conj movements %) pmoves n))) op)
m (apply min (map last sp))]
(first (rand-nth (filter #(= m (last %)) sp)))))
 
(defn jumps [n pos]
(let [movements (vector pos)
pmoves [[1 2] [1 -2] [2 1] [2 -1]
[-1 2] [-1 -2] [-2 -1] [-2 1]]]
(loop [mov movements x 1]
(if (= x (* n n))
mov
(let [np (next-move mov pmoves n)]
(recur (conj mov np) (inc x)))))))
</syntaxhighlight>
{{out}}
<pre>
(jumps 5 [0 0])
[[0 0] [1 2] [0 4] [2 3] [4 4] [3 2] [4 0] [2 1] [1 3] [0 1] [2 0] [4 1] [3 3] [1 4] [0 2] [1 0] [3 1] [4 3] [2 4] [0 3] [1 1] [3 0] [4 2] [3 4] [2 2]]
 
(jumps 8 [0 0])
[[0 0] [2 1] [4 0] [6 1] [7 3] [6 5] [7 7] [5 6] [3 7] [1 6] [0 4] [1 2] [2 0] [0 1] [1 3] [0 5] [1 7] [2 5] [0 6] [2 7] [4 6] [6 7] [7 5] [6 3] [7 1] [5 0] [3 1] [1 0] [0 2] [1 4] [3 5] [4 7] [6 6] [7 4] [6 2] [7 0] [5 1] [7 2] [6 0] [4 1] [5 3] [3 2] [4 4] [5 2] [3 3] [5 4] [4 2] [2 3] [1 1] [3 0] [2 2] [0 3] [2 4] [4 3] [6 4] [4 5] [2 6] [0 7] [1 5] [3 4] [5 5] [7 6] [5 7] [3 6]]
 
(let [j (jumps 40 [0 0])] ;; are
(and (distinct? j) ;; all squares only once? and
(= (count j) (* 40 40)))) ;; 40*40 squares?
true
</pre>
 
=={{header|CoffeeScript}}==
This algorithm finds 100,000 distinct solutions to the 8x8 problem in about 30 seconds. It precomputes knight moves up front, so it turns into a pure graph traversal problem. The program uses iteration and backtracking to find solutions.
<langsyntaxhighlight lang="coffeescript">
graph_tours = (graph, max_num_solutions) ->
# graph is an array of arrays
Line 1,042 ⟶ 2,969:
illustrate_knights_tour tours[0], BOARD_WIDTH
illustrate_knights_tour tours.pop(), BOARD_WIDTH
</syntaxhighlight>
</lang>
 
output
<syntaxhighlight lang="text">
> time coffee knight.coffee
100000 tours found (showing first and last)
Line 1,072 ⟶ 2,999:
user 0m25.656s
sys 0m0.253s
</syntaxhighlight>
</lang>
 
=={{header|D}}==
===Fast Version===
{{trans|C++}}
<langsyntaxhighlight lang="d">import std.stdio, std.algorithm, std.random, std.range,
std.conv, std.typecons, std.typetuple;
 
Line 1,152 ⟶ 3,080:
writeln();
}
}</langsyntaxhighlight>
{{out}}
<pre>23 16 11 6 21
Line 1,200 ⟶ 3,128:
4 67 64 61 238 69 96 59 244 71 94 57 310 73 92 55 354 75 90 53 374 77 88 51 156 79 86 49 146 81 84
1 62 3 68 65 60 237 70 95 58 245 72 93 56 311 74 91 54 355 76 89 52 157 78 87 50 147 80 85 48 145</pre>
 
===Shorter Version===
{{trans|Haskell}}
<syntaxhighlight lang="d">import std.stdio, std.math, std.algorithm, std.range, std.typecons;
 
alias Square = Tuple!(int,"x", int,"y");
 
const(Square)[] knightTour(in Square[] board, in Square[] moves) pure @safe nothrow {
enum findMoves = (in Square sq) pure nothrow @safe =>
cartesianProduct([1, -1, 2, -2], [1, -1, 2, -2])
.filter!(ij => ij[0].abs != ij[1].abs)
.map!(ij => Square(sq.x + ij[0], sq.y + ij[1]))
.filter!(s => board.canFind(s) && !moves.canFind(s));
auto newMoves = findMoves(moves.back);
if (newMoves.empty)
return moves;
//alias warnsdorff = min!(s => findMoves(s).walkLength);
//immutable newSq = newMoves.dropOne.fold!warnsdorff(newMoves.front);
auto pairs = newMoves.map!(s => tuple(findMoves(s).walkLength, s));
immutable newSq = reduce!min(pairs.front, pairs.dropOne)[1];
return board.knightTour(moves ~ newSq);
}
 
void main(in string[] args) {
enum toSq = (in string xy) => Square(xy[0] - '`', xy[1] - '0');
immutable toAlg = (in Square s) => [dchar(s.x + '`'), dchar(s.y + '0')];
immutable sq = toSq((args.length == 2) ? args[1] : "e5");
const board = iota(1, 9).cartesianProduct(iota(1, 9)).map!Square.array;
writefln("%(%-(%s -> %)\n%)", board.knightTour([sq]).map!toAlg.chunks(8));
}</syntaxhighlight>
{{out}}
<pre>e5 -> d7 -> b8 -> a6 -> b4 -> a2 -> c1 -> b3
a1 -> c2 -> a3 -> b1 -> d2 -> f1 -> h2 -> g4
h6 -> g8 -> e7 -> c8 -> a7 -> c6 -> a5 -> b7
d8 -> f7 -> h8 -> g6 -> f8 -> h7 -> f6 -> e8
g7 -> h5 -> g3 -> h1 -> f2 -> d1 -> b2 -> a4
b6 -> a8 -> c7 -> b5 -> c3 -> d5 -> e3 -> c4
d6 -> e4 -> c5 -> d3 -> e1 -> g2 -> h4 -> f5
d4 -> e2 -> f4 -> e6 -> g5 -> f3 -> g1 -> h3</pre>
 
=={{header|Delphi}}==
{{works with|Delphi|6.0}}
{{libheader|Forms,Types,SysUtils,Graphics,ExtCtrls}}
[[File:DelphiKnightsTour.png|thumb|none]]
Brute force method. Takes a long time for most solutions, so some optimization should be used. However, it has nice graphics.
 
<syntaxhighlight lang="Delphi">
{ These routines would normally be in a library,
but are presented here for clarity }
 
function PointAdd(V1,V2: TPoint): TPoint;
{Add V1 and V2}
begin
Result.X:= V1.X+V2.X;
Result.Y:= V1.Y+V2.Y;
end;
 
 
const KnightMoves: array [0..7] of TPoint = (
(X: 2; Y:1),(X: 2; Y:-1),
(X:-2; Y:1),(X:-2; Y:-1),
(X:1; Y: 2),(X:-1; Y: 2),
(X:1; Y:-2),(X:-1; Y:-2));
 
var Board: array [0..7,0..7] of boolean;
 
var Path: array of TPoint;
 
var CellSize,BoardSize: integer;
 
var CurPos: TPoint;
 
var BestPath: integer;
 
{-------------------------------------------------------------}
 
procedure DrawBestPath(Image: TImage);
begin
Image.Canvas.TextOut(BoardSize+5,5, IntToStr(BestPath));
end;
 
 
procedure PushPath(P: TPoint);
begin
SetLength(Path,Length(Path)+1);
Path[High(Path)]:=P;
if Length(Path)>BestPath then BestPath:=Length(Path);
end;
 
 
function PopPath: TPoint;
begin
if Length(Path)<1 then exit;
Result:=Path[High(Path)];
SetLength(Path,Length(Path)-1);
end;
 
 
procedure ClearPath;
begin
SetLength(Path,0);
end;
 
{-------- Routines to draw chess board and path --------------}
 
function GetCellCenter(P: TPoint): TPoint;
{Get pixel position of the center of cell}
begin
Result.X:=CellSize div 2 + CellSize * P.X;
Result.Y:=CellSize div 2 + CellSize * P.Y;
end;
 
 
 
procedure DrawPoint(Canvas: TCanvas; P: TPoint);
{Draw a point on the board}
begin
Canvas.Pen.Color:=clYellow;
Canvas.MoveTo(P.X-1,P.Y-1);
Canvas.LineTo(P.X+1,P.Y+1);
Canvas.MoveTo(P.X+1,P.Y-1);
Canvas.LineTo(P.X-1,P.Y+1);
end;
 
 
procedure DrawPathLine(Canvas: TCanvas; P1,P2: TPoint);
{Draw the path line}
var PS1,PS2: TPoint;
begin
PS1:=GetCellCenter(P1);
PS2:=GetCellCenter(P2);
Canvas.Pen.Width:=5;
Canvas.Pen.Color:=clRed;
Canvas.MoveTo(PS1.X,PS1.Y);
Canvas.LineTo(PS2.X,PS2.Y);
DrawPoint(Canvas,PS1);
DrawPoint(Canvas,PS2);
end;
 
 
procedure DrawPath(Canvas: TCanvas);
{Draw all points on the path}
var I: integer;
begin
for I:=0 to High(Path)-1 do
begin
DrawPathLine(Canvas, Path[I],Path[I+1]);
end;
end;
 
 
procedure DrawBoard(Canvas: TCanvas);
{Draw the chess board}
var R,R2: TRect;
var X,Y: integer;
var Color: TColor;
begin
Canvas.Pen.Color:=clBlack;
R:=Rect(0,0,BoardSize,BoardSize);
Canvas.Rectangle(R);
R:=Rect(0,0,CellSize,CellSize);
for Y:=0 to High(Board[0]) do
for X:=0 to High(Board) do
begin
R2:=R;
if ((X+Y) mod 2)=0 then Color:=clWhite
else Color:=clBlack;
Canvas.Brush.Color:=Color;
OffsetRect(R2,X * CellSize, Y * CellSize);
Canvas.Rectangle(R2);
end;
DrawPath(Canvas);
end;
 
 
function AllVisited: boolean;
{Test if all squares have been visit by path}
var X,Y: integer;
begin
Result:=False;
for Y:=0 to High(Board[0]) do
for X:=0 to High(Board) do
if not Board[X,Y] then exit;
Result:=True;
end;
 
 
 
procedure ClearBoard;
{Clear all board positions}
var X,Y: integer;
begin
for Y:=0 to High(Board[0]) do
for X:=0 to High(Board) do
Board[X,Y]:=False;
end;
 
 
 
function IsValidMove(Pos,Move: TPoint): boolean;
{Test if potential move is valid}
var NP: TPoint;
begin
Result:=False;
NP:=PointAdd(Pos,Move);
if (NP.X<0) or (NP.X>High(Board)) or
(NP.Y<0) or (NP.Y>High(Board[0])) then exit;
if Board[NP.X,NP.Y] then exit;
Result:=True;
end;
 
 
procedure ConfigureScreen(Image: TImage);
{Configure screen size}
begin
if Image.Width<Image.Height then BoardSize:=Image.Width
else BoardSize:=Image.Height;
CellSize:=BoardSize div 8;
end;
 
 
 
 
procedure SetPosition(Image: TImage; P: TPoint; Value: boolean);
{Set a new position by adding it to path}
{Marking position as used and redrawing board}
begin
if Value then PushPath(P)
else P:=PopPath;
Board[P.X,P.Y]:=Value;
DrawBoard(Image.Canvas);
DrawBestPath(Image);
Image.Repaint;
end;
 
 
 
procedure TryAllMoves(Image: TImage; Pos: TPoint);
{Recursively try all moves}
var I: integer;
var NewPos: TPoint;
begin
SetPosition(Image,Pos,True);
if AllVisited then exit;
for I:=0 to High(KnightMoves) do
begin
if AbortFlag then Exit;
if IsValidMove(Pos,KnightMoves[I]) then
begin
NewPos:=PointAdd(Pos,KnightMoves[I]);
TryAllMoves(Image,NewPos);
end;
end;
SetPosition(Image,Pos,False);
Application.ProcessMessages;
end;
 
 
procedure DoKnightsTour(Image: TImage);
{Solve Knights tour by testing all paths}
begin
BestPath:=0;
ConfigureScreen(Image);
ClearPath;
ClearBoard;
DrawBoard(Image.Canvas);
TryAllMoves(Image, Point(0,0));
end;
 
</syntaxhighlight>
{{out}}
 
<pre>
</pre>
 
=={{header|EchoLisp}}==
 
The algorithm uses iterative backtracking and Warnsdorff's heuristic. It can output closed or non-closed tours.
<syntaxhighlight lang="lisp">
(require 'plot)
(define *knight-moves*
'((2 . 1)(2 . -1 ) (1 . -2) (-1 . -2 )(-2 . -1) (-2 . 1) (-1 . 2) (1 . 2)))
(define *hit-squares* null)
(define *legal-moves* null)
(define *tries* 0)
 
(define (square x y n ) (+ y (* x n)))
(define (dim n) (1- (* n n))) ; n^2 - 1
 
;; check legal knight move from sq
;; return null or (list destination-square)
 
(define (legal-disp n sq k-move)
(let ((x (+ (quotient sq n) (first k-move)))
(y (+ (modulo sq n) (rest k-move))))
(if (and (>= x 0) (< x n) (>= y 0) (< y n))
(list (square x y n)) null)))
;; list of legal destination squares from sq
(define (legal-moves sq k-moves n )
(if (null? k-moves) null
(append (legal-moves sq (rest k-moves) n) (legal-disp n sq (first k-moves)))))
 
;; square freedom = number of destination squares not already reached
(define (freedom sq)
(for/sum ((dest (vector-ref *legal-moves* sq)))
(if (vector-ref *hit-squares* dest) 0 1)))
;; The chess adage" A knight on the rim is dim" is false here :
;; choose to move to square with smallest freedom : Warnsdorf's rule
(define (square-sort a b)
(< (freedom a) (freedom b)))
;; knight tour engine
(define (play sq step starter last-one wants-open)
(set! *tries* (1+ *tries*))
(vector-set! *hit-squares* sq step) ;; flag used square
(if (= step last-one) (throw 'HIT last-one)) ;; stop on first path found
 
(when (or wants-open ;; cut search iff closed path
(and (< step last-one) (> (freedom starter) 0))) ;; this ensures a closed path
(for ((target (list-sort square-sort (vector-ref *legal-moves* sq))))
(unless (vector-ref *hit-squares* target)
(play target (1+ step) starter last-one wants-open))))
(vector-set! *hit-squares* sq #f)) ;; unflag used square
(define (show-steps n wants-open)
(string-delimiter "")
(if wants-open
(printf "♘-tour: %d tries." *tries*)
(printf "♞-closed-tour: %d tries." *tries*))
(for ((x n))
(writeln)
(for((y n))
(write (string-pad-right (vector-ref *hit-squares* (square x y n)) 4)))))
 
 
(define (k-tour (n 8) (starter 0) (wants-open #t))
(set! *hit-squares* (make-vector (* n n) #f))
;; build vector of legal moves for squares 0..n^2-1
(set! *legal-moves*
(build-vector (* n n) (lambda(sq) (legal-moves sq *knight-moves* n))))
(set! *tries* 0) ; counter
(try
(play starter 0 starter (dim n) wants-open)
(catch (hit mess) (show-steps n wants-open))))
</syntaxhighlight>
 
 
{{out}}
<syntaxhighlight lang="lisp">
(k-tour 8 0 #f)
♞-closed-tour: 66 tries.
0 47 14 31 62 27 12 29
15 32 63 54 13 30 57 26
48 1 46 61 56 59 28 11
33 16 55 50 53 44 25 58
2 49 42 45 60 51 10 39
17 34 19 52 43 40 7 24
20 3 36 41 22 5 38 9
35 18 21 4 37 8 23 6
 
(k-tour 20 57)
♘-tour: 400 tries.
31 34 29 104 209 36 215 300 211 38 213 354 343 40 345 386 383 42 1 388
28 103 32 35 216 299 210 37 214 335 342 39 346 385 382 41 390 387 396 43
33 30 105 208 201 308 301 336 323 212 353 340 355 344 391 384 395 0 389 2
102 27 202 219 298 217 322 309 334 341 356 347 358 351 376 381 378 399 44 397
203 106 207 200 307 228 311 302 337 324 339 352 373 364 379 392 375 394 3 368
26 101 220 229 218 297 304 321 310 333 348 357 350 359 374 377 380 367 398 45
107 204 199 206 227 306 231 312 303 338 325 330 363 372 365 328 393 254 369 4
100 25 122 221 230 233 296 305 320 313 332 349 326 329 360 371 366 251 46 253
121 108 205 198 145 226 237 232 295 286 319 314 331 362 327 316 255 370 5 178
24 99 144 123 222 129 234 279 236 281 294 289 318 315 256 361 250 179 252 47
109 120 111 130 197 146 225 238 285 278 287 272 293 290 317 180 257 162 177 6
98 23 124 143 128 223 276 235 280 239 282 291 288 265 270 249 176 181 48 161
115 110 119 112 131 196 147 224 277 284 273 266 271 292 245 258 163 174 7 58
22 97 114 125 142 127 140 275 194 267 240 283 264 269 248 175 182 59 160 49
87 116 95 118 113 132 195 148 187 274 263 268 191 244 259 246 173 164 57 8
96 21 88 133 126 141 150 139 262 193 190 241 260 247 172 183 60 159 50 65
77 86 117 94 89 138 135 188 149 186 261 192 171 184 243 156 165 64 9 56
20 81 78 85 134 93 90 151 136 189 170 185 242 155 166 61 158 53 66 51
79 76 83 18 91 74 137 16 169 72 153 14 167 70 157 12 63 68 55 10
82 19 80 75 84 17 92 73 152 15 168 71 154 13 62 69 54 11 52 67
</syntaxhighlight>
 
;Plotting:
64 shades of gray. We plot the move sequence in shades of gray, from black to white. The starting square is red. The ending square is green. One can observe that the squares near the border are played first (dark squares).
<syntaxhighlight lang="lisp">
(define (step-color x y n last-one)
(letrec ((sq (square (floor x) (floor y) n))
(step (vector-ref *hit-squares* sq) n n))
(cond ((= 0 step) (rgb 1 0 0)) ;; red starter
((= last-one step) (rgb 0 1 0)) ;; green end
(else (gray (// step n n))))))
(define ( k-plot n)
(plot-rgb (lambda (x y) (step-color x y n (dim n))) (- n epsilon) (- n epsilon)))
</syntaxhighlight>
 
 
Closed path on a 12x12 board: [http://www.echolalie.org/echolisp/images/k-tour-12.png]
 
Open path on a 24x24 board: [http://www.echolalie.org/echolisp/images/k-tour-24.png]
 
=={{header|Elixir}}==
{{trans|Ruby}}
<syntaxhighlight lang="elixir">defmodule Board do
import Integer, only: [is_odd: 1]
defmodule Cell do
defstruct [:value, :adj]
end
@adjacent [[-1,-2],[-2,-1],[-2,1],[-1,2],[1,2],[2,1],[2,-1],[1,-2]]
defp initialize(rows, cols) do
board = for i <- 1..rows, j <- 1..cols, into: %{}, do: {{i,j}, true}
for i <- 1..rows, j <- 1..cols, into: %{} do
adj = for [di,dj] <- @adjacent, board[{i+di, j+dj}], do: {i+di, j+dj}
{{i,j}, %Cell{value: 0, adj: adj}}
end
end
defp solve(board, ij, num, goal) do
board = Map.update!(board, ij, fn cell -> %{cell | value: num} end)
if num == goal do
throw({:ok, board})
else
wdof(board, ij)
|> Enum.each(fn k -> solve(board, k, num+1, goal) end)
end
end
 
defp wdof(board, ij) do # Warnsdorf's rule
board[ij].adj
|> Enum.filter(fn k -> board[k].value == 0 end)
|> Enum.sort_by(fn k ->
Enum.count(board[k].adj, fn x -> board[x].value == 0 end)
end)
end
defp to_string(board, rows, cols) do
width = to_string(rows * cols) |> String.length
format = String.duplicate("~#{width}w ", cols)
Enum.map_join(1..rows, "\n", fn i ->
:io_lib.fwrite format, (for j <- 1..cols, do: board[{i,j}].value)
end)
end
def knight_tour(rows, cols, sx, sy) do
IO.puts "\nBoard (#{rows} x #{cols}), Start: [#{sx}, #{sy}]"
if is_odd(rows*cols) and is_odd(sx+sy) do
IO.puts "No solution"
else
try do
initialize(rows, cols)
|> solve({sx,sy}, 1, rows*cols)
IO.puts "No solution"
catch
{:ok, board} -> IO.puts to_string(board, rows, cols)
end
end
end
end
 
Board.knight_tour(8,8,4,2)
Board.knight_tour(5,5,3,3)
Board.knight_tour(4,9,1,1)
Board.knight_tour(5,5,1,2)
Board.knight_tour(12,12,2,2)</syntaxhighlight>
 
{{out}}
<pre>
Board (8 x 8), Start: [4, 2]
23 20 3 32 25 10 5 8
2 35 24 21 4 7 26 11
19 22 33 36 31 28 9 6
34 1 50 29 48 37 12 27
51 18 53 44 61 30 47 38
54 43 56 49 58 45 62 13
17 52 41 60 15 64 39 46
42 55 16 57 40 59 14 63
 
Board (5 x 5), Start: [3, 3]
19 8 3 14 25
2 13 18 9 4
7 20 1 24 15
12 17 22 5 10
21 6 11 16 23
 
Board (4 x 9), Start: [1, 1]
1 34 3 28 13 24 9 20 17
4 29 6 33 8 27 18 23 10
35 2 31 14 25 12 21 16 19
30 5 36 7 32 15 26 11 22
 
Board (5 x 5), Start: [1, 2]
No solution
 
Board (12 x 12), Start: [2, 2]
87 24 59 2 89 26 61 4 39 8 31 6
58 1 88 25 60 3 92 27 30 5 38 9
23 86 83 90 103 98 29 62 93 40 7 32
82 57 102 99 84 91 104 97 28 37 10 41
101 22 85 114 105 116 111 94 63 96 33 36
56 81 100 123 128 113 106 117 110 35 42 11
21 122 141 80 115 124 127 112 95 64 109 34
144 55 78 121 142 129 118 107 126 133 12 43
51 20 143 140 79 120 125 138 69 108 65 134
54 73 52 77 130 139 70 119 132 137 44 13
19 50 75 72 17 48 131 68 15 46 135 66
74 53 18 49 76 71 16 47 136 67 14 45
</pre>
 
=={{header|Elm}}==
<syntaxhighlight lang="elm">module Main exposing (main)
 
import Browser exposing (element)
import Html as H
import Html.Attributes as HA
import List exposing (filter, head, length, map, map2, member, tail)
import List.Extra exposing (andThen, minimumBy)
import String exposing (join)
import Svg exposing (g, line, rect, svg)
import Svg.Attributes exposing (fill, height, style, version, viewBox, width, x, x1, x2, y, y1, y2)
import Svg.Events exposing (onClick)
import Time exposing (every)
import Tuple
 
 
type alias Cell =
( Int, Int )
 
type alias BoardSize =
( Int, Int )
 
type alias Model =
{ path : List Cell
, board : List Cell
, pause_ms : Float
, size : BoardSize
}
 
type Msg
= Tick Time.Posix
| SetStart Cell
| SetSize BoardSize
| SetPause Float
 
boardsize_width: BoardSize -> Int
boardsize_width bs =
Tuple.second bs
 
boardsize_height: BoardSize -> Int
boardsize_height bs =
Tuple.first bs
 
boardsize_dec: Int -> Int
boardsize_dec n =
let
minimum_size = 3
in
if n <= minimum_size then
minimum_size
else
n - 1
boardsize_inc: Int -> Int
boardsize_inc n =
let
maximum_size = 40
in
if n >= maximum_size then
maximum_size
else
n + 1
 
pause_inc: Float -> Float
pause_inc n =
n + 10
 
-- decreasing pause time (ms) increases speed
pause_dec: Float -> Float
pause_dec n =
let
minimum_pause = 0
in
if n <= minimum_pause then
minimum_pause
else
n - 10
 
board_init : BoardSize -> List Cell
board_init board_size =
List.range 0 (boardsize_height board_size - 1)
|> andThen
(\r ->
List.range 0 (boardsize_width board_size - 1)
|> andThen
(\c ->
[ ( r, c ) ]
)
)
 
nextMoves : Model -> Cell -> List Cell
nextMoves model ( stRow, stCol ) =
let
c =
[ 1, 2, -1, -2 ]
 
km =
c
|> andThen
(\cRow ->
c
|> andThen
(\cCol ->
if abs cRow == abs cCol then
[]
 
else
[ ( cRow, cCol ) ]
)
)
 
jumps =
List.map (\( kmRow, kmCol ) -> ( kmRow + stRow, kmCol + stCol )) km
in
List.filter (\j -> List.member j model.board && not (List.member j model.path)) jumps
 
 
bestMove : Model -> Maybe Cell
bestMove model =
case List.head model.path of
Just mph ->
minimumBy (List.length << nextMoves model) (nextMoves model mph)
_ ->
Nothing
 
 
-- Initialize the application - https://guide.elm-lang.org/effects/
init : () -> ( Model, Cmd Msg )
init _ =
let
-- Initial board height and width
initial_size =
8
 
-- Initial chess board
initial_board =
board_init (initial_size, initial_size)
 
initial_path =
[]
initial_pause =
10
in
( Model initial_path initial_board initial_pause (initial_size, initial_size), Cmd.none )
 
 
-- View the model - https://guide.elm-lang.org/effects/
view : Model -> H.Html Msg
view model =
let
showChecker row col =
rect
[ x <| String.fromInt col
, y <| String.fromInt row
, width "1"
, height "1"
, fill <|
if modBy 2 (row + col) == 0 then
"blue"
 
else
"grey"
, onClick <| SetStart ( row, col )
]
[]
 
showMove ( row0, col0 ) ( row1, col1 ) =
line
[ x1 <| String.fromFloat (toFloat col0 + 0.5)
, y1 <| String.fromFloat (toFloat row0 + 0.5)
, x2 <| String.fromFloat (toFloat col1 + 0.5)
, y2 <| String.fromFloat (toFloat row1 + 0.5)
, style "stroke:yellow;stroke-width:0.05"
]
[]
 
render mdl =
let
checkers =
mdl.board
|> andThen
(\( r, c ) ->
[ showChecker r c ]
)
 
moves =
case List.tail mdl.path of
Nothing ->
[]
 
Just tl ->
List.map2 showMove mdl.path tl
in
checkers ++ moves
 
unvisited =
length model.board - length model.path
 
center =
[ HA.style "text-align" "center" ]
 
table =
[ HA.style "text-align" "center", HA.style "display" "table", HA.style "width" "auto", HA.style "margin" "auto" ]
table_row =
[ HA.style "display" "table-row", HA.style "width" "auto" ]
 
table_cell =
[ HA.style "display" "table-cell", HA.style "width" "auto", HA.style "padding" "1px 3px" ]
rows =
boardsize_height model.size
 
cols =
boardsize_width model.size
in
H.div
[]
[ H.h1 center [ H.text "Knight's Tour" ]
-- controls
, H.div
table
[ H.div -- labels
table_row
[ H.div
table_cell
[ H.text "Rows"]
, H.div
table_cell
[ H.text "Columns"]
, H.div
table_cell
[ H.text ""]
, H.div
table_cell
[ H.text "Pause (ms)"]
]
, H.div
table_row
[ H.div -- Increase
table_cell
[ H.button [onClick <| SetSize ( boardsize_inc rows, cols )] [ H.text "▲"] ]
, H.div
table_cell
[ H.button [onClick <| SetSize ( rows, boardsize_inc cols )] [ H.text "▲"] ]
, H.div
table_cell
[ H.text ""]
, H.div
table_cell
[ H.button [onClick <| SetPause ( pause_inc model.pause_ms )] [ H.text "▲"] ]
]
, H.div
table_row
[ H.div -- Value
table_cell
[ H.text <| String.fromInt rows ]
, H.div
table_cell
[ H.text <| String.fromInt cols]
, H.div
table_cell
[ H.text ""]
, H.div
table_cell
[ H.text <| String.fromFloat model.pause_ms]
]
, H.div
table_row
[ H.div -- Decrease
table_cell
[ H.button [onClick <| SetSize ( boardsize_dec rows, cols )] [ H.text "▼"] ]
, H.div
table_cell
[ H.button [onClick <| SetSize ( rows, boardsize_dec cols )] [ H.text "▼"] ]
, H.div
table_cell
[ H.text ""]
, H.div
table_cell
[ H.button [onClick <| SetPause ( pause_dec model.pause_ms )] [ H.text "▼"] ]
]
]
, H.h2 center [ H.text "(pick a square)" ]
, H.div -- chess board
center
[ svg
[ version "1.1"
, width (String.fromInt (25 * cols))
, height (String.fromInt (25 * rows))
, viewBox
(join " "
[ String.fromInt 0
, String.fromInt 0
, String.fromInt cols
, String.fromInt rows
]
)
]
[ g [] <| render model ]
]
, H.h3 center [ H.text <| "Unvisited count : " ++ String.fromInt unvisited ]
]
 
-- Update the model - https://guide.elm-lang.org/effects/
update : Msg -> Model -> ( Model, Cmd Msg )
update msg model =
let
mo =
case msg of
SetPause pause ->
{ model | pause_ms = pause }
 
SetSize board_size ->
{ model | board = board_init board_size, path = [], size = board_size }
 
SetStart start ->
{ model | path = [ start ] }
 
Tick _ ->
case model.path of
[] ->
model
 
_ ->
case bestMove model of
Nothing ->
model
 
Just best ->
{ model | path = best :: model.path }
in
( mo, Cmd.none )
 
 
-- Subscribe to https://guide.elm-lang.org/effects/
subscriptions : Model -> Sub Msg
subscriptions model =
Time.every model.pause_ms Tick
 
-- Application entry point
main: Program () Model Msg
main =
element -- https://package.elm-lang.org/packages/elm/browser/latest/Browser#element
{ init = init
, view = view
, update = update
, subscriptions = subscriptions
}
</syntaxhighlight>
 
Link to live demo: https://dmcbane.github.io/knights-tour/
 
=={{header|Erlang}}==
Again I use backtracking. It seemed easier this time.
<syntaxhighlight lang="erlang">
<lang Erlang>
-module( knights_tour ).
 
Line 1,282 ⟶ 4,076:
next_moves_row( 8 ) -> [6, 7];
next_moves_row( N ) -> [N - 2, N - 1, N + 1, N + 2].
</syntaxhighlight>
</lang>
{{out}}
<pre>
Line 1,305 ⟶ 4,099:
1 10 31 64 33 26 53 62
</pre>
 
=={{header|ERRE}}==
Taken from ERRE distribution disk. Comments are in Italian.
<syntaxhighlight lang="erre">
! **********************************************************************
! * *
! * IL GIRO DEL CAVALLO - come collocare un cavallo su di una *
! * scacchiera n*n passando una sola volta *
! * per ogni casella. *
! * *
! **********************************************************************
! ----------------------------------------------------------------------
! Inizializzazione dei parametri
! ----------------------------------------------------------------------
 
PROGRAM KNIGHT
 
!$INTEGER
!$KEY
 
DIM H[25,25],A[8],B[8],P0[8],P1[8]
 
!$INCLUDE="PC.LIB"
 
PROCEDURE INIT_SCACCHIERA
! **********************************************************************
! * Routine di inizializzazione scacchiera *
! **********************************************************************
FOR I1=1 TO 8 DO
U=X+A[I1] V=Y+B[I1]
IF (U>0 AND U<=N) AND (V>0 AND V<=N) THEN
H[U,V]=H[U,V]-1
END IF
END FOR
END PROCEDURE
 
PROCEDURE MOSTRA_SCACCHIERA
! *********************************************************************
! * Routine di visualizzazione della scacchiera *
! *********************************************************************
LOCATE(5,1) COLOR(0,7) PRINT(" Mossa num.";NMOS) COLOR(7,0)
L2=N
FOR I2=1 TO N DO
PRINT
FOR L1=1 TO N DO
IF H[L1,L2]>0 THEN COLOR(15,0) END IF
WRITE("####";H[L1,L2];)
COLOR(7,0)
END FOR
L2=L2-1
END FOR
END PROCEDURE
 
PROCEDURE AGGIORNA_SCACCHIERA
! *********************************************************************
! * Routine di Aggiornamento Scacchiera *
! *********************************************************************
B=1
FOR I1=1 TO 8 DO
U=X+A[I1] V=Y+B[I1]
IF (U>0 AND U<=N) AND (V>0 AND V<=N) THEN
IF H[U,V]<=0 THEN
H[U,V]=H[U,V]+1 B=0
END IF
END IF
END FOR
IF B=1 THEN Q1=0 END IF
END PROCEDURE
 
PROCEDURE MOSSA_MAX_PESO
! *********************************************************************
! * Cerca la prossima mossa con il massimo peso *
! *********************************************************************
M1=0 RO=1
FOR W=1 TO 8 DO
U=Z1+A[W] V=Z2+B[W]
IF (U>0 AND U<=N) AND (V>0 AND V<=N) THEN
IF H[U,V]<=0 AND H[U,V]<=M1 THEN
IF H[U,V]=M1 THEN
RO=RO+1 P0[RO]=W
ELSE
M1=H[U,V] Q1=1 T1=U T2=V RO=1 P0[1]=W
END IF
END IF
END IF
END FOR
END PROCEDURE
 
PROCEDURE MOSSA_MIN_PESO
! *********************************************************************
! * Cerca la prossima mossa con il minimo peso *
! *********************************************************************
M1=-9 RO=1
FOR W=1 TO 8 DO
U=Z1+A[W] V=Z2+B[W]
IF (U>0 AND U<=N) AND (V>0 AND V<=N) THEN
IF H[U,V]<=0 AND H[U,V]>=M1 THEN
IF H[U,V]=M1 THEN
RO=RO+1 P0[RO]=W
ELSE
M1=H[U,V] Q1=1 T1=U T2=V RO=1 P0[1]=W
END IF
END IF
END IF
END FOR
END PROCEDURE
 
BEGIN
A[1]=1 A[2]=2 A[3]=2 A[4]=1
A[5]=-1 A[6]=-2 A[7]=-2 A[8]=-1
B[1]=2 B[2]=1 B[3]=-1 B[4]=-2
B[5]=-2 B[6]=-1 B[7]=1 B[8]=2
 
CLS
PRINT(" *** LA GALOPPATA DEL CAVALIERE ***")
PRINT
PRINT("Inserire la dimensione della scacchiera (max. 25)";)
INPUT(N)
PRINT("Inserire la caselle di partenza (x,y) ";)
INPUT(X1,Y1)
NMOS=1 A1=1 N1=N*N ESCAPE=FALSE
! ----------------------------------------------------------------------
! Set della scacchiera
! ----------------------------------------------------------------------
WHILE NOT ESCAPE DO
FOR I=1 TO N DO
FOR J=1 TO N DO
H[I,J]=0
END FOR
END FOR
FOR I=1 TO N DO
FOR J=1 TO N DO
X=I Y=J
INIT_SCACCHIERA
END FOR
END FOR
 
! ----------------------------------------------------------------------
! Effettua la prima mossa
! ----------------------------------------------------------------------
X=X1 Y=Y1 H[X,Y]=1 L=2
AGGIORNA_SCACCHIERA
Q1=1 Q2=1
! -----------------------------------------------------------------------
! Trova la prossima mossa
! -----------------------------------------------------------------------
WHILE Q1<>0 AND Q2<>0 DO
Q1=0 Z1=X Z2=Y
MOSSA_MIN_PESO
IF RO<=1 THEN
C1=T1 C2=T2
ELSE
! ------------------------------------------------------------------------
! Esamina tutti i vincoli
! ------------------------------------------------------------------------
FOR K=1 TO RO DO
P1[K]=P0[K]
END FOR
R1=RO
IF A1=1 THEN M2=-9 ELSE M2=0 END IF
FOR K=1 TO R1 DO
F1=P1[K] Z1=X+A[F1] Z2=Y+B[F1]
IF A1=1 THEN
MOSSA_MAX_PESO
IF M1<=M2 THEN
!$NULL
ELSE
M2=M1 C1=Z1 C2=Z2
END IF
ELSE
MOSSA_MIN_PESO
IF M1>=M2 THEN
!$NULL
ELSE
M2=M1 C1=Z1 C2=Z2
END IF
END IF
END FOR
! ------------------------------------------------------------------------
! Prossima mossa trovata:aggiorna la scacchiera
! ------------------------------------------------------------------------
END IF
IF Q1<>0 THEN
X=C1 Y=C2 H[X,Y]=L
AGGIORNA_SCACCHIERA
IF L=N1 THEN Q2=0 END IF
END IF
L=L+1
MOSTRA_SCACCHIERA
NMOS=NMOS+1
END WHILE
! ------------------------------------------------------------------------
! La ricerca è terminata: visualizza i risultati
! ------------------------------------------------------------------------
PRINT PRINT
IF Q2<>1 THEN
PRINT("*** Trovata la soluzione! ***")
MOSTRA_SCACCHIERA
ESCAPE=TRUE
ELSE
IF A1=0 THEN
PRINT("Nessuna soluzione.")
ESCAPE=TRUE
ELSE
BEEP
A1=0
END IF
END IF
END WHILE
REPEAT
GET(A$)
UNTIL A$<>""
END PROGRAM
</syntaxhighlight>
{{out}}
<pre> *** LA GALOPPATA DEL CAVALIERE ***
 
Inserire la dimensione della scacchiera (max. 25)? 8
Inserire la caselle di partenza (x,y) ? 1,1
Mossa num. 64
 
64 7 54 41 60 9 48 39
53 42 61 8 55 40 35 10
6 63 44 59 34 49 38 47
43 52 21 62 45 56 11 36
20 5 58 33 50 37 46 25
31 2 51 22 57 26 15 12
4 19 32 29 14 17 24 27
1 30 3 18 23 28 13 16
 
*** Trovata la soluzione! ***
</pre>
 
=={{header|FreeBASIC}}==
<syntaxhighlight lang="freebasic">
Dim Shared As Integer tamano, xc, yc, nm
Dim As Integer f, qm, nmov, n = 0
Dim As String posini
 
Cls : Color 11
Input "Tamaño tablero: ", tamano
Input "Posicion inicial: ", posini
 
Dim As Integer x = Asc(Mid(posini,1,1))-96
Dim As Integer y = Val(Mid(posini,2,1))
Dim Shared As Integer tablero(tamano,tamano), dx(8), dy(8)
For f = 1 To 8 : Read dx(f), dy(f) : Next f
Data 2,1,1,2,-1,2,-2,1,-2,-1,-1,-2,1,-2,2,-1
 
Sub FindMoves()
Dim As Integer i, xt, yt
If xc < 1 Or yc < 1 Or xc > tamano Or yc > tamano Then nm = 1000: Return
If tablero(xc,yc) Then nm = 2000: Return
nm = 0
For i = 1 To 8
xt = xc+dx(i)
yt = yc+dy(i)
If xt < 1 Or yt < 1 Or xt > tamano Or yt > tamano Then 'Salta este movimiento
Elseif tablero(xt,yt) Then 'Salta este movimiento
Else
nm += 1
End If
Next i
End Sub
 
Color 4, 7 'Pinta tablero
For f = 1 To tamano
Locate 15-tamano, 3*f: Print " "; Chr(96+f); " ";
Locate 17-f, 3*(tamano+1)+1: Print Using "##"; f;
Next f
 
Color 15, 0
Do
n += 1
tablero(x,y) = n
Locate 17-y, 3*x: Print Using "###"; n;
If n = tamano*tamano Then Exit Do
nmov = 100
For f = 1 To 8
xc = x+dx(f)
yc = y+dy(f)
FindMoves()
If nm < nmov Then nmov = nm: qm = f
Next f
x = x+dx(qm)
y = y+dy(qm)
Sleep 1
Loop
Color 14 : Locate Csrlin+tamano, 1
Print " Pulsa cualquier tecla para finalizar..."
Sleep
End
</syntaxhighlight>
{{out}}
[https://www.dropbox.com/s/s3bpwechpoueum4/Knights%20Tour%20FreeBasic.png?dl=0 Knights Tour FreeBasic image]
<pre>
Tamaño tablero: 8
Posicion inicial: c3
 
 
a b c d e f g h
24 11 22 19 26 9 38 47 8
21 18 25 10 39 48 27 8 7
12 23 20 53 28 37 46 49 6
17 52 29 40 59 50 7 36 5
30 13 58 51 54 41 62 45 4
57 16 1 42 63 60 35 6 3
2 31 14 55 4 33 44 61 2
15 56 3 32 43 64 5 34 1
 
 
Pulsa cualquier tecla para finalizar...
</pre>
 
=={{header|Fōrmulæ}}==
 
{{FormulaeEntry|page=https://formulae.org/?script=examples/Knight%27s_tour}}
 
=={{header|Fortran}}==
===FORTRAN 77===
{{trans|ATS}}
{{works with|gfortran|11.2.1}}
{{works with|f2c}}
<syntaxhighlight lang="fortran">C-----------------------------------------------------------------------
C
C Find Knight’s Tours.
C
C Using Warnsdorff’s heuristic, find multiple solutions.
C Optionally accept only closed tours.
C
C This program is migrated from my implementation for ATS/Postiats.
C Arrays with dimension 1:64 take the place of stack frames.
C
C Compile with, for instance:
C
C gfortran -O2 -g -std=legacy -o knights_tour knights_tour.f
C
C or
C
C f2c knights_tour.f
C cc -O -o knights_tour knights_tour.c -lf2c
C
C Usage examples:
C
C One tour starting at a1, either open or closed:
C
C echo "a1 1 F" | ./knights_tour
C
C No more than 2000 closed tours starting at c5:
C
C echo "c5 2000 T" | ./knights_tour
C
C-----------------------------------------------------------------------
 
program ktour
implicit none
 
character*2 alg
integer i, j
integer mxtour
logical closed
 
read (*,*) alg, mxtour, closed
call alg2ij (alg, i, j)
call explor (i, j, mxtour, closed)
 
end
 
C-----------------------------------------------------------------------
 
subroutine explor (istart, jstart, mxtour, closed)
implicit none
 
C Explore the space of 'Warnsdorffian' knight’s paths, looking for
C and printing complete tours.
 
integer istart, jstart ! The starting position.
integer mxtour ! The maximum number of tours to print.
logical closed ! Closed tours only?
 
integer board(1:8,1:8)
integer imove(1:8,1:64)
integer jmove(1:8,1:64)
integer nmove(1:64)
integer n
integer itours
logical goodmv
logical isclos
 
itours = 0
call initbd (board)
n = 1
nmove(1) = 8
imove(8, 1) = istart
jmove(8, 1) = jstart
 
1000 if (itours .lt. mxtour .and. n .ne. 0) then
 
if (nmove(n) .eq. 9) then
n = n - 1
if (n .ne. 0) then
call unmove (board, imove, jmove, nmove, n)
nmove(n) = nmove(n) + 1
end if
else if (goodmv (imove, nmove, n)) then
call mkmove (board, imove, jmove, nmove, n)
if (n .eq. 64) then
if (.not. closed) then
itours = itours + 1
call prnt (board, itours)
else if (isclos (board)) then
itours = itours + 1
call prnt (board, itours)
end if
call unmove (board, imove, jmove, nmove, n)
nmove(n) = 9
else if (n .eq. 63) then
call possib (board, n, imove, jmove, nmove)
n = n + 1
nmove(n) = 1
else
call nxtmov (board, n, imove, jmove, nmove)
n = n + 1
nmove(n) = 1
end if
else
nmove(n) = nmove(n) + 1
end if
 
goto 1000
end if
 
end
 
C-----------------------------------------------------------------------
 
subroutine initbd (board)
implicit none
 
C Initialize a chessboard with empty squares.
 
integer board(1:8,1:8)
 
integer i, j
 
do 1010 j = 1, 8
do 1000 i = 1, 8
board(i, j) = -1
1000 continue
1010 continue
 
end
 
C-----------------------------------------------------------------------
 
subroutine mkmove (board, imove, jmove, nmove, n)
implicit none
 
C Fill a square with a move number.
 
integer board(1:8, 1:8)
integer imove(1:8, 1:64)
integer jmove(1:8, 1:64)
integer nmove(1:64)
integer n
 
board(imove(nmove(n), n), jmove(nmove(n), n)) = n
 
end
 
C-----------------------------------------------------------------------
 
subroutine unmove (board, imove, jmove, nmove, n)
implicit none
 
C Unmake a mkmove.
 
integer board(1:8, 1:8)
integer imove(1:8, 1:64)
integer jmove(1:8, 1:64)
integer nmove(1:64)
integer n
 
board(imove(nmove(n), n), jmove(nmove(n), n)) = -1
 
end
 
C-----------------------------------------------------------------------
 
function goodmv (imove, nmove, n)
implicit none
 
logical goodmv
integer imove(1:8, 1:64)
integer nmove(1:64)
integer n
goodmv = (imove(nmove(n), n) .ne. -1)
 
end
 
C-----------------------------------------------------------------------
 
subroutine prnt (board, itours)
implicit none
 
C Print a knight's tour.
 
integer board(1:8,1:8)
integer itours
 
10000 format (1X)
 
C The following plethora of format statements seemed a simple way to
C get this working with f2c. (For gfortran, the 'I0' format
C sufficed.)
10010 format (1X, "Tour number ", I1)
10020 format (1X, "Tour number ", I2)
10030 format (1X, "Tour number ", I3)
10040 format (1X, "Tour number ", I4)
10050 format (1X, "Tour number ", I5)
10060 format (1X, "Tour number ", I6)
10070 format (1X, "Tour number ", I20)
 
if (itours .lt. 10) then
write (*, 10010) itours
else if (itours .lt. 100) then
write (*, 10020) itours
else if (itours .lt. 1000) then
write (*, 10030) itours
else if (itours .lt. 10000) then
write (*, 10040) itours
else if (itours .lt. 100000) then
write (*, 10050) itours
else if (itours .lt. 1000000) then
write (*, 10060) itours
else
write (*, 10070) itours
end if
call prntmv (board)
call prntbd (board)
write (*, 10000)
 
end
 
C-----------------------------------------------------------------------
 
subroutine prntbd (board)
implicit none
 
C Print a chessboard with the move number in each square.
 
integer board(1:8,1:8)
 
integer i, j
 
10000 format (1X, " ", 8("+----"), "+")
10010 format (1X, I2, " ", 8(" | ", I2), " | ")
10020 format (1X, " ", 8(" ", A1))
 
do 1000 i = 8, 1, -1
write (*, 10000)
write (*, 10010) i, (board(i, j), j = 1, 8)
1000 continue
write (*, 10000)
write (*, 10020) 'a', 'b', 'c', 'd', 'e', 'f', 'g', 'h'
 
end
 
C-----------------------------------------------------------------------
 
subroutine prntmv (board)
implicit none
 
C Print the moves of a knight's path, in algebraic notation.
 
integer board(1:8,1:8)
 
integer ipos(1:64)
integer jpos(1:64)
integer numpos
character*2 alg(1:64)
integer columns(1:8)
integer k
integer m
 
character*72 lines(1:8)
 
10000 format (1X, A)
 
call bd2pos (board, ipos, jpos, numpos)
 
C Convert the positions to algebraic notation.
do 1000 k = 1, numpos
call ij2alg (ipos(k), jpos(k), alg(k))
1000 continue
 
C Fill lines with algebraic notations.
do 1020 m = 1, 8
columns(m) = 1
1020 continue
m = 1
do 1100 k = 1, numpos
lines(m)(columns(m) : columns(m) + 1) = alg(k)(1:2)
columns(m) = columns(m) + 2
if (k .ne. numpos) then
lines(m)(columns(m) : columns(m) + 3) = " -> "
columns(m) = columns(m) + 4
else if (numpos .eq. 64 .and.
$ ((abs (ipos(numpos) - ipos(1)) .eq. 2
$ .and. abs (jpos(numpos) - jpos(1)) .eq. 1) .or.
$ ((abs (ipos(numpos) - ipos(1)) .eq. 1
$ .and. abs (jpos(numpos) - jpos(1)) .eq. 2)))) then
lines(m)(columns(m) : columns(m) + 8) = " -> cycle"
columns(m) = columns(m) + 9
endif
if (mod (k, 8) .eq. 0) m = m + 1
1100 continue
 
C Print the lines that have stuff in them.
do 1200 m = 1, 8
if (columns(m) .ne. 1) then
write (*, 10000) lines(m)(1 : columns(m) - 1)
end if
1200 continue
 
end
 
C-----------------------------------------------------------------------
 
function isclos (board)
implicit none
 
C Is a board a closed tour?
 
logical isclos
integer board(1:8,1:8)
integer ipos(1:64) ! The i-positions in order.
integer jpos(1:64) ! The j-positions in order.
integer numpos ! The number of positions so far.
 
call bd2pos (board, ipos, jpos, numpos)
 
isclos = (numpos .eq. 64 .and.
$ ((abs (ipos(numpos) - ipos(1)) .eq. 2
$ .and. abs (jpos(numpos) - jpos(1)) .eq. 1) .or.
$ ((abs (ipos(numpos) - ipos(1)) .eq. 1
$ .and. abs (jpos(numpos) - jpos(1)) .eq. 2))))
 
end
 
C-----------------------------------------------------------------------
 
subroutine bd2pos (board, ipos, jpos, numpos)
implicit none
 
C Convert from a board to a list of board positions.
 
integer board(1:8,1:8)
integer ipos(1:64) ! The i-positions in order.
integer jpos(1:64) ! The j-positions in order.
integer numpos ! The number of positions so far.
 
integer i, j
 
numpos = 0
do 1010 i = 1, 8
do 1000 j = 1, 8
if (board(i, j) .ne. -1) then
numpos = max (board(i, j), numpos)
ipos(board(i, j)) = i
jpos(board(i, j)) = j
end if
1000 continue
1010 continue
 
end
 
C-----------------------------------------------------------------------
 
subroutine nxtmov (board, n, imove, jmove, nmove)
implicit none
 
C Find possible next moves. Prune and sort the moves according to
C Warnsdorff's heuristic, keeping only those that have the minimum
C number of legal following moves.
 
integer board(1:8,1:8)
integer n
integer imove(1:8,1:64)
integer jmove(1:8,1:64)
integer nmove(1:64)
 
integer w1, w2, w3, w4, w5, w6, w7, w8
integer w
integer n1
integer pickw
 
call possib (board, n, imove, jmove, nmove)
 
n1 = n + 1
nmove(n1) = 1
call countf (board, n1, imove, jmove, nmove, w1)
nmove(n1) = 2
call countf (board, n1, imove, jmove, nmove, w2)
nmove(n1) = 3
call countf (board, n1, imove, jmove, nmove, w3)
nmove(n1) = 4
call countf (board, n1, imove, jmove, nmove, w4)
nmove(n1) = 5
call countf (board, n1, imove, jmove, nmove, w5)
nmove(n1) = 6
call countf (board, n1, imove, jmove, nmove, w6)
nmove(n1) = 7
call countf (board, n1, imove, jmove, nmove, w7)
nmove(n1) = 8
call countf (board, n1, imove, jmove, nmove, w8)
 
w = pickw (w1, w2, w3, w4, w5, w6, w7, w8)
 
if (w .eq. 0) then
call disabl (imove(1, n1), jmove(1, n1))
call disabl (imove(2, n1), jmove(2, n1))
call disabl (imove(3, n1), jmove(3, n1))
call disabl (imove(4, n1), jmove(4, n1))
call disabl (imove(5, n1), jmove(5, n1))
call disabl (imove(6, n1), jmove(6, n1))
call disabl (imove(7, n1), jmove(7, n1))
call disabl (imove(8, n1), jmove(8, n1))
else
if (w .ne. w1) call disabl (imove(1, n1), jmove(1, n1))
if (w .ne. w2) call disabl (imove(2, n1), jmove(2, n1))
if (w .ne. w3) call disabl (imove(3, n1), jmove(3, n1))
if (w .ne. w4) call disabl (imove(4, n1), jmove(4, n1))
if (w .ne. w5) call disabl (imove(5, n1), jmove(5, n1))
if (w .ne. w6) call disabl (imove(6, n1), jmove(6, n1))
if (w .ne. w7) call disabl (imove(7, n1), jmove(7, n1))
if (w .ne. w8) call disabl (imove(8, n1), jmove(8, n1))
end if
 
end
 
C-----------------------------------------------------------------------
 
subroutine countf (board, n, imove, jmove, nmove, w)
implicit none
 
C Count the number of moves possible after an nth move.
 
integer board(1:8,1:8)
integer n
integer imove(1:8,1:64)
integer jmove(1:8,1:64)
integer nmove(1:64)
integer w
 
logical goodmv
integer n1
 
if (goodmv (imove, nmove, n)) then
call mkmove (board, imove, jmove, nmove, n)
call possib (board, n, imove, jmove, nmove)
n1 = n + 1
w = 0
if (imove(1, n1) .ne. -1) w = w + 1
if (imove(2, n1) .ne. -1) w = w + 1
if (imove(3, n1) .ne. -1) w = w + 1
if (imove(4, n1) .ne. -1) w = w + 1
if (imove(5, n1) .ne. -1) w = w + 1
if (imove(6, n1) .ne. -1) w = w + 1
if (imove(7, n1) .ne. -1) w = w + 1
if (imove(8, n1) .ne. -1) w = w + 1
call unmove (board, imove, jmove, nmove, n)
else
C The nth move itself is impossible.
w = 0
end if
 
end
 
C-----------------------------------------------------------------------
 
function pickw (w1, w2, w3, w4, w5, w6, w7, w8)
implicit none
 
C From w1..w8, pick out the least nonzero value (or zero if they all
C equal zero).
 
integer pickw
integer w1, w2, w3, w4, w5, w6, w7, w8
 
integer w
integer pickw1
 
w = 0
w = pickw1 (w, w1)
w = pickw1 (w, w2)
w = pickw1 (w, w3)
w = pickw1 (w, w4)
w = pickw1 (w, w5)
w = pickw1 (w, w6)
w = pickw1 (w, w7)
w = pickw1 (w, w8)
 
pickw = w
 
end
 
C-----------------------------------------------------------------------
 
function pickw1 (u, v)
implicit none
 
C A small function used by pickw.
 
integer pickw1
integer u, v
 
if (v .eq. 0) then
pickw1 = u
else if (u .eq. 0) then
pickw1 = v
else
pickw1 = min (u, v)
end if
 
end
 
C-----------------------------------------------------------------------
 
subroutine possib (board, n, imove, jmove, nmove)
implicit none
 
C Find moves that are possible from an nth-move position.
 
integer board(1:8,1:8)
integer n
integer imove(1:8,1:64)
integer jmove(1:8,1:64)
integer nmove(1:64)
 
integer i, j
integer n1
 
i = imove(nmove(n), n)
j = jmove(nmove(n), n)
n1 = n + 1
call trymov (board, i + 1, j + 2, imove(1, n1), jmove(1, n1))
call trymov (board, i + 2, j + 1, imove(2, n1), jmove(2, n1))
call trymov (board, i + 1, j - 2, imove(3, n1), jmove(3, n1))
call trymov (board, i + 2, j - 1, imove(4, n1), jmove(4, n1))
call trymov (board, i - 1, j + 2, imove(5, n1), jmove(5, n1))
call trymov (board, i - 2, j + 1, imove(6, n1), jmove(6, n1))
call trymov (board, i - 1, j - 2, imove(7, n1), jmove(7, n1))
call trymov (board, i - 2, j - 1, imove(8, n1), jmove(8, n1))
 
end
 
C-----------------------------------------------------------------------
 
subroutine trymov (board, i, j, imove, jmove)
implicit none
 
C Try a move to square (i, j).
 
integer board(1:8,1:8)
integer i, j
integer imove, jmove
 
call disabl (imove, jmove)
if (1 .le. i .and. i .le. 8 .and. 1 .le. j .and. j .le. 8) then
if (board(i,j) .eq. -1) then
call enable (i, j, imove, jmove)
end if
end if
 
end
 
C-----------------------------------------------------------------------
 
subroutine enable (i, j, imove, jmove)
implicit none
 
C Enable a potential move.
 
integer i, j
integer imove, jmove
 
imove = i
jmove = j
 
end
 
C-----------------------------------------------------------------------
 
subroutine disabl (imove, jmove)
implicit none
 
C Disable a potential move.
 
integer imove, jmove
 
imove = -1
jmove = -1
 
end
 
C-----------------------------------------------------------------------
 
subroutine alg2ij (alg, i, j)
implicit none
 
C Convert, for instance, 'c5' to i=3,j=5.
 
character*2 alg
integer i, j
 
if (alg(1:1) .eq. 'a') j = 1
if (alg(1:1) .eq. 'b') j = 2
if (alg(1:1) .eq. 'c') j = 3
if (alg(1:1) .eq. 'd') j = 4
if (alg(1:1) .eq. 'e') j = 5
if (alg(1:1) .eq. 'f') j = 6
if (alg(1:1) .eq. 'g') j = 7
if (alg(1:1) .eq. 'h') j = 8
 
if (alg(2:2) .eq. '1') i = 1
if (alg(2:2) .eq. '2') i = 2
if (alg(2:2) .eq. '3') i = 3
if (alg(2:2) .eq. '4') i = 4
if (alg(2:2) .eq. '5') i = 5
if (alg(2:2) .eq. '6') i = 6
if (alg(2:2) .eq. '7') i = 7
if (alg(2:2) .eq. '8') i = 8
 
end
 
C-----------------------------------------------------------------------
 
subroutine ij2alg (i, j, alg)
implicit none
 
C Convert, for instance, i=3,j=5 to 'c5'.
 
integer i, j
character*2 alg
 
character alg1
character alg2
 
if (j .eq. 1) alg1 = 'a'
if (j .eq. 2) alg1 = 'b'
if (j .eq. 3) alg1 = 'c'
if (j .eq. 4) alg1 = 'd'
if (j .eq. 5) alg1 = 'e'
if (j .eq. 6) alg1 = 'f'
if (j .eq. 7) alg1 = 'g'
if (j .eq. 8) alg1 = 'h'
 
if (i .eq. 1) alg2 = '1'
if (i .eq. 2) alg2 = '2'
if (i .eq. 3) alg2 = '3'
if (i .eq. 4) alg2 = '4'
if (i .eq. 5) alg2 = '5'
if (i .eq. 6) alg2 = '6'
if (i .eq. 7) alg2 = '7'
if (i .eq. 8) alg2 = '8'
 
alg(1:1) = alg1
alg(2:2) = alg2
 
end
 
C-----------------------------------------------------------------------</syntaxhighlight>
{{out}}
$ echo "c5 2 T" | ./knights_tour
<pre> Tour number 1
c5 -> a6 -> b8 -> d7 -> f8 -> h7 -> g5 -> h3 ->
g1 -> e2 -> c1 -> a2 -> b4 -> d3 -> e1 -> g2 ->
h4 -> g6 -> h8 -> f7 -> d8 -> b7 -> a5 -> b3 ->
a1 -> c2 -> a3 -> b1 -> d2 -> f3 -> h2 -> f1 ->
g3 -> h1 -> f2 -> e4 -> c3 -> a4 -> b2 -> d1 ->
e3 -> g4 -> h6 -> g8 -> f6 -> h5 -> f4 -> d5 ->
e7 -> c8 -> a7 -> c6 -> e5 -> c4 -> b6 -> a8 ->
c7 -> e8 -> d6 -> b5 -> d4 -> f5 -> g7 -> e6 -> cycle
+----+----+----+----+----+----+----+----+
8 | 56 | 3 | 50 | 21 | 58 | 5 | 44 | 19 |
+----+----+----+----+----+----+----+----+
7 | 51 | 22 | 57 | 4 | 49 | 20 | 63 | 6 |
+----+----+----+----+----+----+----+----+
6 | 2 | 55 | 52 | 59 | 64 | 45 | 18 | 43 |
+----+----+----+----+----+----+----+----+
5 | 23 | 60 | 1 | 48 | 53 | 62 | 7 | 46 |
+----+----+----+----+----+----+----+----+
4 | 38 | 13 | 54 | 61 | 36 | 47 | 42 | 17 |
+----+----+----+----+----+----+----+----+
3 | 27 | 24 | 37 | 14 | 41 | 30 | 33 | 8 |
+----+----+----+----+----+----+----+----+
2 | 12 | 39 | 26 | 29 | 10 | 35 | 16 | 31 |
+----+----+----+----+----+----+----+----+
1 | 25 | 28 | 11 | 40 | 15 | 32 | 9 | 34 |
+----+----+----+----+----+----+----+----+
a b c d e f g h
 
Tour number 2
c5 -> a6 -> b8 -> d7 -> f8 -> h7 -> g5 -> h3 ->
g1 -> e2 -> c1 -> a2 -> b4 -> d3 -> e1 -> g2 ->
h4 -> g6 -> h8 -> f7 -> d8 -> b7 -> a5 -> b3 ->
a1 -> c2 -> a3 -> b1 -> d2 -> f3 -> h2 -> f1 ->
g3 -> h1 -> f2 -> e4 -> c3 -> a4 -> b2 -> d1 ->
e3 -> g4 -> h6 -> g8 -> f6 -> h5 -> f4 -> d5 ->
e7 -> c8 -> a7 -> c6 -> e5 -> c4 -> b6 -> a8 ->
c7 -> b5 -> d6 -> e8 -> g7 -> f5 -> d4 -> e6 -> cycle
+----+----+----+----+----+----+----+----+
8 | 56 | 3 | 50 | 21 | 60 | 5 | 44 | 19 |
+----+----+----+----+----+----+----+----+
7 | 51 | 22 | 57 | 4 | 49 | 20 | 61 | 6 |
+----+----+----+----+----+----+----+----+
6 | 2 | 55 | 52 | 59 | 64 | 45 | 18 | 43 |
+----+----+----+----+----+----+----+----+
5 | 23 | 58 | 1 | 48 | 53 | 62 | 7 | 46 |
+----+----+----+----+----+----+----+----+
4 | 38 | 13 | 54 | 63 | 36 | 47 | 42 | 17 |
+----+----+----+----+----+----+----+----+
3 | 27 | 24 | 37 | 14 | 41 | 30 | 33 | 8 |
+----+----+----+----+----+----+----+----+
2 | 12 | 39 | 26 | 29 | 10 | 35 | 16 | 31 |
+----+----+----+----+----+----+----+----+
1 | 25 | 28 | 11 | 40 | 15 | 32 | 9 | 34 |
+----+----+----+----+----+----+----+----+
a b c d e f g h
</pre>
 
===Fortran 95===
{{works with|gfortran|11.2.1}}
{{trans|ATS}}
<syntaxhighlight lang="fortran">!-----------------------------------------------------------------------
!
! Find Knight’s Tours.
!
! Using Warnsdorff’s heuristic, find multiple solutions.
! Optionally accept only closed tours.
!
! This program is migrated from my implementation for
! ATS/Postiats. Unlike my FORTRAN 77 implementation (which simply
! cannot do so), it uses a recursive call.
!
! Compile with, for instance:
!
! gfortran -O2 -g -std=f95 -o knights_tour knights_tour.f90
!
! Usage examples:
!
! One tour starting at a1, either open or closed:
!
! echo "a1 1 F" | ./knights_tour
!
! No more than 2000 closed tours starting at c5:
!
! echo "c5 2000 T" | ./knights_tour
!
!-----------------------------------------------------------------------
 
program knights_tour
implicit none
 
character(len = 2) inp__alg
integer inp__istart
integer inp__jstart
integer inp__max_tours
logical inp__closed
 
read (*,*) inp__alg, inp__max_tours, inp__closed
call alg2ij (inp__alg, inp__istart, inp__jstart)
call main (inp__istart, inp__jstart, inp__max_tours, inp__closed)
 
contains
 
subroutine main (istart, jstart, max_tours, closed)
integer, intent(in) :: istart, jstart ! The starting position.
integer, intent(in) :: max_tours ! The max. no. of tours to print.
logical, intent(in) :: closed ! Closed tours only?
 
integer board(1:8,1:8)
integer num_tours_printed
 
num_tours_printed = 0
call init_board (board)
call explore (board, 1, istart, jstart, max_tours, &
& num_tours_printed, closed)
end subroutine main
 
recursive subroutine explore (board, n, i, j, max_tours, &
& num_tours_printed, closed)
 
! Recursively the space of 'Warnsdorffian' knight’s paths, looking
! for and printing complete tours.
 
integer, intent(inout) :: board(1:8,1:8)
integer, intent(in) :: n
integer, intent(in) :: i, j
integer, intent(in) :: max_tours
integer, intent(inout) :: num_tours_printed
logical, intent(in) :: closed
 
integer imove(1:8)
integer jmove(1:8)
integer k
 
if (num_tours_printed < max_tours .and. n /= 0) then
if (is_good_move (i, j)) then
call mkmove (board, i, j, n)
if (n == 63) then
call find_possible_moves (board, i, j, imove, jmove)
call try_last_move (board, n + 1, imove(1), jmove(1), &
& num_tours_printed, closed)
call try_last_move (board, n + 1, imove(2), jmove(2), &
& num_tours_printed, closed)
call try_last_move (board, n + 1, imove(3), jmove(3), &
& num_tours_printed, closed)
call try_last_move (board, n + 1, imove(4), jmove(4), &
& num_tours_printed, closed)
call try_last_move (board, n + 1, imove(5), jmove(5), &
& num_tours_printed, closed)
call try_last_move (board, n + 1, imove(6), jmove(6), &
& num_tours_printed, closed)
call try_last_move (board, n + 1, imove(7), jmove(7), &
& num_tours_printed, closed)
call try_last_move (board, n + 1, imove(8), jmove(8), &
& num_tours_printed, closed)
else
call find_next_moves (board, n, i, j, imove, jmove)
do k = 1, 8
if (is_good_move (imove(k), jmove(k))) then
!
! Here is the recursive call.
!
call explore (board, n + 1, imove(k), jmove(k), &
& max_tours, num_tours_printed, closed)
end if
end do
end if
call unmove (board, i, j)
end if
end if
end subroutine explore
 
subroutine try_last_move (board, n, i, j, num_tours_printed, closed)
integer, intent(inout) :: board(1:8,1:8)
integer, intent(in) :: n
integer, intent(in) :: i, j
integer, intent(inout) :: num_tours_printed
logical, intent(in) :: closed
 
integer ipos(1:64)
integer jpos(1:64)
integer numpos
integer idiff
integer jdiff
 
if (is_good_move (i, j)) then
call mkmove (board, i, j, n)
if (.not. closed) then
num_tours_printed = num_tours_printed + 1
call print_tour (board, num_tours_printed)
else
call board2positions (board, ipos, jpos, numpos)
idiff = abs (i - ipos(1))
jdiff = abs (j - jpos(1))
if ((idiff == 1 .and. jdiff == 2) .or. &
(idiff == 2 .and. jdiff == 1)) then
num_tours_printed = num_tours_printed + 1
call print_tour (board, num_tours_printed)
end if
end if
call unmove (board, i, j)
end if
end subroutine try_last_move
 
subroutine init_board (board)
 
! Initialize a chessboard with empty squares.
 
integer, intent(out) :: board(1:8,1:8)
 
integer i, j
 
do j = 1, 8
do i = 1, 8
board(i, j) = -1
end do
end do
end subroutine init_board
 
subroutine mkmove (board, i, j, n)
 
! Fill a square with a move number.
 
integer, intent(inout) :: board(1:8, 1:8)
integer, intent(in) :: i, j
integer, intent(in) :: n
 
board(i, j) = n
end subroutine mkmove
 
subroutine unmove (board, i, j)
 
! Unmake a mkmove.
 
integer, intent(inout) :: board(1:8, 1:8)
integer, intent(in) :: i, j
 
board(i, j) = -1
end subroutine unmove
 
function is_good_move (i, j)
logical is_good_move
integer, intent(in) :: i, j
 
is_good_move = (i /= -1 .and. j /= -1)
end function is_good_move
 
subroutine print_tour (board, num_tours_printed)
 
! Print a knight's tour.
 
integer, intent(in) :: board(1:8,1:8)
integer, intent(in) :: num_tours_printed
 
write (*, '("Tour number ", I0)') num_tours_printed
call print_moves (board)
call print_board (board)
write (*, '()')
end subroutine print_tour
 
subroutine print_board (board)
 
! Print a chessboard with the move number in each square.
 
integer, intent(in) :: board(1:8,1:8)
 
integer i, j
 
do i = 8, 1, -1
write (*, '(" ", 8("+----"), "+")')
write (*, '(I2, " ", 8(" | ", I2), " | ")') &
i, (board(i, j), j = 1, 8)
end do
write (*, '(" ", 8("+----"), "+")')
write (*, '(" ", 8(" ", A1))') &
'a', 'b', 'c', 'd', 'e', 'f', 'g', 'h'
 
end subroutine print_board
 
subroutine print_moves (board)
 
! Print the moves of a knight's path, in algebraic notation.
 
integer, intent(in) :: board(1:8,1:8)
 
integer ipos(1:64)
integer jpos(1:64)
integer numpos
character(len = 2) alg(1:64)
integer columns(1:8)
integer k
integer m
 
character(len = 72) lines(1:8)
 
call board2positions (board, ipos, jpos, numpos)
 
! Convert the positions to algebraic notation.
do k = 1, numpos
call ij2alg (ipos(k), jpos(k), alg(k))
end do
 
! Fill lines with algebraic notations.
do m = 1, 8
columns(m) = 1
end do
m = 1
do k = 1, numpos
lines(m)(columns(m) : columns(m) + 1) = alg(k)(1:2)
columns(m) = columns(m) + 2
if (k /= numpos) then
lines(m)(columns(m) : columns(m) + 3) = " -> "
columns(m) = columns(m) + 4
else if (numpos == 64 .and. &
((abs (ipos(numpos) - ipos(1)) == 2 &
.and. abs (jpos(numpos) - jpos(1)) == 1) .or. &
((abs (ipos(numpos) - ipos(1)) == 1 &
.and. abs (jpos(numpos) - jpos(1)) == 2)))) then
lines(m)(columns(m) : columns(m) + 8) = " -> cycle"
columns(m) = columns(m) + 9
endif
if (mod (k, 8) == 0) m = m + 1
end do
 
! Print the lines that have stuff in them.
do m = 1, 8
if (columns(m) /= 1) then
write (*, '(A)') lines(m)(1 : columns(m) - 1)
end if
end do
 
end subroutine print_moves
 
function is_closed (board)
 
! Is a board a closed tour?
 
logical is_closed
 
integer board(1:8,1:8)
integer ipos(1:64) ! The i-positions in order.
integer jpos(1:64) ! The j-positions in order.
integer numpos ! The number of positions so far.
 
call board2positions (board, ipos, jpos, numpos)
 
is_closed = (numpos == 64 .and. &
((abs (ipos(numpos) - ipos(1)) == 2 &
.and. abs (jpos(numpos) - jpos(1)) == 1) .or. &
((abs (ipos(numpos) - ipos(1)) == 1 &
.and. abs (jpos(numpos) - jpos(1)) == 2))))
 
end function is_closed
 
subroutine board2positions (board, ipos, jpos, numpos)
 
! Convert from a board to a list of board positions.
 
integer, intent(in) :: board(1:8,1:8)
integer, intent(out) :: ipos(1:64) ! The i-positions in order.
integer, intent(out) :: jpos(1:64) ! The j-positions in order.
integer, intent(out) :: numpos ! The number of positions so far.
 
integer i, j
 
numpos = 0
do i = 1, 8
do j = 1, 8
if (board(i, j) /= -1) then
numpos = max (board(i, j), numpos)
ipos(board(i, j)) = i
jpos(board(i, j)) = j
end if
end do
end do
end subroutine board2positions
 
subroutine find_next_moves (board, n, i, j, imove, jmove)
 
! Find possible next moves. Prune and sort the moves according to
! Warnsdorff's heuristic, keeping only those that have the minimum
! number of legal following moves.
 
integer, intent(inout) :: board(1:8,1:8)
integer, intent(in) :: n
integer, intent(in) :: i, j
integer, intent(inout) :: imove(1:8)
integer, intent(inout) :: jmove(1:8)
 
integer w1, w2, w3, w4, w5, w6, w7, w8
integer w
 
call find_possible_moves (board, i, j, imove, jmove)
 
call count_following (board, n + 1, imove(1), jmove(1), w1)
call count_following (board, n + 1, imove(2), jmove(2), w2)
call count_following (board, n + 1, imove(3), jmove(3), w3)
call count_following (board, n + 1, imove(4), jmove(4), w4)
call count_following (board, n + 1, imove(5), jmove(5), w5)
call count_following (board, n + 1, imove(6), jmove(6), w6)
call count_following (board, n + 1, imove(7), jmove(7), w7)
call count_following (board, n + 1, imove(8), jmove(8), w8)
 
w = pick_w (w1, w2, w3, w4, w5, w6, w7, w8)
 
if (w == 0) then
call disable (imove(1), jmove(1))
call disable (imove(2), jmove(2))
call disable (imove(3), jmove(3))
call disable (imove(4), jmove(4))
call disable (imove(5), jmove(5))
call disable (imove(6), jmove(6))
call disable (imove(7), jmove(7))
call disable (imove(8), jmove(8))
else
if (w /= w1) call disable (imove(1), jmove(1))
if (w /= w2) call disable (imove(2), jmove(2))
if (w /= w3) call disable (imove(3), jmove(3))
if (w /= w4) call disable (imove(4), jmove(4))
if (w /= w5) call disable (imove(5), jmove(5))
if (w /= w6) call disable (imove(6), jmove(6))
if (w /= w7) call disable (imove(7), jmove(7))
if (w /= w8) call disable (imove(8), jmove(8))
end if
 
end subroutine find_next_moves
 
subroutine count_following (board, n, i, j, w)
 
! Count the number of moves possible after an nth move.
 
integer, intent(inout) :: board(1:8,1:8)
integer, intent(in) :: n
integer, intent(in) :: i, j
integer, intent(out) :: w
 
integer imove(1:8)
integer jmove(1:8)
 
if (is_good_move (i, j)) then
call mkmove (board, i, j, n)
call find_possible_moves (board, i, j, imove, jmove)
w = 0
if (is_good_move (imove(1), jmove(1))) w = w + 1
if (is_good_move (imove(2), jmove(2))) w = w + 1
if (is_good_move (imove(3), jmove(3))) w = w + 1
if (is_good_move (imove(4), jmove(4))) w = w + 1
if (is_good_move (imove(5), jmove(5))) w = w + 1
if (is_good_move (imove(6), jmove(6))) w = w + 1
if (is_good_move (imove(7), jmove(7))) w = w + 1
if (is_good_move (imove(8), jmove(8))) w = w + 1
call unmove (board, i, j)
else
! The nth move itself is impossible.
w = 0
end if
 
end subroutine count_following
 
function pick_w (w1, w2, w3, w4, w5, w6, w7, w8) result (w)
 
! From w1..w8, pick out the least nonzero value (or zero if they
! all equal zero).
 
integer, intent(in) :: w1, w2, w3, w4, w5, w6, w7, w8
integer w
 
w = 0
w = pick_w1 (w, w1)
w = pick_w1 (w, w2)
w = pick_w1 (w, w3)
w = pick_w1 (w, w4)
w = pick_w1 (w, w5)
w = pick_w1 (w, w6)
w = pick_w1 (w, w7)
w = pick_w1 (w, w8)
end function pick_w
 
function pick_w1 (u, v)
 
! A small function used by pick_w.
 
integer pick_w1
integer, intent(in) :: u, v
 
if (v == 0) then
pick_w1 = u
else if (u == 0) then
pick_w1 = v
else
pick_w1 = min (u, v)
end if
end function pick_w1
 
subroutine find_possible_moves (board, i, j, imove, jmove)
 
! Find moves that are possible from a position.
 
integer, intent(in) :: board(1:8,1:8)
integer, intent(in) :: i, j
integer, intent(out) :: imove(1:8)
integer, intent(out) :: jmove(1:8)
 
call trymov (board, i + 1, j + 2, imove(1), jmove(1))
call trymov (board, i + 2, j + 1, imove(2), jmove(2))
call trymov (board, i + 1, j - 2, imove(3), jmove(3))
call trymov (board, i + 2, j - 1, imove(4), jmove(4))
call trymov (board, i - 1, j + 2, imove(5), jmove(5))
call trymov (board, i - 2, j + 1, imove(6), jmove(6))
call trymov (board, i - 1, j - 2, imove(7), jmove(7))
call trymov (board, i - 2, j - 1, imove(8), jmove(8))
end subroutine find_possible_moves
 
subroutine trymov (board, i, j, imove, jmove)
 
! Try a move to square (i, j).
 
integer, intent(in) :: board(1:8,1:8)
integer, intent(in) :: i, j
integer, intent(inout) :: imove, jmove
 
call disable (imove, jmove)
if (1 <= i .and. i <= 8 .and. 1 <= j .and. j <= 8) then
if (square_is_empty (board, i, j)) then
call enable (i, j, imove, jmove)
end if
end if
 
end subroutine trymov
 
function square_is_empty (board, i, j)
logical square_is_empty
integer, intent(in) :: board(1:8,1:8)
integer, intent(in) :: i, j
 
square_is_empty = (board(i, j) == -1)
end function square_is_empty
 
subroutine enable (i, j, imove, jmove)
 
! Enable a potential move.
 
integer, intent(in) :: i, j
integer, intent(inout) :: imove, jmove
 
imove = i
jmove = j
end subroutine enable
 
subroutine disable (imove, jmove)
 
! Disable a potential move.
 
integer, intent(out) :: imove, jmove
 
imove = -1
jmove = -1
end subroutine disable
 
subroutine alg2ij (alg, i, j)
 
! Convert, for instance, 'c5' to i=3,j=5.
 
character(len = 2), intent(in) :: alg
integer, intent(out) :: i, j
 
if (alg(1:1) == 'a') j = 1
if (alg(1:1) == 'b') j = 2
if (alg(1:1) == 'c') j = 3
if (alg(1:1) == 'd') j = 4
if (alg(1:1) == 'e') j = 5
if (alg(1:1) == 'f') j = 6
if (alg(1:1) == 'g') j = 7
if (alg(1:1) == 'h') j = 8
 
if (alg(2:2) == '1') i = 1
if (alg(2:2) == '2') i = 2
if (alg(2:2) == '3') i = 3
if (alg(2:2) == '4') i = 4
if (alg(2:2) == '5') i = 5
if (alg(2:2) == '6') i = 6
if (alg(2:2) == '7') i = 7
if (alg(2:2) == '8') i = 8
 
end subroutine alg2ij
 
subroutine ij2alg (i, j, alg)
 
! Convert, for instance, i=3,j=5 to 'c5'.
 
integer, intent(in) :: i, j
character(len = 2), intent(out) :: alg
 
character alg1
character alg2
 
if (j == 1) alg1 = 'a'
if (j == 2) alg1 = 'b'
if (j == 3) alg1 = 'c'
if (j == 4) alg1 = 'd'
if (j == 5) alg1 = 'e'
if (j == 6) alg1 = 'f'
if (j == 7) alg1 = 'g'
if (j == 8) alg1 = 'h'
 
if (i == 1) alg2 = '1'
if (i == 2) alg2 = '2'
if (i == 3) alg2 = '3'
if (i == 4) alg2 = '4'
if (i == 5) alg2 = '5'
if (i == 6) alg2 = '6'
if (i == 7) alg2 = '7'
if (i == 8) alg2 = '8'
 
alg(1:1) = alg1
alg(2:2) = alg2
 
end subroutine ij2alg
 
end program
 
!-----------------------------------------------------------------------</syntaxhighlight>
 
{{out}}
$ echo "c5 2 T" | ./knights_tour
<pre>Tour number 1
c5 -> a6 -> b8 -> d7 -> f8 -> h7 -> g5 -> h3 ->
g1 -> e2 -> c1 -> a2 -> b4 -> d3 -> e1 -> g2 ->
h4 -> g6 -> h8 -> f7 -> d8 -> b7 -> a5 -> b3 ->
a1 -> c2 -> a3 -> b1 -> d2 -> f3 -> h2 -> f1 ->
g3 -> h1 -> f2 -> e4 -> c3 -> a4 -> b2 -> d1 ->
e3 -> g4 -> h6 -> g8 -> f6 -> h5 -> f4 -> d5 ->
e7 -> c8 -> a7 -> c6 -> e5 -> c4 -> b6 -> a8 ->
c7 -> e8 -> d6 -> b5 -> d4 -> f5 -> g7 -> e6 -> cycle
+----+----+----+----+----+----+----+----+
8 | 56 | 3 | 50 | 21 | 58 | 5 | 44 | 19 |
+----+----+----+----+----+----+----+----+
7 | 51 | 22 | 57 | 4 | 49 | 20 | 63 | 6 |
+----+----+----+----+----+----+----+----+
6 | 2 | 55 | 52 | 59 | 64 | 45 | 18 | 43 |
+----+----+----+----+----+----+----+----+
5 | 23 | 60 | 1 | 48 | 53 | 62 | 7 | 46 |
+----+----+----+----+----+----+----+----+
4 | 38 | 13 | 54 | 61 | 36 | 47 | 42 | 17 |
+----+----+----+----+----+----+----+----+
3 | 27 | 24 | 37 | 14 | 41 | 30 | 33 | 8 |
+----+----+----+----+----+----+----+----+
2 | 12 | 39 | 26 | 29 | 10 | 35 | 16 | 31 |
+----+----+----+----+----+----+----+----+
1 | 25 | 28 | 11 | 40 | 15 | 32 | 9 | 34 |
+----+----+----+----+----+----+----+----+
a b c d e f g h
 
Tour number 2
c5 -> a6 -> b8 -> d7 -> f8 -> h7 -> g5 -> h3 ->
g1 -> e2 -> c1 -> a2 -> b4 -> d3 -> e1 -> g2 ->
h4 -> g6 -> h8 -> f7 -> d8 -> b7 -> a5 -> b3 ->
a1 -> c2 -> a3 -> b1 -> d2 -> f3 -> h2 -> f1 ->
g3 -> h1 -> f2 -> e4 -> c3 -> a4 -> b2 -> d1 ->
e3 -> g4 -> h6 -> g8 -> f6 -> h5 -> f4 -> d5 ->
e7 -> c8 -> a7 -> c6 -> e5 -> c4 -> b6 -> a8 ->
c7 -> b5 -> d6 -> e8 -> g7 -> f5 -> d4 -> e6 -> cycle
+----+----+----+----+----+----+----+----+
8 | 56 | 3 | 50 | 21 | 60 | 5 | 44 | 19 |
+----+----+----+----+----+----+----+----+
7 | 51 | 22 | 57 | 4 | 49 | 20 | 61 | 6 |
+----+----+----+----+----+----+----+----+
6 | 2 | 55 | 52 | 59 | 64 | 45 | 18 | 43 |
+----+----+----+----+----+----+----+----+
5 | 23 | 58 | 1 | 48 | 53 | 62 | 7 | 46 |
+----+----+----+----+----+----+----+----+
4 | 38 | 13 | 54 | 63 | 36 | 47 | 42 | 17 |
+----+----+----+----+----+----+----+----+
3 | 27 | 24 | 37 | 14 | 41 | 30 | 33 | 8 |
+----+----+----+----+----+----+----+----+
2 | 12 | 39 | 26 | 29 | 10 | 35 | 16 | 31 |
+----+----+----+----+----+----+----+----+
1 | 25 | 28 | 11 | 40 | 15 | 32 | 9 | 34 |
+----+----+----+----+----+----+----+----+
a b c d e f g h
</pre>
 
===Fortran 2008===
{{works with|gfortran|11.2.1}}
(This one is ''not'' a translation of my ATS implementation. I wrote it earlier.)
<syntaxhighlight lang="fortran">!!!
!!! Find a Knight’s Tour.
!!!
!!! Use Warnsdorff’s heuristic, but write the program so it should not
!!! be able to terminate unsuccessfully.
!!!
 
module knights_tour
use, intrinsic :: iso_fortran_env, only: output_unit, error_unit
 
implicit none
private
 
public :: find_a_knights_tour
public :: notation_is_a_square
 
integer, parameter :: number_of_ranks = 8
integer, parameter :: number_of_files = 8
integer, parameter :: number_of_squares = number_of_ranks * number_of_files
 
! ‘Algebraic’ chess notation.
character, parameter :: rank_notation(1:8) = (/ '1', '2', '3', '4', '5', '6', '7', '8' /)
character, parameter :: file_notation(1:8) = (/ 'a', 'b', 'c', 'd', 'e', 'f', 'g', 'h' /)
 
type :: board_square_t
! Squares are represented by their algebraic notation.
character(2) :: algebraic_notation
contains
procedure, pass :: output => board_square_t_output
procedure, pass :: knight_moves => board_square_t_knight_moves
procedure, pass :: equal => board_square_t_equal
generic :: operator(==) => equal
end type board_square_t
 
type :: knight_moves_t
integer :: number_of_squares
type(board_square_t) :: squares(1:8)
end type knight_moves_t
 
type :: path_t
integer :: length
type(board_square_t) :: squares(1:number_of_squares)
contains
procedure, pass :: output => path_t_output
end type path_t
 
contains
 
pure function notation_is_a_square (notation) result (bool)
character(*), intent(in) :: notation
logical :: bool
 
integer :: length
integer :: rank_no
integer :: file_no
 
length = len_trim (notation)
if (length /= 2) then
bool = .false.
else
rank_no = findloc (rank_notation, notation(2:2), 1)
file_no = findloc (file_notation, notation(1:1), 1)
bool = (1 <= rank_no .and. rank_no <= number_of_ranks) &
& .and. (1 <= file_no .and. file_no <= number_of_files)
end if
end function notation_is_a_square
 
subroutine path_t_output (path, unit)
!
! Print a path in algebraic notation.
!
class(path_t), intent(in) :: path
integer, intent(in) :: unit
 
integer :: moves_counter
integer :: i
 
moves_counter = 1
if (1 <= path%length) then
call path%squares(1)%output(unit)
do i = 2, path%length
if (moves_counter == 8) then
write (unit, '(" ->")', advance = 'yes')
moves_counter = 1
else
write (unit, '(" -> ")', advance = 'no')
moves_counter = moves_counter + 1
end if
call path%squares(i)%output(unit)
end do
end if
write (output_unit, '()')
end subroutine path_t_output
 
subroutine board_square_t_output (square, unit)
!
! Print a square in algebraic notation.
!
class(board_square_t), intent(in) :: square
integer, intent(in) :: unit
 
write (unit, '(A2)', advance = 'no') square%algebraic_notation
end subroutine board_square_t_output
 
elemental function board_square_t_equal (p, q) result (bool)
class(board_square_t), intent(in) :: p, q
logical :: bool
 
bool = (p%algebraic_notation == q%algebraic_notation)
end function board_square_t_equal
 
pure function board_square_t_knight_moves (square) result (moves)
!
! Return all possible moves of a knight from a given square.
!
class(board_square_t), intent(in) :: square
type(knight_moves_t) :: moves
 
integer, parameter :: rank_stride(1:number_of_ranks) = (/ +1, +2, +1, +2, -1, -2, -1, -2 /)
integer, parameter :: file_stride(1:number_of_files) = (/ +2, +1, -2, -1, +2, +1, -2, -1 /)
 
integer :: rank_no, file_no
integer :: new_rank_no, new_file_no
integer :: i
character(2) :: notation
 
rank_no = findloc (rank_notation, square%algebraic_notation(2:2), 1)
file_no = findloc (file_notation, square%algebraic_notation(1:1), 1)
 
moves%number_of_squares = 0
do i = 1, 8
new_rank_no = rank_no + rank_stride(i)
new_file_no = file_no + file_stride(i)
if (1 <= new_rank_no &
& .and. new_rank_no <= number_of_ranks &
& .and. 1 <= new_file_no &
& .and. new_file_no <= number_of_files) then
moves%number_of_squares = moves%number_of_squares + 1
notation(2:2) = rank_notation(new_rank_no)
notation(1:1) = file_notation(new_file_no)
moves%squares(moves%number_of_squares) = board_square_t (notation)
end if
end do
end function board_square_t_knight_moves
 
pure function unvisited_knight_moves (path) result (moves)
!
! Return moves of a knight from a given square, but only those
! that have not been visited already.
!
class(path_t), intent(in) :: path
type(knight_moves_t) :: moves
 
type(knight_moves_t) :: all_moves
integer :: i
 
all_moves = path%squares(path%length)%knight_moves()
moves%number_of_squares = 0
do i = 1, all_moves%number_of_squares
if (all (.not. all_moves%squares(i) == path%squares(1:path%length))) then
moves%number_of_squares = moves%number_of_squares + 1
moves%squares(moves%number_of_squares) = all_moves%squares(i)
end if
end do
end function unvisited_knight_moves
 
pure function potential_knight_moves (path) result (moves)
!
! Return moves of a knight from a given square, but only those
! that are unvisited, and from which another unvisited move can be
! made.
!
! Sort the returned moves in nondecreasing order of the number of
! possible moves after the first. (This is how we implement
! Warnsdorff’s heuristic.)
!
class(path_t), intent(in) :: path
type(knight_moves_t) :: moves
 
type(knight_moves_t) :: unvisited_moves
type(knight_moves_t) :: next_moves
type(path_t) :: next_path
type(board_square_t) :: unpruned_squares(1:8)
integer :: warnsdorff_numbers(1:8)
integer :: number_of_unpruned_squares
integer :: i
 
if (path%length == number_of_squares - 1) then
!
! There is only one square left on the board. Either the knight
! can reach it or it cannot.
!
moves = unvisited_knight_moves (path)
else
!
! Use Warnsdorff’s heuristic: return unvisited moves, but try
! first those with the least number of possible moves following
! it.
!
! If the number of possible moves following is zero, prune the
! move, because it is a dead end.
!
number_of_unpruned_squares = 0
unvisited_moves = unvisited_knight_moves (path)
do i = 1, unvisited_moves%number_of_squares
next_path%length = path%length + 1
next_path%squares(1:path%length) = path%squares(1:path%length)
next_path%squares(next_path%length) = unvisited_moves%squares(i)
 
next_moves = unvisited_knight_moves (next_path)
 
if (next_moves%number_of_squares /= 0) then
number_of_unpruned_squares = number_of_unpruned_squares + 1
unpruned_squares(number_of_unpruned_squares) = unvisited_moves%squares(i)
warnsdorff_numbers(number_of_unpruned_squares) = next_moves%number_of_squares
end if
end do
 
! In-place insertion sort of the unpruned squares.
block
type(board_square_t) :: square
integer :: w_number
integer :: i, j
 
i = 2
do while (i <= number_of_unpruned_squares)
square = unpruned_squares(i)
w_number = warnsdorff_numbers(i)
j = i - 1
do while (1 <= j .and. w_number < warnsdorff_numbers(j))
unpruned_squares(j + 1) = unpruned_squares(j)
warnsdorff_numbers(j + 1) = warnsdorff_numbers(j)
j = j - 1
end do
unpruned_squares(j + 1) = square
warnsdorff_numbers(j + 1) = w_number
i = i + 1
end do
end block
 
moves%number_of_squares = number_of_unpruned_squares
moves%squares(1:number_of_unpruned_squares) = &
& unpruned_squares(1:number_of_unpruned_squares)
end if
end function potential_knight_moves
 
subroutine find_a_knights_tour (starting_square)
!
! Find and print a full knight’s tour.
!
character(2), intent(in) :: starting_square
 
type(path_t) :: path
 
path%length = 1
path%squares(1) = board_square_t (starting_square)
path = try_paths (path)
if (path%length /= 0) then
call path%output(output_unit)
else
write (error_unit, '("The program terminated without finding a solution.")')
write (error_unit, '("This is supposed to be impossible for an 8-by-8 board.")')
write (error_unit, '("The program is wrong.")')
error stop
end if
 
contains
 
recursive function try_paths (path) result (solution)
!
! Recursively try all possible paths, but using Warnsdorff’s
! heuristic to speed up the search.
!
class(path_t), intent(in) :: path
type(path_t) :: solution
 
type(path_t) :: new_path
type(knight_moves_t) :: moves
integer :: i
 
if (path%length == number_of_squares) then
solution = path
else
solution%length = 0
 
moves = potential_knight_moves (path)
 
if (moves%number_of_squares /= 0) then
new_path%length = path%length + 1
new_path%squares(1:path%length) = path%squares(1:path%length)
 
i = 1
do while (solution%length == 0 .and. i <= moves%number_of_squares)
new_path%squares(new_path%length) = moves%squares(i)
solution = try_paths (new_path)
i = i + 1
end do
end if
end if
end function try_paths
 
end subroutine find_a_knights_tour
 
end module knights_tour
 
program knights_tour_main
use, intrinsic :: iso_fortran_env, only: output_unit
use, non_intrinsic :: knights_tour
implicit none
 
character(200) :: arg
integer :: arg_count
integer :: i
 
arg_count = command_argument_count ()
do i = 1, arg_count
call get_command_argument (i, arg)
arg = adjustl (arg)
if (1 < i) write (output_unit, '()')
if (notation_is_a_square (arg)) then
call find_a_knights_tour (arg)
else
write (output_unit, '("This is not algebraic notation: ", A)') arg
end if
end do
end program knights_tour_main</syntaxhighlight>
 
$ ./knights_tour a1 b2 c3
<pre>a1 -> c2 -> a3 -> b1 -> d2 -> f1 -> h2 -> g4 ->
h6 -> g8 -> e7 -> c8 -> a7 -> b5 -> c7 -> a8 ->
b6 -> a4 -> b2 -> d1 -> f2 -> h1 -> g3 -> h5 ->
g7 -> e8 -> f6 -> h7 -> f8 -> d7 -> b8 -> a6 ->
b4 -> a2 -> c3 -> d5 -> e3 -> f5 -> h4 -> g2 ->
e1 -> f3 -> g1 -> h3 -> g5 -> e4 -> d6 -> c4 ->
a5 -> b7 -> d8 -> f7 -> h8 -> g6 -> e5 -> c6 ->
d4 -> e6 -> f4 -> e2 -> c1 -> d3 -> c5 -> b3
 
b2 -> a4 -> b6 -> a8 -> c7 -> e8 -> g7 -> h5 ->
g3 -> h1 -> f2 -> d1 -> c3 -> a2 -> c1 -> e2 ->
g1 -> h3 -> f4 -> g2 -> h4 -> g6 -> h8 -> f7 ->
d8 -> b7 -> a5 -> b3 -> a1 -> c2 -> e1 -> d3 ->
b4 -> a6 -> b8 -> d7 -> f8 -> h7 -> g5 -> e6 ->
c5 -> e4 -> f6 -> g8 -> h6 -> g4 -> h2 -> f1 ->
d2 -> b1 -> a3 -> c4 -> e5 -> f3 -> d4 -> b5 ->
d6 -> c8 -> a7 -> c6 -> e7 -> f5 -> e3 -> d5
 
c3 -> a2 -> c1 -> e2 -> g1 -> h3 -> g5 -> h7 ->
f8 -> g6 -> h8 -> f7 -> d8 -> b7 -> a5 -> b3 ->
a1 -> c2 -> a3 -> b1 -> d2 -> f1 -> h2 -> f3 ->
h4 -> g2 -> e1 -> d3 -> f4 -> h5 -> g7 -> e8 ->
f6 -> g8 -> h6 -> g4 -> e5 -> d7 -> b8 -> a6 ->
b4 -> c6 -> a7 -> c8 -> e7 -> d5 -> b6 -> a8 ->
c7 -> e6 -> c5 -> a4 -> b2 -> c4 -> e3 -> d1 ->
f2 -> h1 -> g3 -> e4 -> d6 -> f5 -> d4 -> b5</pre>
 
=={{header|Go}}==
===Warnsdorf's rule===
<lang go>/* Adapted from "Enumerating Knight's Tours using an Ant Colony Algorithm"
<syntaxhighlight lang="go">package main
 
import (
"fmt"
"math/rand"
"time"
)
 
// input, 0-based start position
const startRow = 0
const startCol = 0
 
func main() {
rand.Seed(time.Now().Unix())
for !knightTour() {
}
}
 
var moves = []struct{ dr, dc int }{
{2, 1},
{2, -1},
{1, 2},
{1, -2},
{-1, 2},
{-1, -2},
{-2, 1},
{-2, -1},
}
 
// Attempt knight tour starting at startRow, startCol using Warnsdorff's rule
// and random tie breaking. If a tour is found, print it and return true.
// Otherwise no backtracking, just return false.
func knightTour() bool {
// 8x8 board. squares hold 1-based visit order. 0 means unvisited.
board := make([][]int, 8)
for i := range board {
board[i] = make([]int, 8)
}
r := startRow
c := startCol
board[r][c] = 1 // first move
for move := 2; move <= 64; move++ {
minNext := 8
var mr, mc, nm int
candidateMoves:
for _, cm := range moves {
cr := r + cm.dr
if cr < 0 || cr >= 8 { // off board
continue
}
cc := c + cm.dc
if cc < 0 || cc >= 8 { // off board
continue
}
if board[cr][cc] > 0 { // already visited
continue
}
// cr, cc candidate legal move.
p := 0 // count possible next moves.
for _, m2 := range moves {
r2 := cr + m2.dr
if r2 < 0 || r2 >= 8 {
continue
}
c2 := cc + m2.dc
if c2 < 0 || c2 >= 8 {
continue
}
if board[r2][c2] > 0 {
continue
}
p++
if p > minNext { // bail out as soon as it's eliminated
continue candidateMoves
}
}
if p < minNext { // it's better. keep it.
minNext = p // new min possible next moves
nm = 1 // number of candidates with this p
mr = cr // best candidate move
mc = cc
continue
}
// it ties for best so far.
// keep it with probability 1/(number of tying moves)
nm++ // number of tying moves
if rand.Intn(nm) == 0 { // one chance to keep it
mr = cr
mc = cc
}
}
if nm == 0 { // no legal move
return false
}
// make selected move
r = mr
c = mc
board[r][c] = move
}
// tour complete. print board.
for _, r := range board {
for _, m := range r {
fmt.Printf("%3d", m)
}
fmt.Println()
}
return true
}</syntaxhighlight>
{{out}}
<pre>
1 4 39 20 23 6 63 58
40 19 2 5 62 57 22 7
3 38 41 48 21 24 59 64
18 43 32 37 56 61 8 25
31 14 47 42 49 36 53 60
46 17 44 33 52 55 26 9
13 30 15 50 11 28 35 54
16 45 12 29 34 51 10 27
</pre>
===Ant colony===
<syntaxhighlight lang="go">/* Adapted from "Enumerating Knight's Tours using an Ant Colony Algorithm"
by Philip Hingston and Graham Kendal,
PDF at http://www.cs.nott.ac.uk/~gxk/papers/cec05knights.pdf. */
Line 1,498 ⟶ 6,428:
tourCh <- moves
}
}</langsyntaxhighlight>
Output:
<pre>
Line 1,514 ⟶ 6,444:
 
=={{header|Haskell}}==
<syntaxhighlight lang="haskell">import Data.Bifunctor (bimap)
<lang Haskell>
import SystemData.Char (getArgschr, ord)
import Data.CharList (ordintercalate, chrminimumBy, sort, (\\))
import Data.List (minimumBy, (\\), intercalate, sort)
import Data.Ord (comparing)
import Control.Monad (join)
 
---------------------- KNIGHT'S TOUR ---------------------
 
type Square = (Int, Int)
 
board :: [Square]
board = [ (x,y) | x <- [1..8], y <- [1..8] ]
 
knightMoves :: Square -> [Square]
knightMoves (x,y) = filter (flip elem board) jumps
where jumps = [ (x+i,y+j) | i <- jv, j <- jv, abs i /= abs j ]
jv = [1,-1,2,-2]
 
knightTour :: [Square] -> [Square]
knightTour moves
| candMoves ==null []possibilities = reverse moves
| otherwise = knightTour $ newSquare : moves
where
where newSquare = minimumBy (comparing (length . findMoves)) candMoves
newSquare =
candMoves = findMoves $ head moves
minimumBy
findMoves sq = knightMoves sq \\ moves
(comparing (length . findMoves))
possibilities
possibilities = findMoves $ head moves
findMoves = (\\ moves) . knightOptions
 
knightOptions :: Square -> [Square]
main :: IO ()
knightOptions (x, y) =
main = do
knightMoves >>= sqgo <-. fmapbimap (toSq+ . headx) getArgs(+ y)
where
printTour $ map toAlg $ knightTour [sq]
go move
where toAlg (x,y) = [chr (x + 96), chr (y + 48)]
| toSq [x,y] =uncurry ((ord x&&) -(both 96,onBoard (ord ymove) -= 48)[move]
| otherwise printTour= [] = return ()
printTour tour = do
putStrLn $ intercalate " -> " $ take 8 tour
printTour $ drop 8 tour
</lang>
 
knightMoves :: [(Int, Int)]
Output:
knightMoves =
<pre>
e5 - ((>>=) f7 -<*> h8(\deltas n -> g6deltas ->>= h4go ->n)) g2[1, 2, -> e11, -> f32]
where
go i x
| abs i /= abs x = [(i, x)]
| otherwise = []
 
onBoard :: Int -> Bool
onBoard = (&&) . (0 <) <*> (9 >)
 
both :: (a -> b) -> (a, a) -> (b, b)
both = join bimap
 
--------------------------- TEST -------------------------
startPoint :: String
startPoint = "e5"
 
algebraic :: (Int, Int) -> String
algebraic (x, y) = [chr (x + 96), chr (y + 48)]
 
main :: IO ()
main =
printTour $
algebraic
<$> knightTour
[(\[x, y] -> (ord x - 96, ord y - 48)) startPoint]
where
printTour [] = return ()
printTour tour = do
putStrLn $ intercalate " -> " $ take 8 tour
printTour $ drop 8 tour</syntaxhighlight>
{{Out}}
<pre>e5 -> f7 -> h8 -> g6 -> h4 -> g2 -> e1 -> f3
g1 -> h3 -> g5 -> h7 -> f8 -> d7 -> b8 -> a6
b4 -> a2 -> c1 -> d3 -> b2 -> a4d1 -> b6f2 -> a8h1
c7g3 -> e8h5 -> g7 -> h5e8 -> f4f6 -> e6g8 -> d8h6 -> b7g4
c5h2 -> b3f1 -> a1e3 -> c2f5 -> a3e7 -> b1c8 -> d2a7 -> c4c6
a5d8 -> c6b7 -> a7a5 -> c8b3 -> d6a1 -> b5c2 -> d4 -> e2
c3f4 -> d1e6 -> f2c5 -> h1a4 -> g3b6 -> e4a8 -> f6c7 -> g8d5
h6c3 -> g4e4 -> h2d6 -> f1b5 -> e3a3 -> f5b1 -> e7d2 -> d5c4</pre>
</pre>
 
=={{header|Icon}} and {{header|Unicon}}==
Line 1,569 ⟶ 6,523:
 
The algorithm doesn't always generate a complete tour.
<langsyntaxhighlight Iconlang="icon">link printf
 
procedure main(A)
Line 1,669 ⟶ 6,623:
}
every write(hdr2|hdr1|&null)
end</langsyntaxhighlight>
 
The following can be used when debugging to validate the board structure and to image the available moves on the board.
<langsyntaxhighlight Iconlang="icon">procedure DumpBoard(B) #: Dump Board internals
write("Board size=",B.N)
write("Available Moves at start of tour:", ImageMovesTo(B.movesto))
Line 1,682 ⟶ 6,636:
every s ||:= " " || (!sort(movesto[k])|"\n")
return s
end</langsyntaxhighlight>
 
 
Line 1,734 ⟶ 6,688:
'''Solution:'''<br>
[[j:Essays/Knight's Tour|The Knight's tour essay on the Jwiki]] shows a couple of solutions including one using [[wp:Knight's_tour#Warnsdorff.27s_algorithm|Warnsdorffs algorithm]].
<langsyntaxhighlight lang="j">NB. knight moves for each square of a (y,y) board
kmoves=: monad define
t=. (>,{;~i.y) +"1/ _2]\2 1 2 _1 1 2 1 _2 _1 2 _1 _2 _2 1 _2 _1
Line 1,750 ⟶ 6,704:
assert. ~:p
(,~y)$/:p
)</langsyntaxhighlight>
 
'''Example Use:'''
<langsyntaxhighlight lang="j"> ktourw 8 NB. solution for an 8 x 8 board
0 25 14 23 28 49 12 31
15 22 27 50 13 30 63 48
Line 1,774 ⟶ 6,728:
555 558 553 778 563 570 775 780 785 772 1000...
100 551 556 561 102 777 572 771 104 781 57...
557 554 101 552 571 562 103 776 573 770 10...</langsyntaxhighlight>
 
=={{header|Java}}==
{{Works with|Java|7}}
<langsyntaxhighlight lang="java">import java.util.*;
 
public class KnightsTour {
Line 1,874 ⟶ 6,829:
}
}
}</langsyntaxhighlight>
<pre>34 17 20 3 36 7 22 5
19 2 35 40 21 4 37 8
Line 1,883 ⟶ 6,838:
14 31 64 53 12 29 58 25
63 48 13 30 59 26 11 28 </pre>
===More efficient non-trackback solution===
{{Works with|Java|8}}
<syntaxhighlight lang="text">
package com.knight.tour;
import java.util.ArrayList;
import java.util.Collections;
import java.util.Comparator;
import java.util.List;
 
public class KT {
=={{header|Kotlin}}==
{{trans|Haskell}}
 
private int baseSize = 12; // virtual board size including unreachable out-of-board nodes. i.e. base 12 = 8X8 board
<lang kotlin>import java.util.ArrayList
int actualBoardSize = baseSize - 4;
private static final int[][] moves = { { 1, -2 }, { 2, -1 }, { 2, 1 }, { 1, 2 }, { -1, 2 }, { -2, 1 }, { -2, -1 },
{ -1, -2 } };
private static int[][] grid;
private static int totalNodes;
private ArrayList<int[]> travelledNodes = new ArrayList<>();
public KT(int baseNumber) {
this.baseSize = baseNumber;
this.actualBoardSize = baseSize - 4;
}
 
public static void main(String[] args) {
class Square(val x : Int, val y : Int) {
new KT(12).tour(); // find a solution for 8X8 board
fun equals(s : Square) : Boolean = s.x == x && s.y == y
// new KT(24).tour(); // then for 20X20 board
// new KT(104).tour(); // then for 100X100 board
}
 
private void tour() {
totalNodes = actualBoardSize * actualBoardSize;
travelledNodes.clear();
grid = new int[baseSize][baseSize];
for (int r = 0; r < baseSize; r++)
for (int c = 0; c < baseSize; c++) {
if (r < 2 || r > baseSize - 3 || c < 2 || c > baseSize - 3) {
grid[r][c] = -1; // mark as out-of-board nodes
} else {
grid[r][c] = 0; // nodes within chess board.
}
}
// start from a random node
int startRow = 2 + (int) (Math.random() * actualBoardSize);
int startCol = 2 + (int) (Math.random() * actualBoardSize);
int[] start = { startRow, startCol, 0, 1 };
grid[startRow][startCol] = 1; // mark the first traveled node
travelledNodes.add(start); // add to partial solution chain, which will only have one node.
 
// Start traveling forward
autoKnightTour(start, 2);
}
 
// non-backtracking touring methods. Re-chain the partial solution when all neighbors are traveled to avoid back-tracking.
private void autoKnightTour(int[] start, int nextCount) {
List<int[]> nbrs = neighbors(start[0], start[1]);
if (nbrs.size() > 0) {
Collections.sort(nbrs, new Comparator<int[]>() {
public int compare(int[] a, int[] b) {
return a[2] - b[2];
}
}); // sort the list
int[] next = nbrs.get(0); // the one with the less available neighbors - Warnsdorff's algorithm
next[3] = nextCount;
travelledNodes.add(next);
grid[next[0]][next[1]] = nextCount;
if (travelledNodes.size() == totalNodes) {
System.out.println("Found a path for " + actualBoardSize + " X " + actualBoardSize + " chess board.");
StringBuilder sb = new StringBuilder();
sb.append(System.lineSeparator());
for (int idx = 0; idx < travelledNodes.size(); idx++) {
int[] item = travelledNodes.get(idx);
sb.append("->(" + (item[0] - 2) + "," + (item[1] - 2) + ")");
if ((idx + 1) % 15 == 0) {
sb.append(System.lineSeparator());
}
}
System.out.println(sb.toString() + "\n");
} else { // continuing the travel
autoKnightTour(next, ++nextCount);
}
} else { // no travelable neighbors next - need to rechain the partial chain
int[] last = travelledNodes.get(travelledNodes.size() - 1);
travelledNodes = reChain(travelledNodes);
if (travelledNodes.get(travelledNodes.size() - 1).equals(last)) {
travelledNodes = reChain(travelledNodes);
if (travelledNodes.get(travelledNodes.size() - 1).equals(last)) {
System.out.println("Re-chained twice but no travllable node found. Quiting...");
} else {
int[] end = travelledNodes.get(travelledNodes.size() - 1);
autoKnightTour(end, nextCount);
}
} else {
int[] end = travelledNodes.get(travelledNodes.size() - 1);
autoKnightTour(end, nextCount);
}
}
}
 
private ArrayList<int[]> reChain(ArrayList<int[]> alreadyTraveled) {
int[] last = alreadyTraveled.get(alreadyTraveled.size() - 1);
List<int[]> candidates = neighborsInChain(last[0], last[1]);
int cutIndex;
int[] randomPicked = candidates.get((int) Math.random() * candidates.size());
cutIndex = grid[randomPicked[0]][randomPicked[1]] - 1;
ArrayList<int[]> result = new ArrayList<int[]>(); //create empty list to copy already traveled nodes to
for (int k = 0; k <= cutIndex; k++) {
result.add(result.size(), alreadyTraveled.get(k));
}
for (int j = alreadyTraveled.size() - 1; j > cutIndex; j--) {
alreadyTraveled.get(j)[3] = result.size();
result.add(result.size(), alreadyTraveled.get(j));
}
return result; // re-chained partial solution with different end node
}
 
private List<int[]> neighborsInChain(int r, int c) {
List<int[]> nbrs = new ArrayList<>();
for (int[] m : moves) {
int x = m[0];
int y = m[1];
if (grid[r + y][c + x] > 0 && grid[r + y][c + x] != grid[r][c] - 1) {
int num = countNeighbors(r + y, c + x);
nbrs.add(new int[] { r + y, c + x, num, 0 });
}
}
return nbrs;
}
 
private static List<int[]> neighbors(int r, int c) {
List<int[]> nbrs = new ArrayList<>();
for (int[] m : moves) {
int x = m[0];
int y = m[1];
if (grid[r + y][c + x] == 0) {
int num = countNeighbors(r + y, c + x);
nbrs.add(new int[] { r + y, c + x, num, 0 }); // not-traveled neighbors and number of their neighbors
}
}
return nbrs;
 
}
 
private List<int[]> extendableNeighbors(List<int[]> neighbors) {
List<int[]> nbrs = new ArrayList<>();
for (int[] node : neighbors) {
if (node[2] > 0)
nbrs.add(node);
}
return nbrs;
}
 
private static int countNeighbors(int r, int c) {
int num = 0;
for (int[] m : moves) {
if (grid[r + m[1]][c + m[0]] == 0) {
num++;
}
}
return num;
}
}
</syntaxhighlight>
<pre>
Found a path for 8 X 8 chess board.
 
->(2,1)->(0,0)->(1,2)->(0,4)->(1,6)->(3,7)->(5,6)->(7,7)->(6,5)->(5,7)->(7,6)->(6,4)->(7,2)->(6,0)->(4,1)
->(2,0)->(0,1)->(1,3)->(0,5)->(1,7)->(3,6)->(2,4)->(0,3)->(1,1)->(3,0)->(2,2)->(1,0)->(0,2)->(1,4)->(0,6)
->(2,7)->(1,5)->(0,7)->(2,6)->(4,7)->(6,6)->(4,5)->(3,3)->(2,5)->(4,6)->(6,7)->(7,5)->(5,4)->(3,5)->(2,3)
->(4,4)->(3,2)->(4,0)->(5,2)->(7,3)->(6,1)->(5,3)->(3,4)->(4,2)->(6,3)->(7,1)->(5,0)->(3,1)->(4,3)->(5,5)
->(7,4)->(6,2)->(7,0)->(5,1)
</pre>
 
=={{header|Javascript}}==
===Procedural===
Using Warnsdorff rule and Backtracking.
 
You can test it [http://paulo-jorente.de/webgames/repos/knightsTour/ here].
 
<syntaxhighlight lang="javascript">
class KnightTour {
constructor() {
this.width = 856;
this.height = 856;
this.cellCount = 8;
this.size = 0;
this.knightPiece = "\u2658";
this.knightPos = {
x: 0,
y: 0
};
this.ctx = null;
this.step = this.width / this.cellCount;
this.lastTime = 0;
this.wait;
this.delay;
this.success;
this.jumps;
this.directions = [];
this.visited = [];
this.path = [];
document.getElementById("start").addEventListener("click", () => {
this.startHtml();
});
this.init();
this.drawBoard();
}
 
drawBoard() {
let a = false, xx, yy;
for (let y = 0; y < this.cellCount; y++) {
for (let x = 0; x < this.cellCount; x++) {
if (a) {
this.ctx.fillStyle = "#607db8";
} else {
this.ctx.fillStyle = "#aecaf0";
}
a = !a;
xx = x * this.step;
yy = y * this.step;
this.ctx.fillRect(xx, yy, xx + this.step, yy + this.step);
}
if (!(this.cellCount & 1)) a = !a;
}
if (this.path.length) {
const s = this.step >> 1;
this.ctx.lineWidth = 3;
this.ctx.fillStyle = "black";
this.ctx.beginPath();
this.ctx.moveTo(this.step * this.knightPos.x + s, this.step * this.knightPos.y + s);
let a, b, v = this.path.length - 1;
for (; v > -1; v--) {
a = this.path[v].pos.x * this.step + s;
b = this.path[v].pos.y * this.step + s;
this.ctx.lineTo(a, b);
this.ctx.fillRect(a - 5, b - 5, 10, 10);
}
this.ctx.stroke();
}
}
 
createMoves(pos) {
const possibles = [];
let x = 0,
y = 0,
m = 0,
l = this.directions.length;
for (; m < l; m++) {
x = pos.x + this.directions[m].x;
y = pos.y + this.directions[m].y;
if (x > -1 && x < this.cellCount && y > -1 && y < this.cellCount && !this.visited[x + y * this.cellCount]) {
possibles.push({
x,
y
})
}
}
return possibles;
}
 
warnsdorff(pos) {
const possibles = this.createMoves(pos);
if (possibles.length < 1) return [];
const moves = [];
for (let p = 0, l = possibles.length; p < l; p++) {
let ps = this.createMoves(possibles[p]);
moves.push({
len: ps.length,
pos: possibles[p]
});
}
moves.sort((a, b) => {
return b.len - a.len;
});
return moves;
}
 
startHtml() {
this.cellCount = parseInt(document.getElementById("cellCount").value);
this.size = Math.floor(this.width / this.cellCount)
this.wait = this.delay = parseInt(document.getElementById("delay").value);
this.step = this.width / this.cellCount;
this.ctx.font = this.size + "px Arial";
document.getElementById("log").innerText = "";
document.getElementById("path").innerText = "";
this.path = [];
this.jumps = 1;
this.success = true;
this.visited = [];
const cnt = this.cellCount * this.cellCount;
for (let a = 0; a < cnt; a++) {
this.visited.push(false);
}
const kx = parseInt(document.getElementById("knightx").value),
ky = parseInt(document.getElementById("knighty").value);
this.knightPos = {
x: (kx > this.cellCount || kx < 0) ? Math.floor(Math.random() * this.cellCount) : kx,
y: (ky > this.cellCount || ky < 0) ? Math.floor(Math.random() * this.cellCount) : ky
};
this.mainLoop = (time = 0) => {
const dif = time - this.lastTime;
this.lastTime = time;
this.wait -= dif;
if (this.wait > 0) {
requestAnimationFrame(this.mainLoop);
return;
}
this.wait = this.delay;
let moves;
if (this.success) {
moves = this.warnsdorff(this.knightPos);
} else {
if (this.path.length > 0) {
const path = this.path[this.path.length - 1];
moves = path.m;
if (moves.length < 1) this.path.pop();
this.knightPos = path.pos
this.visited[this.knightPos.x + this.knightPos.y * this.cellCount] = false;
this.jumps--;
this.wait = this.delay;
} else {
document.getElementById("log").innerText = "Can't find a solution!";
return;
}
}
this.drawBoard();
const ft = this.step - (this.step >> 3);
this.ctx.fillStyle = "#000";
this.ctx.fillText(this.knightPiece, this.knightPos.x * this.step, this.knightPos.y * this.step + ft);
if (moves.length < 1) {
if (this.jumps === this.cellCount * this.cellCount) {
document.getElementById("log").innerText = "Tour finished!";
let str = "";
for (let z of this.path) {
str += `${1 + z.pos.x + z.pos.y * this.cellCount}, `;
}
str += `${1 + this.knightPos.x + this.knightPos.y * this.cellCount}`;
document.getElementById("path").innerText = str;
return;
} else {
this.success = false;
}
} else {
this.visited[this.knightPos.x + this.knightPos.y * this.cellCount] = true;
const move = moves.pop();
this.path.push({
pos: this.knightPos,
m: moves
});
this.knightPos = move.pos
this.success = true;
this.jumps++;
}
requestAnimationFrame(this.mainLoop);
};
this.mainLoop();
}
 
init() {
const canvas = document.createElement("canvas");
canvas.id = "cv";
canvas.width = this.width;
canvas.height = this.height;
this.ctx = canvas.getContext("2d");
document.getElementById("out").appendChild(canvas);
this.directions = [{
x: -1,
y: -2
}, {
x: -2,
y: -1
}, {
x: 1,
y: -2
}, {
x: 2,
y: -1
},
{
x: -1,
y: 2
}, {
x: -2,
y: 1
}, {
x: 1,
y: 2
}, {
x: 2,
y: 1
}
];
}
}
new KnightTour();
</syntaxhighlight>
To test it, you'll need an index.html
<pre>
<!DOCTYPE html>
<html>
<head>
<meta charset="UTF-8">
<title>Knight's Tour</title>
<link rel="stylesheet" type="text/css" media="screen" href="style.css" />
</head>
<body>
<div id='out'></div>
<div id='ctrls'>
<span>Cells: </span><input id="cellCount" value="8" type="number" max="250" min="5"><br />
<span>Delay: </span><input id="delay" value="500" type="number" max="2000" min="0"><br />
<span>Knight X: </span><input id="knightx" value="-1" type="number" max="250" min="-1"><br />
<span>Knight Y: </span><input id="knighty" value="-1" type="number" max="250" min="-1"><br />
<button id="start">Start</button>
<div id='log'></div>
<div id="path"></div>
</div>
<script src="tour_bt.js" type="module"></script>
</body>
</html>
</pre>
And a style.css
<pre>
body {
font-family: verdana;
color: white;
font-size: 36px;
background-color: #001f33
}
button {
width: 100%;
height: 40px;
margin: 20px 0px 20px 0px;
font-size: 28px
}
canvas {
border: 4px solid #000;
margin: 40px;
}
#out {
float: left;
}
#ctrls {
margin-top: 40px;
text-align: left;
width: 280px;
line-height: 40px;
float: left;
}
#ctrls input {
float: right;
width: 80px;
height: 24px;
margin-top: 6px;
font-size: 22px;
}
#path {
margin-top: 10px;
font-size: 12px;
line-height: 16px;
}</pre>
 
===Functional===
 
A composition of values, drawing on generic abstractions:
{{Trans|Haskell}}
<syntaxhighlight lang="javascript">(() => {
'use strict';
 
// knightsTour :: Int -> [(Int, Int)] -> [(Int, Int)]
const knightsTour = rowLength => moves => {
const go = path => {
const
findMoves = xy => difference(knightMoves(xy), path),
warnsdorff = minimumBy(
comparing(compose(length, findMoves))
),
options = findMoves(path[0]);
return 0 < options.length ? (
go([warnsdorff(options)].concat(path))
) : reverse(path);
};
 
// board :: [[(Int, Int)]]
const board = concatMap(
col => concatMap(
row => [
[col, row]
],
enumFromTo(1, rowLength)),
enumFromTo(1, rowLength)
);
 
// knightMoves :: (Int, Int) -> [(Int, Int)]
const knightMoves = ([x, y]) =>
concatMap(
([dx, dy]) => {
const ab = [x + dx, y + dy];
return elem(ab, board) ? (
[ab]
) : [];
}, [
[-2, -1],
[-2, 1],
[-1, -2],
[-1, 2],
[1, -2],
[1, 2],
[2, -1],
[2, 1]
]
);
return go(moves);
};
 
// TEST -----------------------------------------------
// main :: IO()
const main = () => {
 
// boardSize :: Int
const boardSize = 8;
 
// tour :: [(Int, Int)]
const tour = knightsTour(boardSize)(
[fromAlgebraic('e5')]
);
 
// report :: String
const report = '(Board size ' +
boardSize + '*' + boardSize + ')\n\n' +
'Route: \n\n' +
showRoute(boardSize)(tour) + '\n\n' +
'Coverage and order: \n\n' +
showCoverage(boardSize)(tour) + '\n\n';
return (
console.log(report),
report
);
}
 
// DISPLAY --------------------------------------------
 
// algebraic :: (Int, Int) -> String
const algebraic = ([x, y]) =>
chr(x + 96) + y.toString();
 
// fromAlgebraic :: String -> (Int, Int)
const fromAlgebraic = s =>
2 <= s.length ? (
[ord(s[0]) - 96, parseInt(s.slice(1))]
) : undefined;
 
// showCoverage :: Int -> [(Int, Int)] -> String
const showCoverage = rowLength => xys => {
const
intMax = xys.length,
w = 1 + intMax.toString().length
return unlines(map(concat,
chunksOf(
rowLength,
map(composeList([justifyRight(w, ' '), str, fst]),
sortBy(
mappendComparing([
compose(fst, snd),
compose(snd, snd)
]),
zip(enumFromTo(1, intMax), xys)
)
)
)
));
};
 
// showRoute :: Int -> [(Int, Int)] -> String
const showRoute = rowLength => xys => {
const w = 1 + rowLength.toString().length;
return unlines(map(
xs => xs.join(' -> '),
chunksOf(
rowLength,
map(compose(justifyRight(w, ' '), algebraic), xys)
)
));
};
 
 
// GENERIC FUNCTIONS ----------------------------------
 
 
// Tuple (,) :: a -> b -> (a, b)
const Tuple = (a, b) => ({
type: 'Tuple',
'0': a,
'1': b,
length: 2
});
 
// chr :: Int -> Char
const chr = x => String.fromCodePoint(x);
 
// chunksOf :: Int -> [a] -> [[a]]
const chunksOf = (n, xs) =>
enumFromThenTo(0, n, xs.length - 1)
.reduce(
(a, i) => a.concat([xs.slice(i, (n + i))]),
[]
);
 
// compare :: a -> a -> Ordering
const compare = (a, b) =>
a < b ? -1 : (a > b ? 1 : 0);
 
// comparing :: (a -> b) -> (a -> a -> Ordering)
const comparing = f =>
(x, y) => {
const
a = f(x),
b = f(y);
return a < b ? -1 : (a > b ? 1 : 0);
};
 
// compose (<<<) :: (b -> c) -> (a -> b) -> a -> c
const compose = (f, g) => x => f(g(x));
 
// composeList :: [(a -> a)] -> (a -> a)
const composeList = fs =>
x => fs.reduceRight((a, f) => f(a), x, fs);
 
// concat :: [[a]] -> [a]
// concat :: [String] -> String
const concat = xs =>
0 < xs.length ? (() => {
const unit = 'string' !== typeof xs[0] ? (
[]
) : '';
return unit.concat.apply(unit, xs);
})() : [];
 
// concatMap :: (a -> [b]) -> [a] -> [b]
const concatMap = (f, xs) =>
xs.reduce((a, x) => a.concat(f(x)), []);
 
 
// difference :: Eq a => [a] -> [a] -> [a]
const difference = (xs, ys) => {
const s = new Set(ys.map(str));
return xs.filter(x => !s.has(str(x)));
};
 
// elem :: Eq a => a -> [a] -> Bool
const elem = (x, xs) => xs.some(eq(x))
 
 
// enumFromThenTo :: Int -> Int -> Int -> [Int]
const enumFromThenTo = (x1, x2, y) => {
const d = x2 - x1;
return Array.from({
length: Math.floor(y - x2) / d + 2
}, (_, i) => x1 + (d * i));
};
 
// enumFromTo :: Int -> Int -> [Int]
const enumFromTo = (m, n) =>
Array.from({
length: 1 + n - m
}, (_, i) => m + i);
 
// eq (==) :: Eq a => a -> a -> Bool
const eq = a => b => {
const t = typeof a;
return t !== typeof b ? (
false
) : 'object' !== t ? (
'function' !== t ? (
a === b
) : a.toString() === b.toString()
) : (() => {
const kvs = Object.entries(a);
return kvs.length !== Object.keys(b).length ? (
false
) : kvs.every(([k, v]) => eq(v)(b[k]));
})();
};
 
// fst :: (a, b) -> a
const fst = tpl => tpl[0];
 
// justifyRight :: Int -> Char -> String -> String
const justifyRight = (n, cFiller) => s =>
n > s.length ? (
s.padStart(n, cFiller)
) : s;
 
 
// length :: [a] -> Int
const length = xs =>
(Array.isArray(xs) || 'string' === typeof xs) ? (
xs.length
) : Infinity;
 
// map :: (a -> b) -> [a] -> [b]
const map = (f, xs) =>
(Array.isArray(xs) ? (
xs
) : xs.split('')).map(f);
 
// mappendComparing :: [(a -> b)] -> (a -> a -> Ordering)
const mappendComparing = fs =>
(x, y) => fs.reduce(
(ordr, f) => (ordr || compare(f(x), f(y))),
0
);
 
// minimumBy :: (a -> a -> Ordering) -> [a] -> a
const minimumBy = f => xs =>
xs.reduce((a, x) => undefined === a ? x : (
0 > f(x, a) ? x : a
), undefined);
 
// ord :: Char -> Int
const ord = c => c.codePointAt(0);
 
// reverse :: [a] -> [a]
const reverse = xs =>
'string' !== typeof xs ? (
xs.slice(0).reverse()
) : xs.split('').reverse().join('');
 
// snd :: (a, b) -> b
const snd = tpl => tpl[1];
 
// sortBy :: (a -> a -> Ordering) -> [a] -> [a]
const sortBy = (f, xs) =>
xs.slice()
.sort(f);
 
// str :: a -> String
const str = x => x.toString();
 
// take :: Int -> [a] -> [a]
// take :: Int -> String -> String
const take = (n, xs) =>
xs.slice(0, n);
 
// unlines :: [String] -> String
const unlines = xs => xs.join('\n');
 
// Use of `take` and `length` here allows for zipping with non-finite
// lists - i.e. generators like cycle, repeat, iterate.
 
// zip :: [a] -> [b] -> [(a, b)]
const zip = (xs, ys) => {
const lng = Math.min(length(xs), length(ys));
const bs = take(lng, ys);
return take(lng, xs).map((x, i) => Tuple(x, bs[i]));
};
 
// MAIN ---
return main();
})();</syntaxhighlight>
{{Out}}
<pre>(Board size 8*8)
 
Route:
 
e5 -> d7 -> b8 -> a6 -> b4 -> a2 -> c1 -> b3
a1 -> c2 -> a3 -> b1 -> d2 -> f1 -> h2 -> g4
h6 -> g8 -> e7 -> c8 -> a7 -> c6 -> a5 -> b7
d8 -> f7 -> h8 -> g6 -> f8 -> h7 -> f6 -> e8
g7 -> h5 -> g3 -> h1 -> f2 -> d1 -> b2 -> a4
b6 -> a8 -> c7 -> b5 -> c3 -> d5 -> e3 -> c4
d6 -> e4 -> c5 -> d3 -> e1 -> g2 -> h4 -> f5
d4 -> e2 -> f4 -> e6 -> g5 -> f3 -> g1 -> h3
 
Coverage and order:
 
9 6 11 40 23 4 21 42
12 39 8 5 44 41 24 3
7 10 45 48 51 22 43 20
38 13 52 57 46 49 2 25
53 58 47 50 1 60 19 32
14 37 62 59 56 31 26 29
63 54 35 16 61 28 33 18
36 15 64 55 34 17 30 27
</pre>
 
=={{header|jq}}==
'''Adapted from [[#Wren|Wren]]'''
 
'''Works with jq, the C implementation of jq'''
 
'''Works with gojq, the Go implementation of jq''' except that
_nwise/1 must be provided.
 
In the following program, the board size is specified by the top-level function named `boardSize`
so that it can readily be changed, e.g. to a variable set on the command-line.
In calculating algebraic notation, however, it is assumed that the board size is no larger than
26x26.
<syntaxhighlight lang="jq">
# The number of columns
def boardSize: 8;
 
# {x,y} with .x >= 0 and .y >= 0
def Square($x; $y): {$x, $y};
 
# Input: a Square assuming .x <= 25
def notate:
.x as $x
| "abcdefghijklmnopqrstuvwxyz"[$x:$x+1] + "\(.y + 1)";
 
# Input: a Square
# Output: a stream of possible Squares reachable from .
def knightMoves:
def axisMoves: [1, 2, -1, -2];
# Is the input Square on the board?
def onBoard:
0 <= .x and .x < boardSize and 0 <= .y and .y < boardSize;
. as $s
| axisMoves
| combinations(2)
| select( (.[0]|length) != (.[1]|length) ) # abs
| Square($s.x + .[0]; $s.y + .[1])
| select(onBoard) ;
 
# $moves should be a non-empty array specifying an initial fragment of a possible tour
def knightTour($moves):
# Find the array of relevant possible one-step moves from the Square specified by .
def findMoves:
[ knightMoves | select( IN($moves[]) | not) ] ;
 
($moves[-1] | findMoves) as $fm
| if $fm == [] then $moves
else ($fm | min_by( findMoves|length )) as $next
| knightTour($moves + [$next])
end ;
 
def knightTourFrom($start):
knightTour([$start]) ;
 
def example($square):
knightTourFrom($square)
| (_nwise(boardSize) | map("\(.x),\(.y)") | join(" ")),
"\nAlgebraic notation:",
(_nwise(boardSize) | map( notate ) | join(" "))
;
 
example(Square(1; 1))
</syntaxhighlight>
{{output}}
<pre>
1,1 3,0 5,1 7,0 6,2 7,4 6,6 4,7
2,6 0,7 1,5 0,3 2,2 1,0 0,2 1,4
0,6 2,7 3,5 1,6 3,7 5,6 7,7 6,5
7,3 6,1 4,0 2,1 0,0 1,2 0,4 2,3
3,1 5,0 7,1 6,3 7,5 6,7 4,6 5,4
4,2 3,4 5,5 7,6 5,7 3,6 1,7 0,5
1,3 0,1 2,0 3,2 4,4 2,5 3,3 4,1
5,3 7,2 6,0 5,2 6,4 4,5 2,4 4,3
 
Algebraic notation:
b2 d1 f2 h1 g3 h5 g7 e8
c7 a8 b6 a4 c3 b1 a3 b5
a7 c8 d6 b7 d8 f7 h8 g6
h4 g2 e1 c2 a1 b3 a5 c4
d2 f1 h2 g4 h6 g8 e7 f5
e3 d5 f6 h7 f8 d7 b8 a6
b4 a2 c1 d3 e5 c6 d4 e2
f4 h3 g1 f3 g5 e6 c5 e4
</pre>
 
=={{header|Julia}}==
Uses the Hidato puzzle solver module, which has its source code listed [[Solve_a_Hidato_puzzle#Julia | here]] in the Hadato task.
<syntaxhighlight lang="julia">using .Hidato # Note that the . here means to look locally for the module rather than in the libraries
 
const chessboard = """
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0 """
 
const knightmoves = [[-2, -1], [-2, 1], [-1, -2], [-1, 2], [1, -2], [1, 2], [2, -1], [2, 1]]
 
board, maxmoves, fixed, starts = hidatoconfigure(chessboard)
printboard(board, " 0", " ")
hidatosolve(board, maxmoves, knightmoves, fixed, starts[1][1], starts[1][2], 1)
printboard(board)
</syntaxhighlight>{{output}}<pre>
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0
1 12 9 6 3 14 17 20
10 7 2 13 18 21 4 15
31 28 11 8 5 16 19 22
64 25 32 29 36 23 48 45
33 30 27 24 49 46 37 58
26 63 52 35 40 57 44 47
53 34 61 50 55 42 59 38
62 51 54 41 60 39 56 43
</pre>
 
=={{header|Kotlin}}==
{{trans|Haskell}}
 
class Pair<Tsyntaxhighlight lang="scala">data class Square(val ax : TInt, val by : TInt)
 
val board = Array<Square>(8 * 8, { Square(it / 8 + 1, it % 8 + 1) })
val axisMoves = arrayarrayOf(1, 2, -1, -2)
 
fun allPairs<T> allPairs(a : Array<T>) = a .flatMap { i -> a .map { j -> Pair(i, j) } }
 
fun knightMoves(s : Square) : List<Square> {
val moves = allPairs(axisMoves) .filter { Math.abs(it.afirst) != Math.abs(it.bsecond) }
fun onBoard(s : Square) = board.any {it equals== s}
return moves .map { Square(s.x + it.afirst, s.y + it.bsecond) } .filter {(::onBoard(it)}
}
 
fun knightTour(moves : List<Square>) : List<Square> {
fun findMoves(s : Square) = knightMoves(s) .filterNot { m -> moves .any { it equals== m } }
val newSquare = findMoves(moves.last()) .minBy { findMoves(it).size }
return if (newSquare == null) moves else knightTour(moves + newSquare)
}
 
fun knightTourFrom(start : Square) = knightTour(arraylistOf(start).toList())
 
fun main(args : Array<String>) {
var col = 0
for (move(x, y) in knightTourFrom(Square(1, 1))) {
System.out.print("${move.x},${move.y}")
System.out.print(if (col == 7) "\n" else " ")
col = (col + 1) % 8
}
}</langsyntaxhighlight>
 
{{out}}
Line 1,937 ⟶ 7,795:
Influenced by the Python version, although computed tours are different.
 
<langsyntaxhighlight lang="locobasic">10 mode 1:defint a-z
20 input "Board size: ",size
30 input "Start position: ",a$
Line 1,983 ⟶ 7,841:
450 ' skip this move
460 next
470 return</langsyntaxhighlight>
 
[[File:Knights tour Locomotive Basic.png]]
 
=={{header|Lua}}==
<langsyntaxhighlight lang="lua">N = 8
 
moves = { {1,-2},{2,-1},{2,1},{1,2},{-1,2},{-2,1},{-2,-1},{-1,-2} }
Line 2,038 ⟶ 7,896:
print( string.format( "%s%d - %s%d", string.sub("ABCDEFGH",last[1],last[1]), last[2], string.sub("ABCDEFGH",lst[i][1],lst[i][1]), lst[i][2] ) )
last = lst[i]
end</langsyntaxhighlight>
=={{header|M2000 Interpreter}}==
<syntaxhighlight lang="m2000 interpreter">
Function KnightTour$(StartW=1, StartH=1){
def boolean swapH, swapV=True
if startW<=4 then swapH=true: StartW=8+1-StartW
if startH>4 then swapV=False: StartH=8+1-StartH
Let final=8*8, last=final-1, HighValue=final+1
Dim Board(1 to 8, 1 to 8), Moves(1 to 8, 1 to 8)=HighValue
f=stack:=1,2,3,4,5,6,7,8
if 8-StartW=2 and StartH=2 then stack f {shift 1,-8}
Function KnightMove(x,w,h) {
a=2:b=1:z=1:p=1
if x mod 2=1 then swap a,b
if x>2 then p-! : if x>4 then swap z, p : if x>6 then p-!
w+=z*a
h+=p*b
if w>=1 and w<=8 and h>=1 and h<=8 then =(w, h) else =(,)
}
For j=1 to 8 :For i=1 to 8
s=stack
For k=1 to 8
m=KnightMove(stackitem(f, k),i, j)
if len(m)>1 then Stack s {data m}
Next : Board(i,j)=s : Next
stack f {shift 1,-8}
Next
For i=1 to 8 :For j=1 to 8
s=Board(i, j)
if len(s)>2 then
so=queue
For k=1 to len(s)
m=stackitem(s, k)
Append so, Len(Board(m#val(0), m#val(1))) :=m
Next
sort ascending so as number
s=stack
stack s {for k=0 to len(so)-1:data so(k!):next}
Board(i,j)=s
end if
Next : Next
s= Board(StartW, StartH)
n=0
BackTrack=Stack
Moves=1
Moves(StartW, StartH)=1
Repeat
n++
While n>len(s) {
if Len(BackTrack)=0 then Print "Break", moves : Break
Moves--
Stack BackTrack {Read s, n}
m=stackitem(s, n)
Moves(m#val(0), m#val(1))=HighValue
n++
}
m=stackitem(s, n)
w=m#val(0)
h=m#val(1)
if Moves(w, h)>=Moves then
if Moves<last then
s1=Board(w, h) :ii=-1
for i=1 to len(s1){m1=stackitem(s1, i) :if Moves(m1#val(0),m1#val(1))>moves then ii=i-1 : exit
}
if ii>=0 then
Moves++
Moves(w,h)=Moves
Stack BackTrack {Push n, s}
s=s1: n=ii
end if
else
Moves++
Moves(w,h)=Moves
end if
end if
until Moves=final
Document export$
Inventory Tour
letters=stack:="a","b","c","d","e","f","g","h"
f=stack:=1,2,3,4,5,6,7,8
if swapV Else stack f {Shift 1,-8}
if swapH then stack letters {Shift 1,-8}
For j=1 to 8:For i=1 to 8
Append Tour, Moves(i,j) :=stackitem$(letters, i)+str$(stackitem(f, j),"")
Next : Next
Sort ascending Tour as number
one=each(Tour)
While one {
export$=Eval$(one)
if not one^=last then export$="->"
If (one^+1) mod 8=0 then
export$={
}
End if
}
=export$
}
Document ex$
ex$= {Knight's Tour from a1
}+KnightTour$()+{Knight's Tour from h1
}+KnightTour$(8,1)+{Knight's Tour from a8
}+KnightTour$(1, 8)+{Knight's Tour from h8
}+KnightTour$(8, 8)
Clipboard ex$
Report ex$
</syntaxhighlight>
{{out}}
<pre>
Knight's Tour from a1
a1->b3->a5->b7->d8->f7->h8->g6->
h4->g2->e1->c2->a3->b1->d2->f1->
h2->g4->h6->g8->e7->c8->a7->b5->
c7->a8->b6->a4->b2->d1->f2->h1->
g3->h5->g7->e8->f6->h7->f8->d7->
b8->a6->b4->a2->c1->e2->g1->h3->
g5->e6->f4->d3->c5->e4->c3->d5->
e3->c4->d6->f5->d4->f3->e5->c6
Knight's Tour from h1
h1->g3->h5->g7->e8->c7->a8->b6->
a4->b2->d1->f2->h3->g1->e2->c1->
a2->b4->a6->b8->d7->f8->h7->g5->
f7->h8->g6->h4->g2->e1->c2->a1->
b3->a5->b7->d8->c6->a7->c8->e7->
g8->h6->g4->h2->f1->d2->b1->a3->
b5->d6->c4->e3->f5->d4->f3->e5->
d3->f4->e6->c5->e4->c3->d5->f6
Knight's Tour from a8
a8->b6->a4->b2->d1->f2->h1->g3->
h5->g7->e8->c7->a6->b8->d7->f8->
h7->g5->h3->g1->e2->c1->a2->b4->
c2->a1->b3->a5->b7->d8->f7->h8->
g6->h4->g2->e1->f3->h2->f1->d2->
b1->a3->b5->a7->c8->e7->g8->h6->
g4->e3->f5->d6->c4->e5->c6->d4->
e6->c5->d3->f4->d5->f6->e4->c3
Knight's Tour from h8
h8->g6->h4->g2->e1->c2->a1->b3->
a5->b7->d8->f7->h6->g8->e7->c8->
a7->b5->a3->b1->d2->f1->h2->g4->
f2->h1->g3->h5->g7->e8->c7->a8->
b6->a4->b2->d1->c3->a2->c1->e2->
g1->h3->g5->h7->f8->d7->b8->a6->
b4->d3->c5->e6->f4->d5->f6->e4->
d6->f5->e3->c4->e5->c6->d4->f3
</pre>
 
=={{header|m4}}==
Warnsdorff’s rule, with random tie-breaks. The program keeps trying
until it finds a solution. Running time can vary a lot.
 
Beware the program writes to a file ‘__random_number__’ in the working directory. (This can be avoided in GNU m4 by using ‘esyscmd’ instead of ‘syscmd’. I do not know how to avoid it in general.)
 
<syntaxhighlight lang="m4">divert(-1)
 
----------------------------------------------------------------------
 
This is free and unencumbered software released into the public
domain.
 
Anyone is free to copy, modify, publish, use, compile, sell, or
distribute this software, either in source code form or as a compiled
binary, for any purpose, commercial or non-commercial, and by any
means.
 
In jurisdictions that recognize copyright laws, the author or authors
of this software dedicate any and all copyright interest in the
software to the public domain. We make this dedication for the benefit
of the public at large and to the detriment of our heirs and
successors. We intend this dedication to be an overt act of
relinquishment in perpetuity of all present and future rights to this
software under copyright law.
 
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
IN NO EVENT SHALL THE AUTHORS BE LIABLE FOR ANY CLAIM, DAMAGES OR
OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE,
ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
OTHER DEALINGS IN THE SOFTWARE.
 
For more information, please refer to <http://unlicense.org/>
 
----------------------------------------------------------------------
 
Find a Knight's tour, via Warnsdorff's rule.
 
For very old or 'Heirloom' m4, you may need to increase the sizes of
internal structures, with, say,
 
m4 -S 1000 -B 100000 knights_tour.m4
 
But I would use one of OpenBSD m4, GNU m4, etc., instead.
 
----------------------------------------------------------------------
 
dnl Get a random number from 0 to one less than $1.
dnl (Note that this is not a very good RNG. Also it writes a file.)
define(`randnum',
`syscmd(`echo $RANDOM > __random_number__')eval(include(__random_number__) % ( $1 ))')
 
 
dnl The left deconstructors for strings.
define(`string_car',`substr($1,0,1)')
define(`string_cdr',`substr($1,1)')
 
dnl Algebraic notation to 'i0j0', with i the ranks and j the files. Bad
dnl algebraic notation gets tranformed to '99999999'.
define(`alg2ij',
`ifelse($1,`a1',`1010',$1,`a2',`2010',$1,`a3',`3010',$1,`a4',`4010',
$1,`a5',`5010',$1,`a6',`6010',$1,`a7',`7010',$1,`a8',`8010',
$1,`b1',`1020',$1,`b2',`2020',$1,`b3',`3020',$1,`b4',`4020',
$1,`b5',`5020',$1,`b6',`6020',$1,`b7',`7020',$1,`b8',`8020',
$1,`c1',`1030',$1,`c2',`2030',$1,`c3',`3030',$1,`c4',`4030',
$1,`c5',`5030',$1,`c6',`6030',$1,`c7',`7030',$1,`c8',`8030',
$1,`d1',`1040',$1,`d2',`2040',$1,`d3',`3040',$1,`d4',`4040',
$1,`d5',`5040',$1,`d6',`6040',$1,`d7',`7040',$1,`d8',`8040',
$1,`e1',`1050',$1,`e2',`2050',$1,`e3',`3050',$1,`e4',`4050',
$1,`e5',`5050',$1,`e6',`6050',$1,`e7',`7050',$1,`e8',`8050',
$1,`f1',`1060',$1,`f2',`2060',$1,`f3',`3060',$1,`f4',`4060',
$1,`f5',`5060',$1,`f6',`6060',$1,`f7',`7060',$1,`f8',`8060',
$1,`g1',`1070',$1,`g2',`2070',$1,`g3',`3070',$1,`g4',`4070',
$1,`g5',`5070',$1,`g6',`6070',$1,`g7',`7070',$1,`g8',`8070',
$1,`h1',`1080',$1,`h2',`2080',$1,`h3',`3080',$1,`h4',`4080',
$1,`h5',`5080',$1,`h6',`6080',$1,`h7',`7080',$1,`h8',`8080',
`99999999')')
 
dnl The reverse of alg2ij. Bad 'i0j0' get transformed to 'z0'.
define(`ij2alg',
`ifelse($1,`1010',`a1',$1,`2010',`a2',$1,`3010',`a3',$1,`4010',`a4',
$1,`5010',`a5',$1,`6010',`a6',$1,`7010',`a7',$1,`8010',`a8',
$1,`1020',`b1',$1,`2020',`b2',$1,`3020',`b3',$1,`4020',`b4',
$1,`5020',`b5',$1,`6020',`b6',$1,`7020',`b7',$1,`8020',`b8',
$1,`1030',`c1',$1,`2030',`c2',$1,`3030',`c3',$1,`4030',`c4',
$1,`5030',`c5',$1,`6030',`c6',$1,`7030',`c7',$1,`8030',`c8',
$1,`1040',`d1',$1,`2040',`d2',$1,`3040',`d3',$1,`4040',`d4',
$1,`5040',`d5',$1,`6040',`d6',$1,`7040',`d7',$1,`8040',`d8',
$1,`1050',`e1',$1,`2050',`e2',$1,`3050',`e3',$1,`4050',`e4',
$1,`5050',`e5',$1,`6050',`e6',$1,`7050',`e7',$1,`8050',`e8',
$1,`1060',`f1',$1,`2060',`f2',$1,`3060',`f3',$1,`4060',`f4',
$1,`5060',`f5',$1,`6060',`f6',$1,`7060',`f7',$1,`8060',`f8',
$1,`1070',`g1',$1,`2070',`g2',$1,`3070',`g3',$1,`4070',`g4',
$1,`5070',`g5',$1,`6070',`g6',$1,`7070',`g7',$1,`8070',`g8',
$1,`1080',`h1',$1,`2080',`h2',$1,`3080',`h3',$1,`4080',`h4',
$1,`5080',`h5',$1,`6080',`h6',$1,`7080',`h7',$1,`8080',`h8',
`z0')')
 
dnl Move a knight from one square to another by an ij-vector. Both input
dnl and output are algebraic notation. If the move is illegal, it comes
dnl out as 'z0'.
define(`move_by',`ij2alg(eval(alg2ij($3) + 1000 * ( $1 ) + 10 * ( $2 )))')
 
dnl For example, a1d3c5 -> 3
define(`path_length',`eval(len($1) / 2)')
 
dnl The left deconstructors for paths.
define(`path_car',`substr($1,0,2)')
define(`path_cdr',`substr($1,2)')
 
dnl The right deconstructors for paths.
define(`path_last',`substr($1,eval(len($1) - 2))')
define(`path_drop_last',`substr($1,0,eval(len($1) - 2))')
 
dnl Extract the nth position from the path.
define(`path_nth',`substr($1,eval(( $2 ) * 2),2)')
 
define(`random_move',`path_nth($1,randnum(path_length($1)))')
 
dnl Is the position $1 contained in the path $2?
define(`path_contains',`ifelse(index($2,$1),-1,0,1)')
 
dnl Find all moves from position $1 that are not already in
dnl the path $2.
define(`possible_moves',
`ifelse(path_contains(move_by(1,2,$1),$2`'z0),`0',move_by(1,2,$1))`'dnl
ifelse(path_contains(move_by(2,1,$1),$2`'z0),`0',move_by(2,1,$1))`'dnl
ifelse(path_contains(move_by(1,-2,$1),$2`'z0),`0',move_by(1,-2,$1))`'dnl
ifelse(path_contains(move_by(2,-1,$1),$2`'z0),`0',move_by(2,-1,$1))`'dnl
ifelse(path_contains(move_by(-1,2,$1),$2`'z0),`0',move_by(-1,2,$1))`'dnl
ifelse(path_contains(move_by(-2,1,$1),$2`'z0),`0',move_by(-2,1,$1))`'dnl
ifelse(path_contains(move_by(-1,-2,$1),$2`'z0),`0',move_by(-1,-2,$1))`'dnl
ifelse(path_contains(move_by(-2,-1,$1),$2`'z0),`0',move_by(-2,-1,$1))')
 
dnl Count how many moves can follow each move in $1.
define(`follows_counts',
`ifelse($1,`',`',
`path_length(possible_moves(path_car($1),$2))`'follows_counts(path_cdr($1),$2)')')
 
dnl Find the smallest positive digit, or zero.
define(`min_positive',
`ifelse($1,`',0,
`pushdef(`min1',min_positive(string_cdr($1)))`'dnl
pushdef(`val1',string_car($1))`'dnl
ifelse(min1,0,val1,
val1,0,min1,
eval(val1 < min1),1,val1,min1)`'dnl
popdef(`min1',`val1')')')
 
dnl Change everything to zero that is not the minimum positive.
define(`apply_warnsdorff',`_$0(min_positive($1),$1)')
define(`_apply_warnsdorff',
`ifelse($2,`',`',`ifelse(string_car($2),$1,$1,0)`'$0($1,string_cdr($2))')')
 
dnl Find potential next moves that satisfy Warnsdorff's rule.
define(`warnsdorff_moves',
`pushdef(`moves',`possible_moves($1,$2)')`'dnl
pushdef(`selections',`apply_warnsdorff(follows_counts(moves))')`'dnl
_$0(moves,selections)`'dnl
popdef(`moves',`selections')')
define(`_warnsdorff_moves',
`ifelse($1,`',`',
`ifelse(string_car($2),0,`$0(path_cdr($1),string_cdr($2))',
`path_car($1)`'$0(path_cdr($1),string_cdr($2))')')')
 
dnl Find potential next moves for the given path.
define(`next_moves',
`ifelse(path_length($1),63,`possible_moves(path_last($1),$1)',
`warnsdorff_moves(path_last($1),$1)')')
 
define(`find_tour',
`ifelse($2,`',`find_tour($1,$1)',
path_length($2),64,$2,
`pushdef(`moves',next_moves($2))`'dnl
ifelse(moves,`',`find_tour($1)',
`find_tour($1,$2`'random_move(next_moves($2)))')`'dnl
popdef(`moves')')')
 
divert`'dnl
dnl
find_tour(a1)
find_tour(c5)
find_tour(h8)</syntaxhighlight>
 
{{out}}
This is just a sample. Outputs are random.
 
$ m4 knights_tour.m4
=={{header|Mathematica}}==
<pre>a1c2a3b1d2f1h2g4h6g8e7c8a7b5c7a8b6a4b2d1f2h1g3h5g7e8f6h7f8d7b8a6b4a2c1e2g1h3g5f7h8g6h4g2e1d3c5b7d8e6f4d5c3e4d6f5e3c4a5b3d4c6e5f3
c5b7d8f7h8g6h4g2e1c2a1b3c1a2b4a6b8d7f8h7g5h3g1e2g3h1f2d1b2a4b6a8c7e8g7h5f6g8h6g4h2f1d2b1a3b5a7c8e7d5c3e4d6f5e3c4a5c6d4e6f4d3e5f3
h8g6f8h7g5h3g1e2c1a2b4a6b8d7b6a8c7e8g7h5g3h1f2d1b2a4c5b7a5b3a1c2e1g2h4f3h2f1d2b1a3b5a7c8e7g8h6f7d8e6f4d3e5g4f6d5c3e4d6c4e3f5d4c6</pre>
 
=={{header|Mathematica}}/{{header|Wolfram Language}}==
'''Solution'''
<syntaxhighlight lang="mathematica">knightsTourMoves[start_] :=
<lang Mathematica>
knightsTourMoves[start_] :=
Module[{
vertexLabels = (# -> ToString@c[[Quotient[# - 1, 8] + 1]] <> ToString[Mod[# - 1, 8] + 1]) & /@ Range[64], knightsGraph,
Line 2,051 ⟶ 8,245:
hamiltonianCycle = ((FindHamiltonianCycle[knightsGraph] /. UndirectedEdge -> DirectedEdge) /. labels)[[1]];
end = Cases[hamiltonianCycle, (x_ \[DirectedEdge] start) :> x][[1]];
FindShortestPath[g, start, end]]</syntaxhighlight>
</lang>
 
'''Usage'''
<syntaxhighlight lang="mathematica">knightsTourMoves["d8"]
<lang Mathematica>
knightsTourMoves["d8"]
 
(* out *)
Line 2,062 ⟶ 8,254:
"c7", "a8", "b6", "c8", "d6", "e4", "d2", "f1", "e3", "d1", "f2", "h1", "g3", "e2", "c1", "d3", "e1", "g2", "h4", "f5", "e7", "d5", \
"f4", "h5", "g7", "e8", "f6", "g8", "h6", "g4", "h2", "f3", "g1", "h3", "g5", "h7", "f8", "d7", "e5", "g6", "h8", "f7"}
</syntaxhighlight>
</lang>
 
'''Analysis'''
 
'''vertexLabels''' replaces the default vertex (i.e. square) names of the chessboard with the standard algebraic names "a1", "a2",...,"h8".
<syntaxhighlight lang="mathematica">
<lang Mathematica>
vertexLabels = (# -> ToString@c[[Quotient[# - 1, 8] + 1]] <> ToString[Mod[# - 1, 8] + 1]) & /@ Range[64]
 
Line 2,078 ⟶ 8,270:
41 -> "f1", 42 -> "f2", 43 -> "f3", 44 -> "f4", 45 -> "f5", 46 -> "f6", 47 -> "f7", 48 -> "f8",
49 -> "g1", 50 -> "g2", 51 -> "g3", 52 -> "g4", 53 -> "g5", 54 -> "g6",55 -> "g7", 56 -> "g8",
57 -> "h1", 58 -> "h2", 59 -> "h3", 60 -> "h4", 61 -> "h5", 62 -> "h6", 63 -> "h7", 64 -> "h8"}</syntaxhighlight>
 
</lang>
 
'''knightsGraph''' creates a graph of the solution space.
<syntaxhighlight lang="mathematica">knightsGraph = KnightTourGraph[i, i, VertexLabels -> vertexLabels, ImagePadding -> 15];</syntaxhighlight>
<lang Mathematica>
knightsGraph = KnightTourGraph[i, i, VertexLabels -> vertexLabels, ImagePadding -> 15];
</lang>
[[File:KnightsTour-3.png]]
 
Find a Hamiltonian cycle (a path that visits each square exactly one time.)
 
<syntaxhighlight lang="mathematica">hamiltonianCycle = ((FindHamiltonianCycle[knightsGraph] /. UndirectedEdge -> DirectedEdge) /. labels)[[1]];</syntaxhighlight>
<lang Mathematica>
hamiltonianCycle = ((FindHamiltonianCycle[knightsGraph] /. UndirectedEdge -> DirectedEdge) /. labels)[[1]];
</lang>
 
Find the end square:
 
<syntaxhighlight lang="mathematica">end = Cases[hamiltonianCycle, (x_ \[DirectedEdge] start) :> x][[1]];</syntaxhighlight>
<lang Mathematica>
end = Cases[hamiltonianCycle, (x_ \[DirectedEdge] start) :> x][[1]];
</lang>
 
Find shortest path from the start square to the end square.
 
<syntaxhighlight lang="mathematica">FindShortestPath[g, start, end]]</syntaxhighlight>
<lang Mathematica>
FindShortestPath[g, start, end]]
</lang>
 
 
 
=={{header|Mathprog}}==
Line 2,115 ⟶ 8,295:
2. It is possible to specify which square is used for any Knights Move.
 
<syntaxhighlight lang="text">
/*Knights.mathprog
Line 2,177 ⟶ 8,357:
end;
</syntaxhighlight>
</lang>
 
Produces:
 
<syntaxhighlight lang="text">
GLPSOL: GLPK LP/MIP Solver, v4.47
Parameter(s) specified in the command line:
Line 2,227 ⟶ 8,407:
23 10 21 16 25
Model has been successfully processed
</syntaxhighlight>
</lang>
 
and
 
<syntaxhighlight lang="text">
/*Knights.mathprog
Line 2,296 ⟶ 8,476:
end;
</syntaxhighlight>
</lang>
 
Produces:
 
<syntaxhighlight lang="text">
GLPSOL: GLPK LP/MIP Solver, v4.47
Parameter(s) specified in the command line:
Line 2,365 ⟶ 8,545:
10 55 20 57 12 37 40 1
Model has been successfully processed
</syntaxhighlight>
</lang>
 
=={{header|Nim}}==
{{trans|C++}}
This is a translation of the C++ and D versions with some changes, the most important being the addition of a check to detect that there is no solution. Without this check, the program crashes with an IndexError as Nim in debug and in release modes generates code to insure that indexes are valid.
 
We have added a case to test the absence of solution. Note that, in this case, there is a lot of backtracking which considerably slows down the execution.
 
<syntaxhighlight lang="nim">import algorithm, options, random, parseutils, strutils, strformat
 
type
Board[N: static Positive] = array[N, array[N, int]]
Move = tuple[x, y: int]
MoveList = array[8, Move]
MoveIndexes = array[8, int]
 
const Moves: MoveList = [(2, 1), (1, 2), (-1, 2), (-2, 1), (-2, -1), (-1, -2), (1, -2), (2, -1)]
 
proc `$`(board: Board): string =
## Display the board.
let size = len($(board.N * board.N)) + 1
for row in board:
for val in row:
stdout.write ($val).align(size)
echo ""
 
proc sortedMoves(board: Board; x, y: int): MoveIndexes =
## Return the list of moves sorted by count of possible moves.
 
var counts: array[8, tuple[value, index: int]]
for i, d1 in Moves:
var count = 0
for d2 in Moves:
let x2 = x + d1.x + d2.x
let y2 = y + d1.y + d2.y
if x2 in 0..<board.N and y2 in 0..<board.N and board[y2][x2] == 0:
inc count
counts[i] = (count, i)
 
counts.shuffle() # Shuffle to randomly break ties.
counts.sort() # Lexicographic sort.
 
for i, count in counts:
result[i] = count.index
 
 
proc knightTour[N: static Positive](start: string): Option[Board[N]] =
## Return the knight tour for a board of size N x N and the starting
## position "start.
## If no solution is found, return "node" else return "some".
 
# Initialize the board with the starting position.
var board: Board[N]
var startx, starty: int
startx = ord(start[0]) - ord('a')
if startx notin 0..<N:
raise newException(ValueError, "wrong column.")
if parseInt(start, starty, 1) != start.len - 1 or starty notin 1..N:
raise newException(ValueError, "wrong line.")
starty = N - starty
board[starty][startx] = 1
 
type OrderItem = tuple[x, y, idx: int; mi: MoveIndexes]
var order: array[N * N, OrderItem]
order[0] = (startx, starty, 0, board.sortedMoves(startx, starty))
 
# Search a tour.
var n = 0
while n < N * N - 1:
let x = order[n].x
let y = order[n].y
var ok = false
 
for i in order[n].idx..7:
let d = Moves[order[n].mi[i]]
if x + d.x notin 0..<N or y + d.y notin 0..<N: continue
if board[y + d.y][x + d.x] == 0:
order[n].idx = i + 1
inc n
board[y + d.y][x + d.x] = n + 1
order[n] = (x + d.x, y + d.y, 0, board.sortedMoves(x + d.x, y + d.y))
ok = true
break
 
if not ok:
# Failed: backtrack.
echo "backtrack"
board[y][x] = 0
dec n
if n < 0: return none(Board[N]) # No solution found.
 
result = some(board)
 
 
proc run[N: static Positive](start: string) =
## Run the algorithm and display the result.
let result = knightTour[N](start)
echo &"Board size: {N}x{N}, starting position: {start}."
if result.isSome(): echo result.get()
else: echo "No solution found.\n"
 
 
when isMainModule:
 
randomize()
 
run[5]("c3")
#run[5]("c4") # No solution, so very slow compared to other cases.
run[8]("b5")
run[31]("a1")</syntaxhighlight>
 
{{out}}
<pre>Board size: 5x5, starting position: c3.
23 16 11 6 21
10 5 22 17 12
15 24 1 20 7
4 9 18 13 2
25 14 3 8 19
 
Board size: 5x5, starting position: c4.
No solution found.
 
Board size: 8x8, starting position: b5.
63 20 3 24 59 36 5 26
2 23 64 37 4 25 58 35
19 62 21 50 55 60 27 6
22 1 54 61 38 45 34 57
53 18 49 44 51 56 7 28
12 15 52 39 46 31 42 33
17 48 13 10 43 40 29 8
14 11 16 47 30 9 32 41
 
Board size: 31x31, starting position: a1.
275 112 19 116 277 604 21 118 823 770 23 120 961 940 25 122 943 926 27 124 917 898 29 126 911 872 31 128 197 870 33
18 115 276 601 20 117 772 767 22 119 958 851 24 121 954 941 26 123 936 925 28 125 912 899 30 127 910 871 32 129 198
111 274 113 278 605 760 603 822 771 824 769 948 957 960 939 944 953 942 927 916 929 918 897 908 913 900 873 196 875 34 869
114 17 600 273 602 775 766 773 768 949 850 959 852 947 952 955 932 937 930 935 924 915 920 905 894 909 882 901 868 199 130
271 110 279 606 759 610 761 776 821 764 825 816 951 956 853 938 945 934 923 928 919 896 893 914 907 904 867 874 195 876 35
16 581 272 599 280 607 774 765 762 779 950 849 826 815 946 933 854 931 844 857 890 921 906 895 886 883 902 881 200 131 194
109 270 281 580 609 758 611 744 777 820 763 780 817 848 827 808 811 846 855 922 843 858 889 892 903 866 885 192 877 36 201
282 15 582 269 598 579 608 757 688 745 778 819 754 783 814 847 828 807 810 845 856 891 842 859 884 887 880 863 202 193 132
267 108 283 578 583 612 689 614 743 756 691 746 781 818 753 784 809 812 829 806 801 840 835 888 865 862 203 878 191 530 37
14 569 268 585 284 597 576 619 690 687 742 755 692 747 782 813 752 785 802 793 830 805 860 841 836 879 864 529 204 133 190
107 266 285 570 577 584 613 686 615 620 695 684 741 732 711 748 739 794 751 786 803 800 839 834 861 528 837 188 531 38 205
286 13 568 265 586 575 596 591 618 685 616 655 696 693 740 733 712 749 738 795 792 831 804 799 838 833 722 527 206 189 134
263 106 287 508 571 590 587 574 621 592 639 694 683 656 731 710 715 734 787 750 737 796 791 832 721 798 207 532 187 474 39
12 417 264 567 288 509 572 595 588 617 654 657 640 697 680 713 730 709 716 735 788 727 720 797 790 723 526 473 208 135 186
105 262 289 416 507 566 589 512 573 622 593 638 653 682 659 698 679 714 729 708 717 736 789 726 719 472 533 184 475 40 209
290 11 418 261 502 415 510 565 594 513 562 641 658 637 652 681 660 699 678 669 728 707 718 675 724 525 704 471 210 185 136
259 104 291 414 419 506 503 514 511 564 623 548 561 642 551 636 651 670 661 700 677 674 725 706 703 534 211 476 183 396 41
10 331 260 493 292 501 420 495 504 515 498 563 624 549 560 643 662 635 650 671 668 701 676 673 524 705 470 395 212 137 182
103 258 293 330 413 494 505 500 455 496 547 516 485 552 625 550 559 644 663 634 649 672 667 702 535 394 477 180 397 42 213
294 9 332 257 492 329 456 421 490 499 458 497 546 517 484 553 626 543 558 645 664 633 648 523 666 469 536 393 220 181 138
255 102 295 328 333 412 491 438 457 454 489 440 459 486 545 518 483 554 627 542 557 646 665 632 537 478 221 398 179 214 43
8 319 256 335 296 345 326 409 422 439 436 453 488 441 460 451 544 519 482 555 628 541 522 647 468 631 392 219 222 139 178
101 254 297 320 327 334 411 346 437 408 423 368 435 452 487 442 461 450 445 520 481 556 629 538 479 466 399 176 215 44 165
298 7 318 253 336 325 344 349 410 347 360 407 424 383 434 427 446 443 462 449 540 521 480 467 630 391 218 223 164 177 140
251 100 303 300 321 316 337 324 343 350 369 382 367 406 425 384 433 428 447 444 463 430 539 390 465 400 175 216 169 166 45
6 299 252 317 304 301 322 315 348 361 342 359 370 381 366 405 426 385 432 429 448 389 464 401 174 217 224 163 150 141 168
99 250 241 302 235 248 307 338 323 314 351 362 341 358 371 380 365 404 377 386 431 402 173 388 225 160 153 170 167 46 143
240 5 98 249 242 305 234 247 308 339 232 313 352 363 230 357 372 379 228 403 376 387 226 159 154 171 162 149 142 151 82
63 2 239 66 97 236 243 306 233 246 309 340 231 312 353 364 229 356 373 378 227 158 375 172 161 148 155 152 83 144 47
4 67 64 61 238 69 96 59 244 71 94 57 310 73 92 55 354 75 90 53 374 77 88 51 156 79 86 49 146 81 84
1 62 3 68 65 60 237 70 95 58 245 72 93 56 311 74 91 54 355 76 89 52 157 78 87 50 147 80 85 48 145</pre>
 
=={{header|ObjectIcon}}==
{{trans|ATS}}
<syntaxhighlight lang="objecticon">#
# Find Knight’s Tours.
#
# Using Warnsdorff’s heuristic, find multiple solutions.
#
# Based on my ATS/Postiats program.
#
# The main difference from the ATS is this program uses a
# co-expression pair to make a generator of solutions, whereas the ATS
# simply prints solutions where they are found.
#
# Usage: ./knights_tour [START_POSITION [MAX_TOURS [closed]]]
# Examples:
# ./knights_tour (prints one tour starting from a1)
# ./knights_tour c5
# ./knights_tour c5 2000
# ./knights_tour c5 2000 closed
#
 
$define DEFAULT_NUMBER_OF_RANKS 8
$define DEFAULT_NUMBER_OF_FILES 8
 
import io
 
procedure main(args)
local f_out
local tours
local tour_board
local n_tour
local starting_position
local i, j
local max_tours
local closed_only
 
starting_position := \algebraic_notation_to_i_j(args[1]) | [1, 1]
i := starting_position[1]
j := starting_position[2]
 
max_tours := integer(args[2]) | 1
closed_only := if \args[3] === "closed" then &yes else &no
 
f_out := FileStream.stdout
 
tours := KnightsTours()
n_tour := 0
if n_tour < max_tours then
every tour_board := tours.generate(i, j, closed_only) do
{
n_tour +:= 1
write("Tour number ", n_tour)
f_out.write(tour_board.make_moves_display())
f_out.write(tour_board.make_board_display())
f_out.write()
if max_tours <= n_tour then
break
}
end
 
procedure algebraic_notation_to_i_j(s)
return [integer(s[2]), ord(s[1]) - ord('a') + 1]
end
 
class Move()
public const i
public const j
 
public new(rank, file)
i := rank
j := file
return
end
 
public make_display(n_ranks)
return char(ord('a') + j - 1) || i
end
end
 
class Chessboard()
 
public const n_ranks
public const n_files
public const n_squares
private board
 
public new(num_ranks, num_files)
/num_ranks := DEFAULT_NUMBER_OF_RANKS
/num_files := DEFAULT_NUMBER_OF_FILES
 
n_files := num_files
n_ranks := num_ranks
n_squares := n_ranks * n_files
board := list(n_squares)
return
end
 
public copy()
local new_board
local i
 
new_board := Chessboard(n_files, n_ranks)
every i := 1 to n_squares do
new_board.board[i] := board[i]
return new_board
end
 
public square(i, j)
# The board is stored in column-major order.
return board[i + (n_ranks * (j - 1))]
end
 
public try(i, j, value)
# Backtracking assignment. Though we use it for ordinary
# assignment.
#
# The board is stored in column-major order.
suspend board[i + (n_ranks * (j - 1))] <- value
end
 
public make_board_display()
local s
local i, j
 
s := ""
every i := n_ranks to 1 by -1 do
{
s ||:= " "
every j := 1 to n_files do
s ||:= "+----"
s ||:= "+\n"
s ||:= right(i, 2) || " "
every j := 1 to n_files do
s ||:= " | " || (\right(square(i, j), 2))
s ||:= " |\n"
}
s ||:= " "
every j := 1 to n_files do
s ||:= "+----"
s ||:= "+\n"
s ||:= " "
every j := 1 to n_files do
s ||:= " " || char(ord('a') + j - 1)
return s
end
 
public make_moves_display()
local positions
local i, j
local s
local first_position, last_position
 
positions := list(n_squares)
every i := 1 to n_ranks do
every j := 1 to n_files do
positions[square(i, j)] := Move(i, j)
 
s := ""
every j := 1 to n_squares - 1 do
{
s ||:= positions[j].make_display()
s ||:= (if j % n_files = 0 then " ->\n" else " -> ")
}
s ||:= positions[n_squares].make_display()
 
first_position := find_nth_position(1)
last_position := find_nth_position(n_squares)
if knight_positions_are_attacking(first_position.i,
first_position.j,
last_position.i,
last_position.j) then
s ||:= " -> cycle"
 
return s
end
 
public find_nth_position(n)
local i, j
local position
 
position := &null
i := 1
while /position & i <= n_ranks do
{
j := 1
while /position & j <= n_files do
{
if square(i, j) = n then
position := Move(i, j)
j +:= 1
}
i +:= 1
}
return position
end
 
end
 
class KnightsTours()
 
public const n_ranks
public const n_files
public const n_squares
private board
 
public new(num_ranks, num_files, i, j, closed_only)
board := Chessboard(num_ranks, num_files)
n_ranks := board.n_ranks
n_files := board.n_files
n_squares := board.n_squares
return
end
 
public generate(i, j, closed_only)
# i,j = starting position.
 
local consumer
local explorer
local tour_board
 
# Simple coroutines. The consumer receives complete tours (each in
# the form of a Chessboard) from the explorer.
consumer := &current
explorer := create explore(consumer, i, j, 1,
closed_only, i, j)
 
while tour_board := @explorer do
suspend tour_board
end
 
private explore(consumer, i, j, n_position,
closed_only, i_start, j_start)
# i,j = starting position.
board.try(i, j, n_position)
explore_inner(consumer, i, j, n_position,
closed_only, i_start, j_start)
board.try(i, j, &null)
end
 
private explore_inner(consumer, i, j, n_position,
closed_only, i_start, j_start)
local moves, mv
 
if n_squares - n_position = 1 then
{
# Is the last move possible? If so, make it and output the
# board. (Only zero or one of the moves can be non-null.)
moves := possible_moves(i, j)
every try_last_move(consumer, moves[1 to 8],
closed_only, i_start, j_start)
}
else
{
moves := next_moves(i, j, n_position)
every mv := !moves do
if \mv then
explore(consumer, mv.i, mv.j, n_position + 1,
closed_only, i_start, j_start)
}
end
 
private try_last_move(consumer, move, closed_only, i_start, j_start)
if \move then
if (/closed_only |
knight_positions_are_attacking(move.i, move.j,
i_start, j_start)) then
{
board.try(move.i, move.j, n_squares)
(board.copy())@consumer
board.try(move.i, move.j, &null)
}
end
 
private next_moves(i, j, n_position)
local moves
local w_list, w
local k
 
moves := possible_moves(i, j)
w_list := list(8)
every k := 1 to 8 do
w_list[k] := count_following_moves(moves[k], n_position)
w := pick_w(w_list)
if w = 0 then
# A dead end.
moves := list(8, &null)
else
# w is least positive number of following moves. Nullify any
# move that has either zero following moves (it is a dead end)
# or more than w following moves (it violates Warnsdorff’s
# heuristic).
every k := 1 to 8 do
if w_list[k] ~= w then
moves[k] := &null
return moves
end
 
private count_following_moves(move, n_position)
local w
local following_moves
 
w := 0
if \move then
{
board.try(move.i, move.j, n_position + 1)
following_moves := possible_moves(move.i, move.j)
every ( \following_moves[1 to 8] & w +:= 1 )
board.try(move.i, move.j, &null)
}
return w
end
 
private pick_w(w_list)
local w
 
w := 0
every w := next_pick (w, w_list[1 to 8])
return w
end
 
private next_pick(u, v)
local w
 
if v = 0 then
w := u
else if u = 0 then
w := v
else
w := min (u, v)
return w
end
 
private possible_moves(i, j)
local move1, move2, move3, move4
local move5, move6, move7, move8
 
move1 := try_move(i + 1, j + 2)
move2 := try_move(i + 2, j + 1)
move3 := try_move(i + 1, j - 2)
move4 := try_move(i + 2, j - 1)
move5 := try_move(i - 1, j + 2)
move6 := try_move(i - 2, j + 1)
move7 := try_move(i - 1, j - 2)
move8 := try_move(i - 2, j - 1)
return [move1, move2, move3, move4,
move5, move6, move7, move8]
end
 
private try_move(i1, j1)
return (1 <= i1 <= n_ranks &
1 <= j1 <= n_files &
/board.square(i1, j1) &
Move(i1, j1)) | &null
end
 
end
 
procedure knight_positions_are_attacking(i1, j1, i2, j2)
local i_diff, j_diff
 
i_diff := abs(i1 - i2)
j_diff := abs(j1 - j2)
return (((i_diff = 2 & j_diff = 1) |
(i_diff = 1 & j_diff = 2)) & &yes) | fail
end</syntaxhighlight>
 
{{out}}
$ ./knights_tour c5 2 closed
<pre>Tour number 1
c5 -> a6 -> b8 -> d7 -> f8 -> h7 -> g5 -> h3 ->
g1 -> e2 -> c1 -> a2 -> b4 -> d3 -> e1 -> g2 ->
h4 -> g6 -> h8 -> f7 -> d8 -> b7 -> a5 -> b3 ->
a1 -> c2 -> a3 -> b1 -> d2 -> f3 -> h2 -> f1 ->
g3 -> h1 -> f2 -> e4 -> c3 -> a4 -> b2 -> d1 ->
e3 -> g4 -> h6 -> g8 -> f6 -> h5 -> f4 -> d5 ->
e7 -> c8 -> a7 -> c6 -> e5 -> c4 -> b6 -> a8 ->
c7 -> e8 -> d6 -> b5 -> d4 -> f5 -> g7 -> e6 -> cycle
+----+----+----+----+----+----+----+----+
8 | 56 | 3 | 50 | 21 | 58 | 5 | 44 | 19 |
+----+----+----+----+----+----+----+----+
7 | 51 | 22 | 57 | 4 | 49 | 20 | 63 | 6 |
+----+----+----+----+----+----+----+----+
6 | 2 | 55 | 52 | 59 | 64 | 45 | 18 | 43 |
+----+----+----+----+----+----+----+----+
5 | 23 | 60 | 1 | 48 | 53 | 62 | 7 | 46 |
+----+----+----+----+----+----+----+----+
4 | 38 | 13 | 54 | 61 | 36 | 47 | 42 | 17 |
+----+----+----+----+----+----+----+----+
3 | 27 | 24 | 37 | 14 | 41 | 30 | 33 | 8 |
+----+----+----+----+----+----+----+----+
2 | 12 | 39 | 26 | 29 | 10 | 35 | 16 | 31 |
+----+----+----+----+----+----+----+----+
1 | 25 | 28 | 11 | 40 | 15 | 32 | 9 | 34 |
+----+----+----+----+----+----+----+----+
a b c d e f g h
 
Tour number 2
c5 -> a6 -> b8 -> d7 -> f8 -> h7 -> g5 -> h3 ->
g1 -> e2 -> c1 -> a2 -> b4 -> d3 -> e1 -> g2 ->
h4 -> g6 -> h8 -> f7 -> d8 -> b7 -> a5 -> b3 ->
a1 -> c2 -> a3 -> b1 -> d2 -> f3 -> h2 -> f1 ->
g3 -> h1 -> f2 -> e4 -> c3 -> a4 -> b2 -> d1 ->
e3 -> g4 -> h6 -> g8 -> f6 -> h5 -> f4 -> d5 ->
e7 -> c8 -> a7 -> c6 -> e5 -> c4 -> b6 -> a8 ->
c7 -> b5 -> d6 -> e8 -> g7 -> f5 -> d4 -> e6 -> cycle
+----+----+----+----+----+----+----+----+
8 | 56 | 3 | 50 | 21 | 60 | 5 | 44 | 19 |
+----+----+----+----+----+----+----+----+
7 | 51 | 22 | 57 | 4 | 49 | 20 | 61 | 6 |
+----+----+----+----+----+----+----+----+
6 | 2 | 55 | 52 | 59 | 64 | 45 | 18 | 43 |
+----+----+----+----+----+----+----+----+
5 | 23 | 58 | 1 | 48 | 53 | 62 | 7 | 46 |
+----+----+----+----+----+----+----+----+
4 | 38 | 13 | 54 | 63 | 36 | 47 | 42 | 17 |
+----+----+----+----+----+----+----+----+
3 | 27 | 24 | 37 | 14 | 41 | 30 | 33 | 8 |
+----+----+----+----+----+----+----+----+
2 | 12 | 39 | 26 | 29 | 10 | 35 | 16 | 31 |
+----+----+----+----+----+----+----+----+
1 | 25 | 28 | 11 | 40 | 15 | 32 | 9 | 34 |
+----+----+----+----+----+----+----+----+
a b c d e f g h
</pre>
 
=={{header|Perl}}==
Knight's tour using [[wp:Knight's_tour#Warnsdorff.27s_algorithm|Warnsdorffs algorithm]]
<langsyntaxhighlight lang="perl">use strict;
use warnings;
# Find a knight's tour
Line 2,455 ⟶ 9,223:
return unless $square =~ /^([a-h])([1-8])$/;
return (8-$2, ord($1) - ord('a'));
}</langsyntaxhighlight>
 
Sample output (start square c3):
Line 2,461 ⟶ 9,229:
[[File:perl_knights_tour.png]]
 
=={{header|Perl 6Phix}}==
This is pretty fast (<<1s) up to size 48, before some sizes start to take quite some time to complete. It will even solve a 200x200 in 0.67s
{{trans|Perl}}
<!--<syntaxhighlight lang="phix">(phixonline)-->
<lang perl6>my @board;
<span style="color: #008080;">with</span> <span style="color: #008080;">javascript_semantics</span>
<span style="color: #008080;">constant</span> <span style="color: #000000;">size</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">8</span><span style="color: #0000FF;">,</span>
<span style="color: #000000;">nchars</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #7060A8;">sprintf</span><span style="color: #0000FF;">(</span><span style="color: #008000;">" %d"</span><span style="color: #0000FF;">,</span><span style="color: #000000;">size</span><span style="color: #0000FF;">*</span><span style="color: #000000;">size</span><span style="color: #0000FF;">)),</span>
<span style="color: #000000;">fmt</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">sprintf</span><span style="color: #0000FF;">(</span><span style="color: #008000;">" %%%dd"</span><span style="color: #0000FF;">,</span><span style="color: #000000;">nchars</span><span style="color: #0000FF;">-</span><span style="color: #000000;">1</span><span style="color: #0000FF;">),</span>
<span style="color: #000000;">blank</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">repeat</span><span style="color: #0000FF;">(</span><span style="color: #008000;">' '</span><span style="color: #0000FF;">,</span><span style="color: #000000;">nchars</span><span style="color: #0000FF;">)</span>
<span style="color: #000080;font-style:italic;">-- to simplify output, each square is nchars</span>
<span style="color: #004080;">sequence</span> <span style="color: #000000;">board</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">repeat</span><span style="color: #0000FF;">(</span><span style="color: #7060A8;">repeat</span><span style="color: #0000FF;">(</span><span style="color: #008000;">' '</span><span style="color: #0000FF;">,</span><span style="color: #000000;">size</span><span style="color: #0000FF;">*</span><span style="color: #000000;">nchars</span><span style="color: #0000FF;">),</span><span style="color: #000000;">size</span><span style="color: #0000FF;">)</span>
<span style="color: #000080;font-style:italic;">-- keep current counts, immediately backtrack if any hit 0
-- (in line with the above, we only use every nth entry)</span>
<span style="color: #004080;">sequence</span> <span style="color: #000000;">warnsdorffs</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">repeat</span><span style="color: #0000FF;">(</span><span style="color: #7060A8;">repeat</span><span style="color: #0000FF;">(</span><span style="color: #000000;">0</span><span style="color: #0000FF;">,</span><span style="color: #000000;">size</span><span style="color: #0000FF;">*</span><span style="color: #000000;">nchars</span><span style="color: #0000FF;">),</span><span style="color: #000000;">size</span><span style="color: #0000FF;">)</span>
<span style="color: #008080;">constant</span> <span style="color: #000000;">ROW</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">1</span><span style="color: #0000FF;">,</span> <span style="color: #000000;">COL</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">2</span><span style="color: #0000FF;">,</span>
<span style="color: #000000;">moves</span> <span style="color: #0000FF;">=</span> <span style="color: #0000FF;">{{-</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,-</span><span style="color: #000000;">2</span><span style="color: #0000FF;">},{-</span><span style="color: #000000;">2</span><span style="color: #0000FF;">,-</span><span style="color: #000000;">1</span><span style="color: #0000FF;">},{-</span><span style="color: #000000;">2</span><span style="color: #0000FF;">,</span><span style="color: #000000;">1</span><span style="color: #0000FF;">},{-</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span><span style="color: #000000;">2</span><span style="color: #0000FF;">},{</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span><span style="color: #000000;">2</span><span style="color: #0000FF;">},{</span><span style="color: #000000;">2</span><span style="color: #0000FF;">,</span><span style="color: #000000;">1</span><span style="color: #0000FF;">},{</span><span style="color: #000000;">2</span><span style="color: #0000FF;">,-</span><span style="color: #000000;">1</span><span style="color: #0000FF;">},{</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,-</span><span style="color: #000000;">2</span><span style="color: #0000FF;">}}</span>
<span style="color: #008080;">function</span> <span style="color: #000000;">onboard</span><span style="color: #0000FF;">(</span><span style="color: #004080;">integer</span> <span style="color: #000000;">row</span><span style="color: #0000FF;">,</span> <span style="color: #004080;">integer</span> <span style="color: #000000;">col</span><span style="color: #0000FF;">)</span>
<span style="color: #008080;">return</span> <span style="color: #000000;">row</span><span style="color: #0000FF;">>=</span><span style="color: #000000;">1</span> <span style="color: #008080;">and</span> <span style="color: #000000;">row</span><span style="color: #0000FF;"><=</span><span style="color: #000000;">size</span> <span style="color: #008080;">and</span> <span style="color: #000000;">col</span><span style="color: #0000FF;">>=</span><span style="color: #000000;">nchars</span> <span style="color: #008080;">and</span> <span style="color: #000000;">col</span><span style="color: #0000FF;"><=</span><span style="color: #000000;">nchars</span><span style="color: #0000FF;">*</span><span style="color: #000000;">size</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">function</span>
<span style="color: #008080;">procedure</span> <span style="color: #000000;">init_warnsdorffs</span><span style="color: #0000FF;">()</span>
<span style="color: #008080;">for</span> <span style="color: #000000;">row</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span> <span style="color: #008080;">to</span> <span style="color: #000000;">size</span> <span style="color: #008080;">do</span>
<span style="color: #008080;">for</span> <span style="color: #000000;">col</span><span style="color: #0000FF;">=</span><span style="color: #000000;">nchars</span> <span style="color: #008080;">to</span> <span style="color: #000000;">nchars</span><span style="color: #0000FF;">*</span><span style="color: #000000;">size</span> <span style="color: #008080;">by</span> <span style="color: #000000;">nchars</span> <span style="color: #008080;">do</span>
<span style="color: #008080;">for</span> <span style="color: #000000;">move</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span> <span style="color: #008080;">to</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">moves</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">do</span>
<span style="color: #004080;">integer</span> <span style="color: #000000;">nrow</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">row</span><span style="color: #0000FF;">+</span><span style="color: #000000;">moves</span><span style="color: #0000FF;">[</span><span style="color: #000000;">move</span><span style="color: #0000FF;">][</span><span style="color: #000000;">ROW</span><span style="color: #0000FF;">],</span>
<span style="color: #000000;">ncol</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">col</span><span style="color: #0000FF;">+</span><span style="color: #000000;">moves</span><span style="color: #0000FF;">[</span><span style="color: #000000;">move</span><span style="color: #0000FF;">][</span><span style="color: #000000;">COL</span><span style="color: #0000FF;">]*</span><span style="color: #000000;">nchars</span>
<span style="color: #008080;">if</span> <span style="color: #000000;">onboard</span><span style="color: #0000FF;">(</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">,</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">then</span>
<span style="color: #000000;">warnsdorffs</span><span style="color: #0000FF;">[</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">][</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">]</span> <span style="color: #0000FF;">+=</span> <span style="color: #000000;">1</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">for</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">for</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">for</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">procedure</span>
<span style="color: #004080;">atom</span> <span style="color: #000000;">t0</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">time</span><span style="color: #0000FF;">(),</span>
<span style="color: #000000;">t1</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">time</span><span style="color: #0000FF;">()+</span><span style="color: #000000;">1</span>
<span style="color: #004080;">integer</span> <span style="color: #000000;">tries</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">0</span>
<span style="color: #008080;">function</span> <span style="color: #000000;">solve</span><span style="color: #0000FF;">(</span><span style="color: #004080;">integer</span> <span style="color: #000000;">row</span><span style="color: #0000FF;">,</span> <span style="color: #004080;">integer</span> <span style="color: #000000;">col</span><span style="color: #0000FF;">,</span> <span style="color: #004080;">integer</span> <span style="color: #000000;">n</span><span style="color: #0000FF;">)</span>
<span style="color: #008080;">if</span> <span style="color: #7060A8;">time</span><span style="color: #0000FF;">()></span><span style="color: #000000;">t1</span> <span style="color: #008080;">and</span> <span style="color: #7060A8;">platform</span><span style="color: #0000FF;">()!=</span><span style="color: #004600;">JS</span> <span style="color: #008080;">then</span>
<span style="color: #0000FF;">?{</span><span style="color: #000000;">row</span><span style="color: #0000FF;">,</span><span style="color: #7060A8;">floor</span><span style="color: #0000FF;">(</span><span style="color: #000000;">col</span><span style="color: #0000FF;">/</span><span style="color: #000000;">nchars</span><span style="color: #0000FF;">),</span><span style="color: #000000;">n</span><span style="color: #0000FF;">,</span><span style="color: #000000;">tries</span><span style="color: #0000FF;">}</span>
<span style="color: #7060A8;">puts</span><span style="color: #0000FF;">(</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span><span style="color: #7060A8;">join</span><span style="color: #0000FF;">(</span><span style="color: #000000;">board</span><span style="color: #0000FF;">,</span><span style="color: #008000;">"\n"</span><span style="color: #0000FF;">))</span>
<span style="color: #000000;">t1</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">time</span><span style="color: #0000FF;">()+</span><span style="color: #000000;">1</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
<span style="color: #000000;">tries</span><span style="color: #0000FF;">+=</span> <span style="color: #000000;">1</span>
<span style="color: #008080;">if</span> <span style="color: #000000;">n</span><span style="color: #0000FF;">></span><span style="color: #000000;">size</span><span style="color: #0000FF;">*</span><span style="color: #000000;">size</span> <span style="color: #008080;">then</span> <span style="color: #008080;">return</span> <span style="color: #000000;">1</span> <span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
<span style="color: #004080;">sequence</span> <span style="color: #000000;">wmoves</span> <span style="color: #0000FF;">=</span> <span style="color: #0000FF;">{}</span>
<span style="color: #004080;">integer</span> <span style="color: #000000;">nrow</span><span style="color: #0000FF;">,</span> <span style="color: #000000;">ncol</span>
<span style="color: #008080;">for</span> <span style="color: #000000;">move</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span> <span style="color: #008080;">to</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">moves</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">do</span>
<span style="color: #000000;">nrow</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">row</span><span style="color: #0000FF;">+</span><span style="color: #000000;">moves</span><span style="color: #0000FF;">[</span><span style="color: #000000;">move</span><span style="color: #0000FF;">][</span><span style="color: #000000;">ROW</span><span style="color: #0000FF;">]</span>
<span style="color: #000000;">ncol</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">col</span><span style="color: #0000FF;">+</span><span style="color: #000000;">moves</span><span style="color: #0000FF;">[</span><span style="color: #000000;">move</span><span style="color: #0000FF;">][</span><span style="color: #000000;">COL</span><span style="color: #0000FF;">]*</span><span style="color: #000000;">nchars</span>
<span style="color: #008080;">if</span> <span style="color: #000000;">onboard</span><span style="color: #0000FF;">(</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">,</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">)</span>
<span style="color: #008080;">and</span> <span style="color: #000000;">board</span><span style="color: #0000FF;">[</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">][</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">]=</span><span style="color: #008000;">' '</span> <span style="color: #008080;">then</span>
<span style="color: #000000;">wmoves</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">append</span><span style="color: #0000FF;">(</span><span style="color: #000000;">wmoves</span><span style="color: #0000FF;">,{</span><span style="color: #000000;">warnsdorffs</span><span style="color: #0000FF;">[</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">][</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">],</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">,</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">})</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">for</span>
<span style="color: #000000;">wmoves</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">sort</span><span style="color: #0000FF;">(</span><span style="color: #000000;">wmoves</span><span style="color: #0000FF;">)</span>
<span style="color: #000080;font-style:italic;">-- avoid creating orphans</span>
<span style="color: #008080;">if</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">wmoves</span><span style="color: #0000FF;">)<</span><span style="color: #000000;">2</span> <span style="color: #008080;">or</span> <span style="color: #000000;">wmoves</span><span style="color: #0000FF;">[</span><span style="color: #000000;">2</span><span style="color: #0000FF;">][</span><span style="color: #000000;">1</span><span style="color: #0000FF;">]></span><span style="color: #000000;">1</span> <span style="color: #008080;">then</span>
<span style="color: #008080;">for</span> <span style="color: #000000;">m</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span> <span style="color: #008080;">to</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">wmoves</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">do</span>
<span style="color: #0000FF;">{?,</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">,</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">}</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">wmoves</span><span style="color: #0000FF;">[</span><span style="color: #000000;">m</span><span style="color: #0000FF;">]</span>
<span style="color: #000000;">warnsdorffs</span><span style="color: #0000FF;">[</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">][</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">]</span> <span style="color: #0000FF;">-=</span> <span style="color: #000000;">1</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">for</span>
<span style="color: #008080;">for</span> <span style="color: #000000;">m</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span> <span style="color: #008080;">to</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">wmoves</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">do</span>
<span style="color: #0000FF;">{?,</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">,</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">}</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">wmoves</span><span style="color: #0000FF;">[</span><span style="color: #000000;">m</span><span style="color: #0000FF;">]</span>
<span style="color: #004080;">integer</span> <span style="color: #000000;">scol</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">ncol</span><span style="color: #0000FF;">-</span><span style="color: #000000;">nchars</span><span style="color: #0000FF;">+</span><span style="color: #000000;">1</span>
<span style="color: #000000;">board</span><span style="color: #0000FF;">[</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">][</span><span style="color: #000000;">scol</span><span style="color: #0000FF;">..</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">]</span> <span style="color: #0000FF;">=</span> <span style="color: #7060A8;">sprintf</span><span style="color: #0000FF;">(</span><span style="color: #000000;">fmt</span><span style="color: #0000FF;">,</span><span style="color: #000000;">n</span><span style="color: #0000FF;">)</span>
<span style="color: #008080;">if</span> <span style="color: #000000;">solve</span><span style="color: #0000FF;">(</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">,</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">,</span><span style="color: #000000;">n</span><span style="color: #0000FF;">+</span><span style="color: #000000;">1</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">then</span> <span style="color: #008080;">return</span> <span style="color: #000000;">1</span> <span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
<span style="color: #000000;">board</span><span style="color: #0000FF;">[</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">][</span><span style="color: #000000;">scol</span><span style="color: #0000FF;">..</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">]</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">blank</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">for</span>
<span style="color: #008080;">for</span> <span style="color: #000000;">m</span><span style="color: #0000FF;">=</span><span style="color: #000000;">1</span> <span style="color: #008080;">to</span> <span style="color: #7060A8;">length</span><span style="color: #0000FF;">(</span><span style="color: #000000;">wmoves</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">do</span>
<span style="color: #0000FF;">{?,</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">,</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">}</span> <span style="color: #0000FF;">=</span> <span style="color: #000000;">wmoves</span><span style="color: #0000FF;">[</span><span style="color: #000000;">m</span><span style="color: #0000FF;">]</span>
<span style="color: #000000;">warnsdorffs</span><span style="color: #0000FF;">[</span><span style="color: #000000;">nrow</span><span style="color: #0000FF;">][</span><span style="color: #000000;">ncol</span><span style="color: #0000FF;">]</span> <span style="color: #0000FF;">+=</span> <span style="color: #000000;">1</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">for</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
<span style="color: #008080;">return</span> <span style="color: #000000;">0</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">function</span>
<span style="color: #000000;">init_warnsdorffs</span><span style="color: #0000FF;">()</span>
<span style="color: #000000;">board</span><span style="color: #0000FF;">[</span><span style="color: #000000;">1</span><span style="color: #0000FF;">][</span><span style="color: #000000;">nchars</span><span style="color: #0000FF;">]</span> <span style="color: #0000FF;">=</span> <span style="color: #008000;">'1'</span>
<span style="color: #008080;">if</span> <span style="color: #000000;">solve</span><span style="color: #0000FF;">(</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span><span style="color: #000000;">nchars</span><span style="color: #0000FF;">,</span><span style="color: #000000;">2</span><span style="color: #0000FF;">)</span> <span style="color: #008080;">then</span>
<span style="color: #7060A8;">puts</span><span style="color: #0000FF;">(</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span><span style="color: #7060A8;">join</span><span style="color: #0000FF;">(</span><span style="color: #000000;">board</span><span style="color: #0000FF;">,</span><span style="color: #008000;">"\n"</span><span style="color: #0000FF;">))</span>
<span style="color: #7060A8;">printf</span><span style="color: #0000FF;">(</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span><span style="color: #008000;">"\nsolution found in %d tries (%3.2fs)\n"</span><span style="color: #0000FF;">,{</span><span style="color: #000000;">tries</span><span style="color: #0000FF;">,</span><span style="color: #7060A8;">time</span><span style="color: #0000FF;">()-</span><span style="color: #000000;">t0</span><span style="color: #0000FF;">})</span>
<span style="color: #008080;">else</span>
<span style="color: #7060A8;">puts</span><span style="color: #0000FF;">(</span><span style="color: #000000;">1</span><span style="color: #0000FF;">,</span><span style="color: #008000;">"no solutions found\n"</span><span style="color: #0000FF;">)</span>
<span style="color: #008080;">end</span> <span style="color: #008080;">if</span>
<!--</syntaxhighlight>-->
{{out}}
<pre>
"started"
1 16 31 40 3 18 21 56
30 39 2 17 42 55 4 19
15 32 41 46 53 20 57 22
38 29 48 43 58 45 54 5
33 14 37 52 47 60 23 62
28 49 34 59 44 63 6 9
13 36 51 26 11 8 61 24
50 27 12 35 64 25 10 7
solution found in 64 tries (0.00s)
</pre>
 
=={{header|Picat}}==
my $I = 8;
<syntaxhighlight lang="picat">import cp.
my $J = 8;
my $F = $I*$J > 99 ?? "%3d" !! "%2d";
# Choose starting position - may be passed in on command line; if
# not, choose random square.
my ($i, $j);
 
main =>
if my $sq = shift @*ARGS {
N = 8,
die "$*PROGRAM_NAME: illegal start square '$sq'\n" unless ($i, $j) = from_algebraic($sq);
A = new_array(N,N),
}
foreach (R in 1..N, C in 1..N)
else {
($i, $j) Connected = [(^$I).pickR+1, (^$JC+2).pick;,
(R+1, C-2),
}
(R-1, C+2),
(R-1, C-2),
# Move sequence
(R+2, C+1),
my @moves = ();
(R+2, C-1),
(R-2, C+1),
for 1 .. $I * $J -> $move {
(R-2, C-1)],
# Record current move
A[R,C] :: [(R1-1)*N+C1 : (R1,C1) in Connected, R1 >= 1, R1 =< N, C1 >= 1, C1 =< N]
push @moves, to_algebraic($i,$j);
end,
# @board[$i] //= []; # (uncomment if autoviv is broken)
V = vars(A),
@board[$i][$j] = $move;
circuit(V),
solve([ff],V),
# Find move with the smallest degree
my @min OutputM = new_array(9N,N);,
fill_output_matrix(N,OutputM,V,1,1),
for possible_moves($i,$j) -> @target {
foreach (R myin ($ni, $nj1..N) = @target;
my $next =foreach possible_moves($ni,$njC in 1..N);
@min = $next, $ni, $nj if $nextprintf("%3d <", @minOutputM[0R,C];)
end,
}
nl
# And make itend.
 
($i, $j) = @min[1,2];
fill_output_matrix(N,OutputM,V,I,Count) =>
}
if Count =< N*N then
R = (I-1) div N + 1,
# Print the move list
C = (I-1) mod N + 1,
for @moves.kv -> $i, $m {
OutputM[R,C] = Count,
print ',', $i %% 16 ?? "\n" !! " " if $i;
fill_output_matrix(N,OutputM,V,V[I],Count+1)
print $m;
end.
}
</syntaxhighlight>
say "\n";
 
{{out}}
# And the board, with move numbers
<pre>
for ^$I -> $i {
1 62 5 10 13 24 55 8
for ^$J -> $j {
4 #11 Assumes (1) ANSI2 sequences work,63 and (2) output6 9 14 23
61 64 #35 is light12 text on25 a dark56 background. 7 54
34 3 print "\e[7m"26 if $i59 % 236 == $j15 % 2;22 57
39 60 37 18 27 58 53 16
printf $F, @board[$i][$j];
30 33 40 43 46 17 50 21
print "\e[0m";
41 38 31 28 19 48 45 52
}
32 29 42 47 44 51 20 49
print "\n";
</pre>
}
# Find the list of positions the knight can move to from the given square
sub possible_moves($i,$j) {
grep -> [$ni, $nj] { $ni ~~ ^$I and $nj ~~ ^$J and !@board[$ni][$nj] },
[$i-2,$j-1], [$i-2,$j+1], [$i-1,$j-2], [$i-1,$j+2],
[$i+1,$j-2], [$i+1,$j+2], [$i+2,$j-1], [$i+2,$j+1];
}
# Return the algebraic name of the square identified by the coordinates
# i=rank, 0=black's home row; j=file, 0=white's queen's rook
sub to_algebraic($i,$j) {
chr(ord('a') + $j) ~ ($I - $i);
}
# Return the coordinates matching the given algebraic name
sub from_algebraic($square where /^ (<[a..z]>) (\d+) $/) {
$I - $1, ord(~$0) - ord('a');
}</lang>
(Output identical to Perl's above.)
 
=={{header|PicoLisp}}==
<langsyntaxhighlight PicoLisplang="picolisp">(load "@lib/simul.l")
 
# Build board
Line 2,569 ⟶ 9,411:
(moves Tour) )
(push 'Tour @) )
(flip Tour) )</langsyntaxhighlight>
Output:
<pre>-> (b1 a3 b5 a7 c8 b6 a8 c7 a6 b8 d7 f8 h7 g5 h3 g1 e2 c1 a2 b4 c2 a1 b3 a5 b7
Line 2,577 ⟶ 9,419:
=={{header|PostScript}}==
You probably shouldn't send this to a printer. Solution using Warnsdorffs algorithm.
<langsyntaxhighlight lang="postscript">%!PS-Adobe-3.0
%%BoundingBox: 0 0 300 300
 
Line 2,686 ⟶ 9,528:
3 1 100 { solve } for
 
%%EOF</langsyntaxhighlight>
 
=={{header|Prolog}}==
Worlks{{Works with |SWI-Prolog.<br>}}
Knights tour using [[wp:Knight's_tour#Warnsdorff.27s_algorithm|Warnsdorffs algorithm]]
 
<langsyntaxhighlight Prologlang="prolog">% N is the number of lines of the chessboard
knight(N) :-
Max is N * N,
Line 2,772 ⟶ 9,614:
M1 is M + 1,
display(N, M1, T).
</syntaxhighlight>
</lang>
 
Output :
Line 2,807 ⟶ 9,649:
31 188 257 266 29 270 273 290 27 318 327 324 25 336 329 400 23 20 331 392
256 191 30 189 274 265 28 269 272 291 26 319 328 325 24 337 330 391 22 19
true .</pre>
 
===Alternative version===
</pre>
{{Works with|GNU Prolog}}
<syntaxhighlight lang="prolog">:- initialization(main).
 
 
board_size(8).
in_board(X*Y) :- board_size(N), between(1,N,Y), between(1,N,X).
 
 
% express jump-graph in dynamic "move"-rules
make_graph :-
findall(_, (in_board(P), assert_moves(P)), _).
 
% where
assert_moves(P) :-
findall(_, (can_move(P,Q), asserta(move(P,Q))), _).
 
can_move(X*Y,Q) :-
( one(X,X1), two(Y,Y1) ; two(X,X1), one(Y,Y1) )
, Q = X1*Y1, in_board(Q)
. % where
one(M,N) :- succ(M,N) ; succ(N,M).
two(M,N) :- N is M + 2 ; N is M - 2.
 
 
 
hamiltonian(P,Pn) :-
board_size(N), Size is N * N
, hamiltonian(P,Size,[],Ps), enumerate(Size,Ps,Pn)
.
% where
enumerate(_, [] , [] ).
enumerate(N, [P|Ps], [N:P|Pn]) :- succ(M,N), enumerate(M,Ps,Pn).
 
 
hamiltonian(P,N,Ps,Res) :-
N =:= 1 -> Res = [P|Ps]
; warnsdorff(Ps,P,Q), succ(M,N)
, hamiltonian(Q,M,[P|Ps],Res)
.
% where
warnsdorff(Ps,P,Q) :-
moves(Ps,P,Qs), maplist(next_moves(Ps), Qs, Xs)
, keysort(Xs,Ys), member(_-Q,Ys)
.
next_moves(Ps,Q,L-Q) :- moves(Ps,Q,Rs), length(Rs,L).
 
moves(Ps,P,Qs) :-
findall(Q, (move(P,Q), \+ member(Q,Ps)), Qs).
 
show_path(Pn) :- findall(_, (in_board(P), show_cell(Pn,P)), _).
% where
show_cell(Pn,X*Y) :-
member(N:X*Y,Pn), format('%3.0d',[N]), board_size(X), nl.
 
 
main :- make_graph, hamiltonian(5*3,Pn), show_path(Pn), halt.</syntaxhighlight>
{{Output}}
<pre> 5 18 35 22 3 16 55 24
36 21 4 17 54 23 2 15
19 6 59 34 1 14 25 56
60 37 20 53 62 57 32 13
7 52 61 58 33 30 63 26
38 49 40 29 64 45 12 31
41 8 51 48 43 10 27 46
50 39 42 9 28 47 44 1</pre>
[http://ideone.com/jnFTT3 20x20 board runs in: time: 0.91 memory: 68608.]
 
=={{header|Python}}==
Knights tour using [[wp:Knight's_tour#Warnsdorff.27s_algorithm|Warnsdorffs algorithm]]
<langsyntaxhighlight lang="python">import copy
 
boardsize=6
Line 2,877 ⟶ 9,787:
start = input('Start position: ')
board = knights_tour(start, boardsize)
print(boardstring(board, boardsize=boardsize))</langsyntaxhighlight>
 
;Sample runs
Line 2,944 ⟶ 9,854:
The 200x200 example warmed my study in its computation but did return a tour.
 
P.S. There is a slight deviation to a strict interpretation of WarnsdorffsWarnsdorff's algorithm in that as a convenianceconvenience, tuples of the length of the nightknight moves followed by the position are minimized so knights moves with the same length will try and break the ties based on their minimum x,y position. In practice, it seems to give comparable results to the original algorithm.
 
boardsize: 5
Start position: a3
Traceback (most recent call last):
File "rosettacodekt.py", line 65, in <module>
board = knights_tour(start, boardsize)
File "rosettacodekt.py", line 51, in knights_tour
P = min(accessibility(board, P, boardsize))[1]
ValueError: min() arg is an empty sequence
 
=={{header|R}}==
Based on a slight modification of [[wp:Knight%27s_tour#Warnsdorff.27s_rule|Warnsdorff's algorithm]], in that if a dead-end is reached, the program backtracks to the next best move.
 
<langsyntaxhighlight lang="r">#!/usr/bin/Rscript
# M x N Chess Board.
Line 3,017 ⟶ 9,936:
# Begin tour.
setboard(position, 1); knightTour(position, 2)</langsyntaxhighlight>
 
Output:
Line 3,035 ⟶ 9,954:
 
=={{header|Racket}}==
<langsyntaxhighlight lang="racket">
#lang racket
(define N 8)
Line 3,060 ⟶ 9,979:
" "))))
(draw (tour (random N) (random N)))
</syntaxhighlight>
</lang>
{{out}}
<pre>
Line 3,072 ⟶ 9,991:
29 26 7 62 21 24 5 2
</pre>
 
=={{header|Raku}}==
(formerly Perl 6)
{{trans|Perl}}
<syntaxhighlight lang="raku" line>my @board;
 
my $I = 8;
my $J = 8;
my $F = $I*$J > 99 ?? "%3d" !! "%2d";
# Choose starting position - may be passed in on command line; if
# not, choose random square.
my ($i, $j);
 
if my $sq = shift @*ARGS {
die "$*PROGRAM_NAME: illegal start square '$sq'\n" unless ($i, $j) = from_algebraic($sq);
}
else {
($i, $j) = (^$I).pick, (^$J).pick;
}
# Move sequence
my @moves = ();
for 1 .. $I * $J -> $move {
# Record current move
push @moves, to_algebraic($i,$j);
@board[$i][$j] = $move;
# Find move with the smallest degree
my @min = (9);
for possible_moves($i,$j) -> @target {
my ($ni, $nj) = @target;
my $next = possible_moves($ni,$nj);
@min = $next, $ni, $nj if $next < @min[0];
}
# And make it
($i, $j) = @min[1,2];
}
# Print the move list
for @moves.kv -> $i, $m {
print ',', $i %% 16 ?? "\n" !! " " if $i;
print $m;
}
say "\n";
# And the board, with move numbers
for ^$I -> $i {
for ^$J -> $j {
# Assumes (1) ANSI sequences work, and (2) output
# is light text on a dark background.
print "\e[7m" if $i % 2 == $j % 2;
printf $F, @board[$i][$j];
print "\e[0m";
}
print "\n";
}
# Find the list of positions the knight can move to from the given square
sub possible_moves($i,$j) {
grep -> [$ni, $nj] { $ni ~~ ^$I and $nj ~~ ^$J and !@board[$ni][$nj] },
[$i-2,$j-1], [$i-2,$j+1], [$i-1,$j-2], [$i-1,$j+2],
[$i+1,$j-2], [$i+1,$j+2], [$i+2,$j-1], [$i+2,$j+1];
}
# Return the algebraic name of the square identified by the coordinates
# i=rank, 0=black's home row; j=file, 0=white's queen's rook
sub to_algebraic($i,$j) {
chr(ord('a') + $j) ~ ($I - $i);
}
# Return the coordinates matching the given algebraic name
sub from_algebraic($square where /^ (<[a..z]>) (\d+) $/) {
$I - $1, ord(~$0) - ord('a');
}</syntaxhighlight>
(Output identical to Perl's above.)
 
=={{Header|RATFOR}}==
{{trans|ATS}}
For use with the public domain ratfor77 translator and a FORTRAN 77 compiler.
<syntaxhighlight lang="ratfor">#-----------------------------------------------------------------------
#
# Find Knight’s Tours.
#
# Using Warnsdorff’s heuristic, find multiple solutions.
# Optionally accept only closed tours.
#
# This program is migrated from my implementation for ATS/Postiats.
# Arrays with dimension 1:64 take the place of stack frames.
#
# Compile with, for instance:
#
# ratfor77 knights_tour.r > knights_tour.f
# gfortran -O2 -g -std=legacy -o knights_tour knights_tour.f
#
# or
#
# ratfor77 knights_tour.r > knights_tour.f
# f2c knights_tour.f
# cc -O -o knights_tour knights_tour.c -lf2c
#
# Usage examples:
#
# One tour starting at a1, either open or closed:
#
# echo "a1 1 F" | ./knights_tour
#
# No more than 2000 closed tours starting at c5:
#
# echo "c5 2000 T" | ./knights_tour
#
#-----------------------------------------------------------------------
 
program ktour
implicit none
 
character*2 alg
integer i, j
integer mxtour
logical closed
 
read (*,*) alg, mxtour, closed
call alg2ij (alg, i, j)
call explor (i, j, mxtour, closed)
 
end
 
#-----------------------------------------------------------------------
 
subroutine explor (istart, jstart, mxtour, closed)
implicit none
 
# Explore the space of 'Warnsdorffian' knight’s paths, looking for
# and printing complete tours.
 
integer istart, jstart # The starting position.
integer mxtour # The maximum number of tours to print.
logical closed # Closed tours only?
 
integer board(1:8,1:8)
integer imove(1:8,1:64)
integer jmove(1:8,1:64)
integer nmove(1:64)
integer n
integer itours
logical goodmv
logical isclos
 
itours = 0
call initbd (board)
n = 1
nmove(1) = 8
imove(8, 1) = istart
jmove(8, 1) = jstart
 
while (itours < mxtour && n != 0) {
if (nmove(n) == 9) {
n = n - 1
if (n != 0) {
call unmove (board, imove, jmove, nmove, n)
nmove(n) = nmove(n) + 1
}
} else if (goodmv (imove, nmove, n)) {
call mkmove (board, imove, jmove, nmove, n)
if (n == 64) {
if (.not. closed) {
itours = itours + 1
call prnt (board, itours)
} else if (isclos (board)) {
itours = itours + 1
call prnt (board, itours)
}
call unmove (board, imove, jmove, nmove, n)
nmove(n) = 9
} else if (n == 63) {
call possib (board, n, imove, jmove, nmove)
n = n + 1
nmove(n) = 1
} else {
call nxtmov (board, n, imove, jmove, nmove)
n = n + 1
nmove(n) = 1
}
} else {
nmove(n) = nmove(n) + 1
}
}
 
end
 
#-----------------------------------------------------------------------
 
subroutine initbd (board)
implicit none
 
# Initialize a chessboard with empty squares.
 
integer board(1:8,1:8)
 
integer i, j
 
do j = 1, 8 {
do i = 1, 8 {
board(i, j) = -1
}
}
 
end
 
#-----------------------------------------------------------------------
 
subroutine mkmove (board, imove, jmove, nmove, n)
implicit none
 
# Fill a square with a move number.
 
integer board(1:8, 1:8)
integer imove(1:8, 1:64)
integer jmove(1:8, 1:64)
integer nmove(1:64)
integer n
 
board(imove(nmove(n), n), jmove(nmove(n), n)) = n
 
end
 
#-----------------------------------------------------------------------
 
subroutine unmove (board, imove, jmove, nmove, n)
implicit none
 
# Unmake a mkmove.
 
integer board(1:8, 1:8)
integer imove(1:8, 1:64)
integer jmove(1:8, 1:64)
integer nmove(1:64)
integer n
 
board(imove(nmove(n), n), jmove(nmove(n), n)) = -1
 
end
 
#-----------------------------------------------------------------------
 
function goodmv (imove, nmove, n)
implicit none
 
logical goodmv
integer imove(1:8, 1:64)
integer nmove(1:64)
integer n
 
goodmv = (imove(nmove(n), n) != -1)
 
end
 
#-----------------------------------------------------------------------
 
subroutine prnt (board, itours)
implicit none
 
# Print a knight's tour.
 
integer board(1:8,1:8)
integer itours
 
10000 format (1X)
 
# The following plethora of format statements seemed a simple way to
# get this working with f2c. (For gfortran, the 'I0' format
# sufficed.)
10010 format (1X, "Tour number ", I1)
10020 format (1X, "Tour number ", I2)
10030 format (1X, "Tour number ", I3)
10040 format (1X, "Tour number ", I4)
10050 format (1X, "Tour number ", I5)
10060 format (1X, "Tour number ", I6)
10070 format (1X, "Tour number ", I20)
 
if (itours < 10) {
write (*, 10010) itours
} else if (itours < 100) {
write (*, 10020) itours
} else if (itours < 1000) {
write (*, 10030) itours
} else if (itours < 10000) {
write (*, 10040) itours
} else if (itours < 100000) {
write (*, 10050) itours
} else if (itours < 1000000) {
write (*, 10060) itours
} else {
write (*, 10070) itours
}
call prntmv (board)
call prntbd (board)
write (*, 10000)
 
end
 
#-----------------------------------------------------------------------
 
subroutine prntbd (board)
implicit none
 
# Print a chessboard with the move number in each square.
 
integer board(1:8,1:8)
 
integer i, j
 
10000 format (1X, " ", 8("+----"), "+")
10010 format (1X, I2, " ", 8(" | ", I2), " | ")
10020 format (1X, " ", 8(" ", A1))
 
do i = 8, 1, -1 {
write (*, 10000)
write (*, 10010) i, (board(i, j), j = 1, 8)
}
write (*, 10000)
write (*, 10020) 'a', 'b', 'c', 'd', 'e', 'f', 'g', 'h'
 
end
 
#-----------------------------------------------------------------------
 
subroutine prntmv (board)
implicit none
 
# Print the moves of a knight's path, in algebraic notation.
 
integer board(1:8,1:8)
 
integer ipos(1:64)
integer jpos(1:64)
integer numpos
character*2 alg(1:64)
integer columns(1:8)
integer k
integer m
 
character*72 lines(1:8)
 
10000 format (1X, A)
 
call bd2pos (board, ipos, jpos, numpos)
 
# Convert the positions to algebraic notation.
do k = 1, numpos {
call ij2alg (ipos(k), jpos(k), alg(k))
}
 
# Fill lines with algebraic notations.
do m = 1, 8 {
columns(m) = 1
}
m = 1
do k = 1, numpos {
lines(m)(columns(m) : columns(m) + 1) = alg(k)(1:2)
columns(m) = columns(m) + 2
if (k != numpos) {
lines(m)(columns(m) : columns(m) + 3) = " -> "
columns(m) = columns(m) + 4
} else if (numpos == 64 && _
((abs (ipos(numpos) - ipos(1)) == 2 _
&& abs (jpos(numpos) - jpos(1)) == 1) _
|| ((abs (ipos(numpos) - ipos(1)) == 1 _
&& abs (jpos(numpos) - jpos(1)) == 2)))) {
lines(m)(columns(m) : columns(m) + 8) = " -> cycle"
columns(m) = columns(m) + 9
}
if (mod (k, 8) == 0) m = m + 1
}
 
# Print the lines that have stuff in them.
do m = 1, 8 {
if (columns(m) != 1) {
write (*, 10000) lines(m)(1 : columns(m) - 1)
}
}
 
end
 
#-----------------------------------------------------------------------
 
function isclos (board)
implicit none
 
# Is a board a closed tour?
 
logical isclos
integer board(1:8,1:8)
integer ipos(1:64) # The i-positions in order.
integer jpos(1:64) # The j-positions in order.
integer numpos # The number of positions so far.
 
call bd2pos (board, ipos, jpos, numpos)
 
isclos = (numpos == 64 && _
((abs (ipos(numpos) - ipos(1)) == 2 _
&& abs (jpos(numpos) - jpos(1)) == 1) _
|| ((abs (ipos(numpos) - ipos(1)) == 1 _
&& abs (jpos(numpos) - jpos(1)) == 2))))
 
end
 
#-----------------------------------------------------------------------
 
subroutine bd2pos (board, ipos, jpos, numpos)
implicit none
 
# Convert from a board to a list of board positions.
 
integer board(1:8,1:8)
integer ipos(1:64) # The i-positions in order.
integer jpos(1:64) # The j-positions in order.
integer numpos # The number of positions so far.
 
integer i, j
 
numpos = 0
do i = 1, 8 {
do j = 1, 8 {
if (board(i, j) != -1) {
numpos = max (board(i, j), numpos)
ipos(board(i, j)) = i
jpos(board(i, j)) = j
}
}
}
 
end
 
#-----------------------------------------------------------------------
 
subroutine nxtmov (board, n, imove, jmove, nmove)
implicit none
 
# Find possible next moves. Prune and sort the moves according to
# Warnsdorff's heuristic, keeping only those that have the minimum
# number of legal following moves.
 
integer board(1:8,1:8)
integer n
integer imove(1:8,1:64)
integer jmove(1:8,1:64)
integer nmove(1:64)
 
integer w1, w2, w3, w4, w5, w6, w7, w8
integer w
integer n1
integer pickw
 
call possib (board, n, imove, jmove, nmove)
 
n1 = n + 1
nmove(n1) = 1
call countf (board, n1, imove, jmove, nmove, w1)
nmove(n1) = 2
call countf (board, n1, imove, jmove, nmove, w2)
nmove(n1) = 3
call countf (board, n1, imove, jmove, nmove, w3)
nmove(n1) = 4
call countf (board, n1, imove, jmove, nmove, w4)
nmove(n1) = 5
call countf (board, n1, imove, jmove, nmove, w5)
nmove(n1) = 6
call countf (board, n1, imove, jmove, nmove, w6)
nmove(n1) = 7
call countf (board, n1, imove, jmove, nmove, w7)
nmove(n1) = 8
call countf (board, n1, imove, jmove, nmove, w8)
 
w = pickw (w1, w2, w3, w4, w5, w6, w7, w8)
 
if (w == 0) {
call disabl (imove(1, n1), jmove(1, n1))
call disabl (imove(2, n1), jmove(2, n1))
call disabl (imove(3, n1), jmove(3, n1))
call disabl (imove(4, n1), jmove(4, n1))
call disabl (imove(5, n1), jmove(5, n1))
call disabl (imove(6, n1), jmove(6, n1))
call disabl (imove(7, n1), jmove(7, n1))
call disabl (imove(8, n1), jmove(8, n1))
} else {
if (w != w1) call disabl (imove(1, n1), jmove(1, n1))
if (w != w2) call disabl (imove(2, n1), jmove(2, n1))
if (w != w3) call disabl (imove(3, n1), jmove(3, n1))
if (w != w4) call disabl (imove(4, n1), jmove(4, n1))
if (w != w5) call disabl (imove(5, n1), jmove(5, n1))
if (w != w6) call disabl (imove(6, n1), jmove(6, n1))
if (w != w7) call disabl (imove(7, n1), jmove(7, n1))
if (w != w8) call disabl (imove(8, n1), jmove(8, n1))
}
 
end
 
#-----------------------------------------------------------------------
 
subroutine countf (board, n, imove, jmove, nmove, w)
implicit none
 
# Count the number of moves possible after an nth move.
 
integer board(1:8,1:8)
integer n
integer imove(1:8,1:64)
integer jmove(1:8,1:64)
integer nmove(1:64)
integer w
 
logical goodmv
integer n1
 
if (goodmv (imove, nmove, n)) {
call mkmove (board, imove, jmove, nmove, n)
call possib (board, n, imove, jmove, nmove)
n1 = n + 1
w = 0
if (imove(1, n1) != -1) w = w + 1
if (imove(2, n1) != -1) w = w + 1
if (imove(3, n1) != -1) w = w + 1
if (imove(4, n1) != -1) w = w + 1
if (imove(5, n1) != -1) w = w + 1
if (imove(6, n1) != -1) w = w + 1
if (imove(7, n1) != -1) w = w + 1
if (imove(8, n1) != -1) w = w + 1
call unmove (board, imove, jmove, nmove, n)
} else {
# The nth move itself is impossible.
w = 0
}
 
end
 
#-----------------------------------------------------------------------
 
function pickw (w1, w2, w3, w4, w5, w6, w7, w8)
implicit none
 
# From w1..w8, pick out the least nonzero value (or zero if they all
# equal zero).
 
integer pickw
integer w1, w2, w3, w4, w5, w6, w7, w8
 
integer w
integer pickw1
 
w = 0
w = pickw1 (w, w1)
w = pickw1 (w, w2)
w = pickw1 (w, w3)
w = pickw1 (w, w4)
w = pickw1 (w, w5)
w = pickw1 (w, w6)
w = pickw1 (w, w7)
w = pickw1 (w, w8)
 
pickw = w
 
end
 
#-----------------------------------------------------------------------
 
function pickw1 (u, v)
implicit none
 
# A small function used by pickw.
 
integer pickw1
integer u, v
 
if (v == 0) {
pickw1 = u
} else if (u == 0) {
pickw1 = v
} else {
pickw1 = min (u, v)
}
 
end
 
#-----------------------------------------------------------------------
 
subroutine possib (board, n, imove, jmove, nmove)
implicit none
 
# Find moves that are possible from an nth-move position.
 
integer board(1:8,1:8)
integer n
integer imove(1:8,1:64)
integer jmove(1:8,1:64)
integer nmove(1:64)
 
integer i, j
integer n1
 
i = imove(nmove(n), n)
j = jmove(nmove(n), n)
n1 = n + 1
call trymov (board, i + 1, j + 2, imove(1, n1), jmove(1, n1))
call trymov (board, i + 2, j + 1, imove(2, n1), jmove(2, n1))
call trymov (board, i + 1, j - 2, imove(3, n1), jmove(3, n1))
call trymov (board, i + 2, j - 1, imove(4, n1), jmove(4, n1))
call trymov (board, i - 1, j + 2, imove(5, n1), jmove(5, n1))
call trymov (board, i - 2, j + 1, imove(6, n1), jmove(6, n1))
call trymov (board, i - 1, j - 2, imove(7, n1), jmove(7, n1))
call trymov (board, i - 2, j - 1, imove(8, n1), jmove(8, n1))
 
end
 
#-----------------------------------------------------------------------
 
subroutine trymov (board, i, j, imove, jmove)
implicit none
 
# Try a move to square (i, j).
 
integer board(1:8,1:8)
integer i, j
integer imove, jmove
 
call disabl (imove, jmove)
if (1 <= i && i <= 8 && 1 <= j && j <= 8) {
if (board(i,j) == -1) {
call enable (i, j, imove, jmove)
}
}
 
end
 
#-----------------------------------------------------------------------
 
subroutine enable (i, j, imove, jmove)
implicit none
 
# Enable a potential move.
 
integer i, j
integer imove, jmove
 
imove = i
jmove = j
 
end
 
#-----------------------------------------------------------------------
 
subroutine disabl (imove, jmove)
implicit none
 
# Disable a potential move.
 
integer imove, jmove
 
imove = -1
jmove = -1
 
end
 
#-----------------------------------------------------------------------
 
subroutine alg2ij (alg, i, j)
implicit none
 
# Convert, for instance, 'c5' to i=3,j=5.
 
character*2 alg
integer i, j
 
if (alg(1:1) == 'a') j = 1
if (alg(1:1) == 'b') j = 2
if (alg(1:1) == 'c') j = 3
if (alg(1:1) == 'd') j = 4
if (alg(1:1) == 'e') j = 5
if (alg(1:1) == 'f') j = 6
if (alg(1:1) == 'g') j = 7
if (alg(1:1) == 'h') j = 8
 
if (alg(2:2) == '1') i = 1
if (alg(2:2) == '2') i = 2
if (alg(2:2) == '3') i = 3
if (alg(2:2) == '4') i = 4
if (alg(2:2) == '5') i = 5
if (alg(2:2) == '6') i = 6
if (alg(2:2) == '7') i = 7
if (alg(2:2) == '8') i = 8
 
end
 
#-----------------------------------------------------------------------
 
subroutine ij2alg (i, j, alg)
implicit none
 
# Convert, for instance, i=3,j=5 to 'c5'.
 
integer i, j
character*2 alg
 
character alg1
character alg2
 
if (j == 1) alg1 = 'a'
if (j == 2) alg1 = 'b'
if (j == 3) alg1 = 'c'
if (j == 4) alg1 = 'd'
if (j == 5) alg1 = 'e'
if (j == 6) alg1 = 'f'
if (j == 7) alg1 = 'g'
if (j == 8) alg1 = 'h'
 
if (i == 1) alg2 = '1'
if (i == 2) alg2 = '2'
if (i == 3) alg2 = '3'
if (i == 4) alg2 = '4'
if (i == 5) alg2 = '5'
if (i == 6) alg2 = '6'
if (i == 7) alg2 = '7'
if (i == 8) alg2 = '8'
 
alg(1:1) = alg1
alg(2:2) = alg2
 
end
 
#-----------------------------------------------------------------------</syntaxhighlight>
 
{{out}}
$ echo "c5 2 T" | ./knights_tour
<pre> Tour number 1
c5 -> a6 -> b8 -> d7 -> f8 -> h7 -> g5 -> h3 ->
g1 -> e2 -> c1 -> a2 -> b4 -> d3 -> e1 -> g2 ->
h4 -> g6 -> h8 -> f7 -> d8 -> b7 -> a5 -> b3 ->
a1 -> c2 -> a3 -> b1 -> d2 -> f3 -> h2 -> f1 ->
g3 -> h1 -> f2 -> e4 -> c3 -> a4 -> b2 -> d1 ->
e3 -> g4 -> h6 -> g8 -> f6 -> h5 -> f4 -> d5 ->
e7 -> c8 -> a7 -> c6 -> e5 -> c4 -> b6 -> a8 ->
c7 -> e8 -> d6 -> b5 -> d4 -> f5 -> g7 -> e6 -> cycle
+----+----+----+----+----+----+----+----+
8 | 56 | 3 | 50 | 21 | 58 | 5 | 44 | 19 |
+----+----+----+----+----+----+----+----+
7 | 51 | 22 | 57 | 4 | 49 | 20 | 63 | 6 |
+----+----+----+----+----+----+----+----+
6 | 2 | 55 | 52 | 59 | 64 | 45 | 18 | 43 |
+----+----+----+----+----+----+----+----+
5 | 23 | 60 | 1 | 48 | 53 | 62 | 7 | 46 |
+----+----+----+----+----+----+----+----+
4 | 38 | 13 | 54 | 61 | 36 | 47 | 42 | 17 |
+----+----+----+----+----+----+----+----+
3 | 27 | 24 | 37 | 14 | 41 | 30 | 33 | 8 |
+----+----+----+----+----+----+----+----+
2 | 12 | 39 | 26 | 29 | 10 | 35 | 16 | 31 |
+----+----+----+----+----+----+----+----+
1 | 25 | 28 | 11 | 40 | 15 | 32 | 9 | 34 |
+----+----+----+----+----+----+----+----+
a b c d e f g h
 
Tour number 2
c5 -> a6 -> b8 -> d7 -> f8 -> h7 -> g5 -> h3 ->
g1 -> e2 -> c1 -> a2 -> b4 -> d3 -> e1 -> g2 ->
h4 -> g6 -> h8 -> f7 -> d8 -> b7 -> a5 -> b3 ->
a1 -> c2 -> a3 -> b1 -> d2 -> f3 -> h2 -> f1 ->
g3 -> h1 -> f2 -> e4 -> c3 -> a4 -> b2 -> d1 ->
e3 -> g4 -> h6 -> g8 -> f6 -> h5 -> f4 -> d5 ->
e7 -> c8 -> a7 -> c6 -> e5 -> c4 -> b6 -> a8 ->
c7 -> b5 -> d6 -> e8 -> g7 -> f5 -> d4 -> e6 -> cycle
+----+----+----+----+----+----+----+----+
8 | 56 | 3 | 50 | 21 | 60 | 5 | 44 | 19 |
+----+----+----+----+----+----+----+----+
7 | 51 | 22 | 57 | 4 | 49 | 20 | 61 | 6 |
+----+----+----+----+----+----+----+----+
6 | 2 | 55 | 52 | 59 | 64 | 45 | 18 | 43 |
+----+----+----+----+----+----+----+----+
5 | 23 | 58 | 1 | 48 | 53 | 62 | 7 | 46 |
+----+----+----+----+----+----+----+----+
4 | 38 | 13 | 54 | 63 | 36 | 47 | 42 | 17 |
+----+----+----+----+----+----+----+----+
3 | 27 | 24 | 37 | 14 | 41 | 30 | 33 | 8 |
+----+----+----+----+----+----+----+----+
2 | 12 | 39 | 26 | 29 | 10 | 35 | 16 | 31 |
+----+----+----+----+----+----+----+----+
1 | 25 | 28 | 11 | 40 | 15 | 32 | 9 | 34 |
+----+----+----+----+----+----+----+----+
a b c d e f g h
</pre>
 
 
 
 
=={{header|REXX}}==
This REXX version is modeled after the XPL0 example.
 
<lang rexx>/*REXX pgm to solve the knight's tour problem for a NxN chessboard. */
The size of the chessboard may be specified as well as the knight's starting position.
parse arg N .; if N=='' | N==',' then N=8 /*user can specify board size.*/
 
NoNo= "No knight's tour solution for" NxN'.'; @.=
This is an &nbsp; ''open tour'' &nbsp; solution. &nbsp; (See this task's &nbsp; ''discussion'' &nbsp; page for an explanation, the section is &nbsp; ''The 7x7 problem''.)
/*define the outside of the board*/
<syntaxhighlight lang="rexx">/*REXX program solves the knight's tour problem for a (general) NxN chessboard.*/
NN=N**2; NxN='a ' N"x"N ' chessboard' /* [↓] R=rank, F=file. */
parse arg do r=1N forsRank N;sFile . do f=1 for N; @.r.f=0; end /*f*/; end /*robtain optional arguments from the CL*/
if N=='' | N=="," then N=8 /*[↑]No zeroboardsize outspecified? the NxNUse chessboarddefault.*/
Krif sRank= =''2 1| -1sRank=="," -2 -2then -1sRank=N 1 2' /*No starting rank given? /*legal "rank" move for a knight. " */
Kfif sFile== '1' 2| sFile=="," 2 then sFile=1 -1 -2 -2 -1' /* " /* " " file" " " " " */
NN=N**2; NxN='a ' N"x"N ' chessboard' /*file [↓] [↓] do ir=1rank for 8 /*legal knight moves*/
@.=; do r=1 for N; do f=1 for N; Kr@.i r.f= word(Kr,i).; end /*f*/; Kf.i =end word(Kf,i)/*r*/
beg= '-1-' end /*i*/ /*[↑] create an empty /*for fastNxN indexingchessboard.*/
@.1.1 = 1 Kr = '2 1 -1 -2 -2 -1 1 2' /*the knight'slegal starting"rank" position moves for a knight.*/
Kf = '1 2 2 1 -1 -2 -2 -1' /* " " "file" " " " " */
if \(N==1) & \move(2,1,1) then do; say NoNo; exit; end
kr.M=words(Kr) /*number of possible moves for a Knight*/
say "A solution for the knight's tour on" NxN':';!=left('',9*(n<18))
parse var Kr Kr.1 Kr.2 Kr.3 Kr.4 Kr.5 Kr.6 Kr.7 Kr.8 /*parse the legal moves by hand*/
_=substr(copies("┼───",N),2); say; say ! translate('┌'_"┐", '┬', "┼")
parse var Kf doKf.1 Kf.2 Kf.3 r=NKf.4 Kf.5 forKf.6 NKf.7 Kf.8 by -1; /* " " if" r\==N then say !" '├'_"┤"; L=@. " */
@.sRank.sFile= beg /*the knight's starting position. */
do f=1 for N; L=L'│'centre(@.r.f,3) /*preserve squareness.*/
@kt= "knight's tour" /*a handy-dandy literal for the SAYs. */
end /*f*/
if \move(2, sRank, sFile) say& ! L'│'\(N==1) then say 'No' @kt "solution for" /*show a rank of the chessboardNxN'. */'
end /*r*/ /*80 cols can view 19x19 chessbrd*/ else say 'A solution for the' @kt "on" NxN':'
say ! translate=left(''_"┘", '┴',9 "┼"* (n<18) ) /*showused thefor last rankindentation of thechessboard. board*/
_=substr(copies("┼───",N),2); say; say ! translate('┌'_"┐", '┬', "┼") /*a square.*/
exit /*stick a fork in it, we're done.*/
/* [↓] build a display for chessboard.*/
/*──────────────────────────────────MOVE subroutine─────────────────────*/
do r=N for N by -1; if r\==N then say ! '├'_"┤"; L=@.
move: procedure expose @. Kr. Kf. N NN; parse arg #,rank,file
do tf=1 for 8N; ?=@.r.f; if ?==NN then nr?=rank+Kr.t'end'; L=L'│'center(?, 3) /*is nf=file+Kf.t"end"?*/
end /*f*/ if @.nr.nf==0 then do; @.nr.nf=# /*Kndone movewith rank of the chessboard.*/
say ! translate(L'│', , .) /*display a if #==NN " " " then return 1 /*last 1? " */
end /*r*/ if move(#+1,nr,nf) then return 1 /*19x19 chessboard can be shown 80 cols*/
 
@.nr.nf=0 /*undo the above move. */
say ! translate('└'_"┘", '┴', "┼") /*show the last rank of the endchessboard.*/
exit /*stick a fork in it, we're all done. */
end /*t*/
/*──────────────────────────────────────────────────────────────────────────────────────*/
return 0</lang>
move: procedure expose @. Kr. Kf. NN; parse arg #,rank,file /*obtain move,rank,file.*/
'''output'''
do t=1 for Kr.M; nr=rank+Kr.t; nf=file+Kf.t /*position of the knight*/
<pre style="overflow:scroll">
if @.nr.nf==. then do; @.nr.nf=# /*Empty? Knight can move*/
if #==NN then return 1 /*is this the last move?*/
if move(#+1,nr,nf) then return 1 /* " " " " " */
@.nr.nf=. /*undo the above move. */
end /*try different move. */
end /*t*/ /* [↑] all moves tried.*/
return 0 /*tour is not possible. */</syntaxhighlight>
'''output''' &nbsp; when using the default input:
<pre>
A solution for the knight's tour on a 8x8 chessboard:
 
┌───┬───┬───┬───┬───┬───┬───┬───┐
│52│-1-│38 │47│55 │56│34 │45 │543 │36 5│19 │22 │13
├───┼───┼───┼───┼───┼───┼───┼───┤
│57│54 │44 │53│4742 │23│37 │14│20 │25│2364 │17
├───┼───┼───┼───┼───┼───┼───┼───┤
│48│39 │51│56 │33 │46 │55│35 │26│18 │21 │12 │15│10
├───┼───┼───┼───┼───┼───┼───┼───┤
│43│48 │58│53 │40 3│57 │50│24 │41│11 │24│167 │205
├───┼───┼───┼───┼───┼───┼───┼───┤
│36│59 │49│32 │42│45 │27│52 │62│41 │11│26 │16 │299 │12
├───┼───┼───┼───┼───┼───┼───┼───┤
│59│44 │49 2│58 │37│25 │40│62 │33│15 │28 │19 │6 8│27
├───┼───┼───┼───┼───┼───┼───┼───┤
│38│31 │35│60 │32│51 │61│42 │10│29 │63 │308 │17│13 │end│
├───┼───┼───┼───┼───┼───┼───┼───┤
│50 1│43 │60│30 │39│61 │34│14 │31│63 │18│289 │647
└───┴───┴───┴───┴───┴───┴───┴───┘
</pre>
 
=={{header|Ruby}}==
Knights tour using [[wp:Knight's_tour#Warnsdorff.27s_rule|Warnsdorffs rule]]
<lang ruby>
<syntaxhighlight lang="ruby">class Board
# Solve a Knight's Tour
Cell = Struct.new(:value, :adj) do
#
def self.end=(end_val)
# Nigel_Galloway
@@end = end_val
# May 6th., 2012.
end
 
class Cell
def try(seq_num)
Adjust = [[-1,-2],[-2,-1],[-2,1],[-1,2],[1,2],[2,1],[2,-1],[1,-2]]
def initialize(row=0, col=0, self.value =nil) seq_num
return true if seq_num==@@end
@adj = Adjust.map{|r,c| [row+r,col+c]}
@t a = false[]
adj.each_with_index do |cell, n|
$zbl[value] = false unless value.nil?
a << [wdof(cell.adj)*10+n, cell] if cell.value.zero?
@value = value
end
a.sort.each {|_, cell| return true if cell.try(seq_num+1)}
self.value = 0
false
end
def wdof(adj)
adj.count {|cell| cell.value.zero?}
end
end
def try(value=1)
def initialize(rows, cols)
return true if value > $e
return@rows, false@cols if= @trows, cols
unless defined? ADJACENT # default move (Knight)
return false if @value > 0 and @value != value
eval("ADJACENT = [[-1,-2],[-2,-1],[-2,1],[-1,2],[1,2],[2,1],[2,-1],[1,-2]]")
return false if @value == 0 and not $zbl[value]
@t = trueend
frame = ADJACENT.flatten.map(&:abs).max
h = Hash.new
@board = Array.new(rows+frame) do |i|
@adj.each_with_index{|(row, col), n|
Array.new(cols+frame) do |j|
cell = $board[row][col]
(i<rows and j<cols) ? Cell.new(0) : nil # frame (Sentinel value : nil)
h[cell.wdof*100+n] = cell if cell.value
}
h.sort.each{|key,cell|
if cell.try(value+1)
@value = value
return true
end
}end
@trows.times =do false|i|
cols.times do |j|
@board[i][j].adj = ADJACENT.map{|di,dj| @board[i+di][j+dj]}.compact
end
end
Cell.end = rows * cols
@format = " %#{(rows * cols).to_s.size}d"
end
def wdon
def solve(sx, sy)
(@value.nil? or @value > 0 or @t) ? 0 : 1
if (@rows*@cols).odd? and (sx+sy).odd?
puts "No solution"
else
puts (@board[sx][sy].try(1) ? to_s : "No solution")
end
end
def wdof
def to_s
@adj.inject(0){|res, (row, col)| res += $board[row][col].wdon}
(0...@rows).map do |x|
(0...@cols).map{|y| @format % @board[x][y].value}.join
end
end
attr_reader :value
end
 
def knight_tour(rows=8, cols=rows, xsx=rand(rows), ysy=rand(cols))
puts "\nBoard (%d x %d), Start:[%d, %d]" % [rows, cols, sx, sy]
$e = rows * cols
$zbl = ArrayBoard.new($e+1rows,true cols).solve(sx, sy)
$board = Array.new(rows+2) do |i|
Array.new(cols+2) do |j|
(i<rows and j<cols) ? Cell.new(i,j,0) : Cell.new
end
end
$board[x][y].try
rows.times{|r| cols.times{|c| printf("%3s",$board[r][c].value)}; puts}
end
 
knight_tour(8,8,3,1)
 
</lang>
knight_tour(5,5,2,2)
 
knight_tour(4,9,0,0)
 
knight_tour(5,5,0,1)
 
knight_tour(12,12,1,1)</syntaxhighlight>
Which produces:
<pre>
Board (8 x 8), Start:[3, 1]
23 20 3 32 25 10 5 8
2 35 24 21 4 7 26 11
Line 3,198 ⟶ 10,938:
17 52 41 60 15 64 39 46
42 55 16 57 40 59 14 63
 
Board (5 x 5), Start:[2, 2]
19 8 3 14 25
2 13 18 9 4
7 20 1 24 15
12 17 22 5 10
21 6 11 16 23
 
Board (4 x 9), Start:[0, 0]
1 34 3 28 13 24 9 20 17
4 29 6 33 8 27 18 23 10
35 2 31 14 25 12 21 16 19
30 5 36 7 32 15 26 11 22
 
Board (5 x 5), Start:[0, 1]
No solution
 
Board (12 x 12), Start:[1, 1]
87 24 59 2 89 26 61 4 39 8 31 6
58 1 88 25 60 3 92 27 30 5 38 9
23 86 83 90 103 98 29 62 93 40 7 32
82 57 102 99 84 91 104 97 28 37 10 41
101 22 85 114 105 116 111 94 63 96 33 36
56 81 100 123 128 113 106 117 110 35 42 11
21 122 141 80 115 124 127 112 95 64 109 34
144 55 78 121 142 129 118 107 126 133 12 43
51 20 143 140 79 120 125 138 69 108 65 134
54 73 52 77 130 139 70 119 132 137 44 13
19 50 75 72 17 48 131 68 15 46 135 66
74 53 18 49 76 71 16 47 136 67 14 45
</pre>
cf. [[Solve a Holy Knight's tour#Ruby|Solve a Holy Knight's tour]]:
 
=={{header|Rust}}==
<syntaxhighlight lang="rust">use std::fmt;
 
const SIZE: usize = 8;
const MOVES: [(i32, i32); 8] = [
(2, 1),
(1, 2),
(-1, 2),
(-2, 1),
(-2, -1),
(-1, -2),
(1, -2),
(2, -1),
];
 
#[derive(Copy, Clone, Eq, PartialEq, PartialOrd, Ord)]
struct Point {
x: i32,
y: i32,
}
 
impl Point {
fn mov(&self, &(dx, dy): &(i32, i32)) -> Self {
Self {
x: self.x + dx,
y: self.y + dy,
}
}
}
 
struct Board {
field: [[i32; SIZE]; SIZE],
}
 
impl Board {
fn new() -> Self {
Self {
field: [[0; SIZE]; SIZE],
}
}
 
fn available(&self, p: Point) -> bool {
0 <= p.x
&& p.x < SIZE as i32
&& 0 <= p.y
&& p.y < SIZE as i32
&& self.field[p.x as usize][p.y as usize] == 0
}
 
// calculate the number of possible moves
fn count_degree(&self, p: Point) -> i32 {
let mut count = 0;
for dir in MOVES.iter() {
let next = p.mov(dir);
if self.available(next) {
count += 1;
}
}
count
}
}
 
impl fmt::Display for Board {
fn fmt(&self, f: &mut fmt::Formatter) -> fmt::Result {
for row in self.field.iter() {
for x in row.iter() {
write!(f, "{:3} ", x)?;
}
write!(f, "\n")?;
}
Ok(())
}
}
 
fn knights_tour(x: i32, y: i32) -> Option<Board> {
let mut board = Board::new();
let mut p = Point { x: x, y: y };
let mut step = 1;
board.field[p.x as usize][p.y as usize] = step;
step += 1;
 
while step <= (SIZE * SIZE) as i32 {
// choose next square by Warnsdorf's rule
let mut candidates = vec![];
for dir in MOVES.iter() {
let adj = p.mov(dir);
if board.available(adj) {
let degree = board.count_degree(adj);
candidates.push((degree, adj));
}
}
match candidates.iter().min() {
// move to next square
Some(&(_, adj)) => p = adj,
// can't move
None => return None,
};
board.field[p.x as usize][p.y as usize] = step;
step += 1;
}
Some(board)
}
 
fn main() {
let (x, y) = (3, 1);
println!("Board size: {}", SIZE);
println!("Starting position: ({}, {})", x, y);
match knights_tour(x, y) {
Some(b) => print!("{}", b),
None => println!("Fail!"),
}
}</syntaxhighlight>
{{out}}
<pre>
Board size: 8
Starting position: (3, 1)
23 20 3 32 25 10 5 8
2 33 24 21 4 7 26 11
19 22 51 34 31 28 9 6
50 1 40 29 54 35 12 27
41 18 55 52 61 30 57 36
46 49 44 39 56 53 62 13
17 42 47 60 15 64 37 58
48 45 16 43 38 59 14 63
</pre>
 
=={{header|Scala}}==
<syntaxhighlight lang="scala">
val b=Seq.tabulate(8,8,8,8)((x,y,z,t)=>(1L<<(x*8+y),1L<<(z*8+t),f"${97+z}%c${49+t}%c",(x-z)*(x-z)+(y-t)*(y-t)==5)).flatten.flatten.flatten.filter(_._4).groupBy(_._1)
def f(p:Long,s:Long,v:Any){if(-1L!=s)b(p).foreach(x=>if((s&x._2)==0)f(x._2,s|x._2,v+x._3))else println(v)}
f(1,1,"a1")
</syntaxhighlight>
<pre>
a1b3a5b7c5a4b2c4a3b1c3a2b4a6b8c6a7b5c7a8b6c8d6e4d2f1e3c2d4e2c1d3e1g2f4d5e7g8h6f5h4g6h8f7d8e6f8d7e5g4h2f3g1h3g5h7f6e8g7h5g3h1f2d1
</pre>
 
=={{header|Scheme}}==
<syntaxhighlight lang="scheme">
;;/usr/bin/petite
;;encoding:utf-8
;;Author:Panda
;;Mail:panbaoxiang@hotmail.com
;;Created Time:Thu 29 Jan 2015 10:18:49 AM CST
;;Description:
 
;;size of the chessboard
(define X 8)
(define Y 8)
;;position is an integer that could be decoded into the x coordinate and y coordinate
(define(decode position)
(cons (div position Y) (remainder position Y)))
;;record the paths and number of territories you have conquered
(define dictionary '())
(define counter 1)
;;define the forbiddend territories(conquered and cul-de-sac)
(define forbiddened '())
;;renew when havn't conquered the world.
(define (renew position)
(define possible
(let ((rules (list (+ (* 2 Y) 1 position)
(+ (* 2 Y) -1 position)
(+ (* -2 Y) 1 position)
(+ (* -2 Y) -1 position)
(+ Y 2 position)
(+ Y -2 position)
(- position Y 2)
(- position Y -2))))
(filter (lambda(x) (not (or (member x forbiddened) (< x 0) (>= x (* X Y))))) rules)))
(if (null? possible)
(begin (set! forbiddened (cons (car dictionary) forbiddened))
(set! dictionary (cdr dictionary))
(set! counter (- counter 1))
(car dictionary))
(begin (set! dictionary (cons (car possible) dictionary))
(set! forbiddened dictionary)
(set! counter (+ counter 1))
(car possible))))
;;go to search
(define (go position)
(if (= counter (* X Y))
(begin
(set! result (reverse dictionary))
(display (map (lambda(x) (decode x)) result)))
(go (renew position))))
</syntaxhighlight>
{{out}}
<pre>
(go 35)
((6 . 4) (4 . 5) (6 . 6) (4 . 7) (7 . 0) (5 . 1) (7 . 2) (5 . 3) (7 . 4) (5 . 5) (7 . 6) (5 . 7) (4 . 0) (6 . 1) (4 . 2) (6 . 3) (4 . 4) (6 . 5) (4 . 6) (6 . 7) (5 . 0) (7 . 1) (5 . 2) (7 . 3) (5 . 4) (7 . 5) (5 . 6) (7 . 7) (6 . 0) (4 . 1) (6 . 2) (4 . 3) (2 . 4) (0 . 5) (2 . 6) (0 . 7) (3 . 0) (1 . 1) (3 . 2) (1 . 3) (3 . 4) (1 . 5) (3 . 6) (1 . 7) (0 . 0) (2 . 1) (0 . 2) (2 . 3) (0 . 4) (2 . 5) (0 . 6) (2 . 7) (1 . 0) (3 . 1) (1 . 2) (3 . 3) (1 . 4) (3 . 5) (1 . 6) (3 . 7) (2 . 0) (0 . 1) (2 . 2))
</pre>
 
=={{header|SequenceL}}==
Knights tour using [[wp:Knight's_tour#Warnsdorff.27s_rule|Warnsdorffs rule]] (No Backtracking)
<syntaxhighlight lang="sequencel">
import <Utilities/Sequence.sl>;
import <Utilities/Conversion.sl>;
 
main(args(2)) :=
let
N := stringToInt(args[1]) when size(args) > 0 else 8;
M := stringToInt(args[2]) when size(args) > 1 else N;
startX := stringToInt(args[3]) when size(args) > 2 else 1;
startY := stringToInt(args[4]) when size(args) > 3 else 1;
board[i,j] := 0 foreach i within 1 ... N, j within 1 ... M;
spacing := size(toString(N*M)) + 1;
in
join(printRow(
tour(setBoard(board, startX, startX, 1), [startX,startY], 2),
spacing));
 
potentialMoves := [[2,1], [2,-1], [1,2], [1,-2], [-1,2], [-1,-2], [-2,1], [-2,-1]];
 
printRow(row(1), spacing) := join(printSquare(row, spacing)) ++ "\n";
 
printSquare(val, spacing) :=
let
str := toString(val);
in
duplicate(' ', spacing - size(str)) ++ str;
 
tour(board(2), current(1), move) :=
let
validMoves := validMove(board, current + potentialMoves);
numMoves[i] := size(validMove(board, validMoves[i] + potentialMoves));
chosenMove := minPosition(numMoves);
in
board when move > size(board) * size(board[1]) else
[] when size(validMoves) = 0 else
[] when move < size(board) * size(board[1]) and numMoves[chosenMove] = 0 else
tour(setBoard(board, validMoves[chosenMove][1], validMoves[chosenMove][2], move), validMoves[chosenMove], move + 1);
 
validMove(board(2), position(1)) :=
(position when board[position[1], position[2]] = 0)
when position[1] >= 1 and position[1] <= size(board) and position[2] >= 1 and position[2] <= size(board);
minPosition(x(1)) := minPositionHelper(x, 2, 1, x[1]);
minPositionHelper(x(1), i, minPos, minVal) :=
minPos when i > size(x) else
minPositionHelper(x, i + 1, minPos, minVal) when x[i] > minVal else
minPositionHelper(x, i + 1, i, x[i]);
 
setBoard(board(2), x, y, value)[i,j] :=
value when x = i and y = j else
board[i,j] foreach i within 1 ... size(board), j within 1 ... size(board[1]);
</syntaxhighlight>
{{out}}
8 X 8 board:
<pre>
1 16 31 40 3 18 21 56
30 39 2 17 42 55 4 19
15 32 41 46 53 20 57 22
38 29 48 43 58 45 54 5
33 14 37 52 47 60 23 62
28 49 34 59 44 63 6 9
13 36 51 26 11 8 61 24
50 27 12 35 64 25 10 7
</pre>
20 X 20 board:
<pre>
1 40 81 90 3 42 77 94 5 44 73 102 7 46 69 62 9 48 51 60
82 89 2 41 92 95 4 43 76 101 6 45 72 103 8 47 68 61 10 49
39 80 91 96 153 78 93 100 129 74 109 104 123 70 111 120 63 50 59 52
88 83 154 79 98 159 152 75 108 105 128 71 110 121 124 67 112 119 64 11
155 38 97 160 157 200 99 162 151 130 107 122 127 132 141 118 125 66 53 58
84 87 156 199 176 161 158 201 106 163 150 131 142 145 126 133 140 113 12 65
37 182 85 178 207 198 175 164 173 216 143 166 149 222 139 146 117 134 57 54
86 179 206 197 204 177 208 217 202 165 172 221 144 167 148 223 138 55 114 13
183 36 181 212 209 218 203 174 215 220 227 170 281 224 303 168 147 116 135 56
180 211 196 205 230 213 238 219 228 171 280 225 302 169 282 343 304 137 14 115
35 184 231 210 237 246 229 214 279 226 301 298 283 342 367 308 347 344 305 136
232 195 236 245 234 239 278 247 300 297 284 359 366 309 348 345 368 307 350 15
185 34 233 240 261 248 287 296 285 358 299 310 341 378 365 384 349 346 369 306
194 241 250 235 244 277 260 313 294 311 360 373 364 383 354 379 370 385 16 351
33 186 243 262 249 288 295 286 361 316 357 340 377 372 395 386 353 380 333 388
242 193 254 251 276 259 314 293 312 321 374 363 398 355 382 371 394 387 352 17
187 32 263 258 267 252 289 322 315 362 317 356 339 376 399 396 381 334 389 332
192 255 190 253 264 275 268 271 292 323 320 375 326 397 338 335 390 393 18 21
31 188 257 266 29 270 273 290 27 318 327 324 25 336 329 400 23 20 331 392
256 191 30 189 274 265 28 269 272 291 26 319 328 325 24 337 330 391 22 19
</pre>
 
=={{header|Sidef}}==
{{trans|Raku}}
<syntaxhighlight lang="ruby">var board = []
var I = 8
var J = 8
var F = (I*J > 99 ? '%3d' : '%2d')
 
var (i, j) = (I.irand, J.irand)
 
func from_algebraic(square) {
if (var match = square.match(/^([a-z])([0-9])\z/)) {
return(I - Num(match[1]), match[0].ord - 'a'.ord)
}
die "Invalid block square: #{square}"
}
 
func possible_moves(i,j) {
gather {
for ni,nj in [
[i-2,j-1], [i-2,j+1], [i-1,j-2], [i-1,j+2],
[i+1,j-2], [i+1,j+2], [i+2,j-1], [i+2,j+1],
] {
if ((ni ~~ ^I) && (nj ~~ ^J) && !board[ni][nj]) {
take([ni, nj])
}
}
}
}
 
func to_algebraic(i,j) {
('a'.ord + j).chr + Str(I - i)
}
 
if (ARGV[0]) {
(i, j) = from_algebraic(ARGV[0])
}
 
var moves = []
for move in (1 .. I*J) {
moves << to_algebraic(i, j)
board[i][j] = move
var min = [9]
for target in possible_moves(i, j) {
var (ni, nj) = target...
var nxt = possible_moves(ni, nj).len
if (nxt < min[0]) {
min = [nxt, ni, nj]
}
}
 
(i, j) = min[1,2]
}
 
say (moves/4 -> map { .join(', ') }.join("\n") + "\n")
 
for i in ^I {
for j in ^J {
(i%2 == j%2) && print "\e[7m"
F.printf(board[i][j])
print "\e[0m"
}
print "\n"
}</syntaxhighlight>
 
=={{header|Swift}}==
 
{{trans|Rust}}
 
<syntaxhighlight lang="swift">public struct CPoint {
public var x: Int
public var y: Int
 
public init(x: Int, y: Int) {
(self.x, self.y) = (x, y)
}
 
public func move(by: (dx: Int, dy: Int)) -> CPoint {
return CPoint(x: self.x + by.dx, y: self.y + by.dy)
}
}
 
extension CPoint: Comparable {
public static func <(lhs: CPoint, rhs: CPoint) -> Bool {
if lhs.x == rhs.x {
return lhs.y < rhs.y
} else {
return lhs.x < rhs.x
}
}
}
 
public class KnightsTour {
public var size: Int { board.count }
 
private var board: [[Int]]
 
public init(size: Int) {
board = Array(repeating: Array(repeating: 0, count: size), count: size)
}
 
public func countMoves(forPoint point: CPoint) -> Int {
return KnightsTour.knightMoves.lazy
.map(point.move)
.reduce(0, {count, movedTo in
return squareAvailable(movedTo) ? count + 1 : count
})
}
 
public func printBoard() {
for row in board {
for x in row {
print("\(x) ", terminator: "")
}
 
print()
}
 
print()
}
 
private func reset() {
for i in 0..<size {
for j in 0..<size {
board[i][j] = 0
}
}
}
 
public func squareAvailable(_ p: CPoint) -> Bool {
return 0 <= p.x
&& p.x < size
&& 0 <= p.y
&& p.y < size
&& board[p.x][p.y] == 0
}
 
public func tour(startingAt point: CPoint = CPoint(x: 0, y: 0)) -> Bool {
var step = 2
var p = point
 
reset()
 
board[p.x][p.y] = 1
 
while step <= size * size {
let candidates = KnightsTour.knightMoves.lazy
.map(p.move)
.map({moved in (moved, self.countMoves(forPoint: moved), self.squareAvailable(moved)) })
.filter({ $0.2 })
 
guard let bestMove = candidates.sorted(by: bestChoice).first else {
return false
}
 
p = bestMove.0
board[p.x][p.y] = step
 
step += 1
}
 
return true
}
}
 
private func bestChoice(_ choice1: (CPoint, Int, Bool), _ choice2: (CPoint, Int, Bool)) -> Bool {
if choice1.1 == choice2.1 {
return choice1.0 < choice2.0
}
 
return choice1.1 < choice2.1
}
 
extension KnightsTour {
fileprivate static let knightMoves = [
(2, 1),
(1, 2),
(-1, 2),
(-2, 1),
(-2, -1),
(-1, -2),
(1, -2),
(2, -1),
]
}
 
let b = KnightsTour(size: 8)
 
print()
 
let completed = b.tour(startingAt: CPoint(x: 3, y: 1))
 
if completed {
print("Completed tour")
} else {
print("Did not complete tour")
}
 
b.printBoard()</syntaxhighlight>
 
{{out}}
 
<pre>Completed tour
23 20 3 32 25 10 5 8
2 33 24 21 4 7 26 11
19 22 51 34 31 28 9 6
50 1 40 29 54 35 12 27
41 18 55 52 61 30 57 36
46 49 44 39 56 53 62 13
17 42 47 60 15 64 37 58
48 45 16 43 38 59 14 63</pre>
 
=={{header|Tcl}}==
<langsyntaxhighlight lang="tcl">package require Tcl 8.6; # For object support, which makes coding simpler
 
oo::class create KnightsTour {
Line 3,307 ⟶ 11,570:
expr {$a in [my ValidMoves $b]}
}
}</langsyntaxhighlight>
Demonstrating:
<langsyntaxhighlight lang="tcl">set kt [KnightsTour new]
$kt constructRandom
$kt print
Line 3,316 ⟶ 11,579:
} else {
puts "This is an open tour"
}</langsyntaxhighlight>
Sample output:
<pre>
Line 3,328 ⟶ 11,591:
</pre>
The above code supports other sizes of boards and starting from nominated locations:
<langsyntaxhighlight lang="tcl">set kt [KnightsTour new 7 7]
$kt constructFrom {0 0}
$kt print
Line 3,335 ⟶ 11,598:
} else {
puts "This is an open tour"
}</langsyntaxhighlight>
Which could produce this output:
<pre>
Line 3,344 ⟶ 11,607:
-> c3
This is an open tour
</pre>
 
=={{header|Wren}}==
{{trans|Kotlin}}
<syntaxhighlight lang="wren">class Square {
construct new(x, y) {
_x = x
_y = y
}
 
x { _x }
y { _y }
 
==(other) { _x == other.x && _y == other.y }
}
 
var board = List.filled(8 * 8, null)
for (i in 0...board.count) board[i] = Square.new((i/8).floor + 1, i%8 + 1)
var axisMoves = [1, 2, -1, -2]
 
var allPairs = Fn.new { |a|
var pairs = []
for (i in a) {
for (j in a) pairs.add([i, j])
}
return pairs
}
 
var knightMoves = Fn.new { |s|
var moves = allPairs.call(axisMoves).where { |p| p[0].abs != p[1].abs }
var onBoard = Fn.new { |s| board.any { |i| i == s } }
return moves.map { |p| Square.new(s.x + p[0], s.y + p[1]) }.where(onBoard)
}
 
var knightTour // recursive
knightTour = Fn.new { |moves|
var findMoves = Fn.new { |s|
return knightMoves.call(s).where { |m| !moves.any { |m2| m2 == m } }.toList
}
var fm = findMoves.call(moves[-1])
if (fm.isEmpty) return moves
var lowest = findMoves.call(fm[0]).count
var lowestIndex = 0
for (i in 1...fm.count) {
var count = findMoves.call(fm[i]).count
if (count < lowest) {
lowest = count
lowestIndex = i
}
}
var newSquare = fm[lowestIndex]
return knightTour.call(moves + [newSquare])
}
 
var knightTourFrom = Fn.new { |start| knightTour.call([start]) }
 
var col = 0
for (p in knightTourFrom.call(Square.new(1, 1))) {
System.write("%(p.x),%(p.y)")
System.write((col == 7) ? "\n" : " ")
col = (col + 1) % 8
}</syntaxhighlight>
 
{{out}}
<pre>
1,1 2,3 3,1 1,2 2,4 1,6 2,8 4,7
6,8 8,7 7,5 8,3 7,1 5,2 7,3 8,1
6,2 4,1 2,2 1,4 2,6 1,8 3,7 5,8
7,7 8,5 6,6 7,8 8,6 7,4 8,2 6,1
4,2 2,1 3,3 5,4 3,5 4,3 5,1 6,3
8,4 7,2 6,4 5,6 4,8 2,7 1,5 3,6
1,7 3,8 5,7 4,5 5,3 6,5 4,4 3,2
1,3 2,5 4,6 3,4 5,5 6,7 8,8 7,6
</pre>
 
=={{header|XPL0}}==
<langsyntaxhighlight XPL0lang="xpl0">int Board(8+2+2, 8+2+2); \board array with borders
int LegalX, LegalY; \arrays of legal moves
def IntSize=4; \number of bytes in an integer (4 or 2)
Line 3,397 ⟶ 11,733:
]
else Text(0, "No Solution.^M^J");
]</langsyntaxhighlight>
 
Example output:
Line 3,412 ⟶ 11,748:
</pre>
 
=={{header|XSLT 3.0}}==
This solution is for XSLT 3.0 Working Draft 10 (July 2012). This solution, originally reported on [http://seanbdurkin.id.au/pascaliburnus2/archives/10 this blog post], will be updated or removed when the final version of XSLT 3.0 is released.
 
First we build a generic package for solving any kind of tour over the chess board. Here it is…
<syntaxhighlight lang="text">
<xsl:package xsl:version="3.0"
xmlns:xsl="http://www.w3.org/1999/XSL/Transform"
Line 3,473 ⟶ 11,809:
</xsl:package>
</syntaxhighlight>
</lang>
 
And now for the style-sheet to solve the Knight’s tour…
 
<syntaxhighlight lang="text">
<xsl:stylesheet version="3.0"
xmlns:xsl="http://www.w3.org/1999/XSL/Transform"
Line 3,516 ⟶ 11,852:
</xsl:stylesheet>
</syntaxhighlight>
</lang>
 
So an input like this…
 
<syntaxhighlight lang="text">
<tt>
<knight>
Line 3,526 ⟶ 11,862:
</knight>
</tt>
</syntaxhighlight>
</lang>
 
…should be transformed in something like this…
 
<syntaxhighlight lang="text">
<tt>
<knight>
Line 3,539 ⟶ 11,875:
</knight>
</tt>
</syntaxhighlight>
</lang>
 
=={{header|zkl}}==
<langsyntaxhighlight lang="zkl"> // Use Warnsdorff's rule to perform a knights tour of a 8x8 board in
// linear time.
// See Pohl, Ira (July 1967),
Line 3,555 ⟶ 11,891:
(0).pump(64,board.append.fpM("1-",Void)); // fill board with Void
}
fcn idx(x,y) { x*8+y }
fcn isMoveOK(x,y){ (0<=x<8) and (0<=y<8) and Void == board[idx(x,y)] }
fcn gyrate(x,y,f){ // walk all legal moves from (a,b)
deltas.pump(List,'wrap([(dx,dy)]){
x+=dx; y+=dy; if(isMoveOK(x,y)) f(x,y); else Void.Skip});
});
}
fcn count(x,y){ n:=Ref(0); gyrate(x,y,n.inc); n.value }
Line 3,566 ⟶ 11,903:
board[idx(x,y)]=n;
while(m:=moves(x,y)){
min:=m.reduce('wrap(pc,[(_,_,c)]){ (pc<c) and pc or c },9);
m=m.filter('wrap([(_,_,c)]){ c==min }); // moves with same min moves
if(m.len()>1){ // tie breaker time, may need to backtrack
bs:=board.copy();
if (64 == m.pump(Void,'wrap([(a,b)]){
board[idx(a,b)]=n;
n2:=knightsTour(a,b,n+1);
Line 3,585 ⟶ 11,922:
return(n);
}
fcn toString{ board.pump(String,T.fp(Void.Read,7),
fcn(ns){ vm.arglist.apply("%2s".fmt).concat(",")+"\n" });
}
}</langsyntaxhighlight>
 
<langsyntaxhighlight lang="zkl">b:=Board(); b.knightsTour(3,3);
b.println();</langsyntaxhighlight>
{{out}}
<pre>
Line 3,604 ⟶ 11,941:
</pre>
Check that a solution for all squares is found:
<langsyntaxhighlight lang="zkl">[[(x,y); [0..7]; [0..7];
{ b:=Board(); n:=b.knightsTour(x,y); if(n!=64) b.println(">>>",x,",",y) } ]];</langsyntaxhighlight>
{{out}}Nada
 
2,455

edits