Knight's tour

From Rosetta Code
(Redirected from Knight's Tour)
Task
Knight's tour
You are encouraged to solve this task according to the task description, using any language you may know.
Task

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.

Input and output may be textual or graphical, according to the conventions of the programming environment. If textual, squares should be indicated in algebraic notation. The output should indicate the order in which the knight visits the squares, starting with the initial position. The form of the output may be a diagram of the board with the squares numbered according to visitation sequence, or a textual list of algebraic coordinates in order, or even an actual animation of the knight moving around the chessboard.

Input: starting square

Output: move sequence


Related tasks



11l

Translation of: Python
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()
Output:
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

360 Assembly

Translation of: BBC PASIC
*        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
Output:
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

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.

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; Scene: Tour := Empty) return Tour;
   -- finds tour via backtracking
   -- either no tour has been found, i.e., Get_Tour returns 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)!"
 
   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;

Here is the implementation:

with Ada.Text_IO, Ada.Integer_Text_IO;
 
package body Knights_Tour is
 
 
   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));
   -- places for the night to go (relative to the current position)
   
   function Count_Moves(Board: Tour) return Natural 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;
      begin
         Found := False;
         Visited(X, Y) := Move_Number;
         if Move_Number = Move_Count then
            Found := True;
         else
            for P in Pairs'Range loop
               XX := X + Pairs(P)(1);
               YY := Y + Pairs(P)(2);
               if (XX in Index) and then (YY in Index)
                                and then Visited(XX, YY) = 0 then
                  Visit(XX, YY, Move_Number+1, Found); -- recursion
                  if Found then
                     return; -- no need to search further
                  end if;
               end if;
            end loop;
            Visited(X, Y) := 0; -- undo previous mark
         end if;
      end Visit;
 
   begin
      Visited := Scene;
      Visit(Start_X, Start_Y, 1, Done);
      if not Done then
         Visited := Scene;
      end if;
      return Visited;
   end Get_Tour;
  
   procedure Tour_IO(The_Tour: Tour; Width: Natural := 4) is
   begin
      for I in Index loop
         for J in Index loop
	    if The_Tour(I, J) < 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;
   end Tour_IO;
 
end Knights_Tour;

Here is the main program:

with Knights_Tour, Ada.Command_Line;

procedure Test_Knight is

   Size: Positive := Positive'Value(Ada.Command_Line.Argument(1));

   package KT is new Knights_Tour(Size => Size);

begin
   KT.Tour_IO(KT.Get_Tour(1, 1));
end Test_Knight;

For small sizes, this already works well (< 1 sec for size 8). Sample output:

>./test_knight 8
   1  38  55  34   3  36  19  22
  54  47   2  37  20  23   4  17
  39  56  33  46  35  18  21  10
  48  53  40  57  24  11  16   5
  59  32  45  52  41  26   9  12
  44  49  58  25  62  15   6  27
  31  60  51  42  29   8  13  64
  50  43  30  61  14  63  28   7

For larger sizes we'll use Warnsdorff's heuristic (without any thoughtful tie breaking). We enhance the specification adding 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.

   
   function Warnsdorff_Get_Tour(Start_X, Start_Y: Index; Scene: Tour := Empty) 
			       return Tour;
   -- uses Warnsdorff heurisitic to find a tour faster
   -- same interface as Get_Tour

Its implementation is as follows.

   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;
      begin
         for P in Pairs'Range loop
            if X+Pairs(P)(1) in Index and then Y+Pairs(P)(2) in Index and then
              Visited(X+Pairs(P)(1),  Y+Pairs(P)(2)) = 0 then
               Result := Result + 1;
            end if;
         end loop;
         return Result;
      end Neighbors;
 
      procedure Sort(Options: in out Pair_Array) is
         N_Bors: array(Options'Range) of Natural;
         K: Positive range Options'Range;
         N: Natural;
         P: Pair;
      begin
         for Opt in Options'Range loop
            N_Bors(Opt) := Neighbors(Options(Opt)(1), Options(Opt)(2));
         end loop;
         for Opt in Options'Range loop
            K := Opt;
            for Alternative in Opt+1 .. Options'Last loop
               if N_Bors(Alternative) < N_Bors(Opt) then
                  K := Alternative;
               end if;
            end loop;
            N           := N_Bors(Opt);
            N_Bors(Opt) := N_Bors(K);
            N_Bors(K)   := N;
            P            := Options(Opt);
            Options(Opt) := Options(K);
            Options(K)   := P;
         end loop;
      end Sort;
 
      procedure Visit(X, Y: Index; Move: Positive; Found: out Boolean) is
         Next_Count: Natural range 0 .. 8 := 0;
         Next_Steps: Pair_Array(1 .. 8);
         XX, YY: Integer;
      begin
         Found := False;
         Visited(X, Y) := Move;
         if Move = Move_Count then
            Found := True;
         else
            -- consider all possible places to go
            for P in Pairs'Range loop
               XX := X + Pairs(P)(1);
               YY := Y + Pairs(P)(2);
               if (XX in Index) and then (YY in Index)
                 and then Visited(XX, YY) = 0 then
                  Next_Count := Next_Count+1;
                  Next_Steps(Next_Count) := (XX, YY);
               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);
               if Found then
                  return; -- no need to search further
            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 := Scene;
      Visit(Start_X, Start_Y, 1, Done);
      if not Done then
         Visited := Scene;
      end if;
      return Visited;
   end Warnsdorff_Get_Tour;

The modification for the main program is trivial:

with Knights_Tour, Ada.Command_Line;

procedure Test_Fast is

   Size: Positive := Positive'Value(Ada.Command_Line.Argument(1));

   package KT is new Knights_Tour(Size => Size);

begin
   KT.Tour_IO(KT.Warnsdorff_Get_Tour(1, 1));
end Test_Fast;

This works still well for somewhat larger sizes:

>./test_fast 24
   1 108  45  52   3 112  57  60   5  62 131 144   7  64 147 170   9  66 187 192  11  68  71 190
  46  51   2 111  56  53   4 113 130  59   6  63 146 169   8  65 186 215  10  67 188 191  12  69
 107  44 109  54 123 114 129  58  61 132 145 168 143 148 185 214 171 198 225 216 193  70 189  72
  50  47 122 115 110  55 140 133 128 167 142 149 184 213 172 199 226 255 246 197 224 217 194  13
  43 106  49 124 139 134 127 166 141 150 183 212 173 200 227 254 247 242 223 256 245 196  73 218
  48 121 116 135 126 165 138 151 182 211 174 201 228 253 248 241 290 263 304 243 222 257  14 195
 105  42 125 164 137 152 181 210 175 202 229 252 249 240 289 264 329 308 291 262 303 244 219  74
 120 117 136 153 180 163 176 203 230 267 250 239 288 265 328 309 334 345 330 305 292 221 258  15
  41 104 119 160 177 204 231 268 209 238 287 266 251 310 335 344 357 332 307 346 261 302  75 220
 118 159 154 205 162 179 208 237 286 269 324 311 336 327 438 333 418 347 356 331 306 293  16 259
 103  40 161 178 207 232 285 270 323 312 337 326 483 416 343 422 437 358 419 298 349 260 301  76
 158 155 206 233 284 271 236 313 338 325 482 415 342 439 484 417 420 423 348 355 360 299 294  17
  39 102 157 272 235 314 339 322 481 414 341 492 497 514 421 440 485 436 359 424 297 350  77 300
 156 273 234 315 276 283 478 413 340 493 480 513 530 491 498 515 452 441 454 435 354 361  18 295
 101  38 275 282 397 412 321 494 479 512 557 496 543 534 529 490 499 486 451 442 425 296 351  78
 274 279 316 277 320 477 410 511 570 495 554 535 556 531 542 533 516 453 444 455 434 353 362  19
  37 100 281 398 411 396 575 476 567 558 561 544 553 536 521 528 489 500 487 450 443 426  79 352
 280 317 278 319 402 409 510 569 560 571 566 555 550 541 532 537 522 517 460 445 456 433  20 363
  99  36 389 378 399 576 395 574 475 568 559 562 545 552 525 520 527 488 501 462 449 364 427  80
  94 379 318 401 388 403 408 509 572 565 474 551 540 549 538 523 518 461 446 459 432 457 366  21
  35  98  93 390 377 400 573 394 375 508 563 546 373 524 519 526 371 502 463 466 365 448  81 428
 380  95 382 385 404 387 376 407 564 473 374 507 548 539 372 503 464 467 370 447 458 431  22 367
 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

ALGOL 68

Works with: ALGOL 68G version Any - tested with release 2.8.win32
# 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;
# 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 );

INT lowest move  = LWB offset v;
INT highest move = UPB offset v;

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 #

BEGIN
    # 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
END
Output:
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

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)
  }
Output:

$ ./knights_tour c5 2 closed

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

AutoHotkey

Library: GDIP
#SingleInstance, Force
#NoEnv
SetBatchLines, -1
; Uncomment if Gdip.ahk is not in your standard library
;#Include, Gdip.ahk
If !pToken := Gdip_Startup(){
   MsgBox, 48, Gdiplus error!, Gdiplus failed to start. Please ensure you have Gdiplus on your system.
   ExitApp
}
; I've added a simple new function here, just to ensure if anyone is having any problems then to make sure they are using the correct library version
if (Gdip_LibraryVersion() < 1.30)
{
	MsgBox, 48, Version error!, Please download the latest version of the gdi+ library
	ExitApp
}
OnExit, Exit
tour := "a1 b3 d2 c4 a5 b7 d8 e6 d4 b5 c7 a8 b6 c8 a7 c6 b8 a6 b4 d5 e3 d1 b2 a4 c5 d7 f8 h7 f6 g8 h6 f7 h8 g6 e7 f5 h4 g2 e1 d3 e5 g4 f2 h1 g3 f1 h2 f3 g1 h3 g5 e4 d6 e8 g7 h5 f4 e2 c1 a2 c3 b1 a3 c2 "
; Knight's tour with maximum symmetry by George Jelliss, http://www.mayhematics.com/t/8f.htm
; I know, I know, but I followed the task outline to the letter! Besides, this path is the prettiest.

; Input: starting square
InputBox, start, Knight's Tour Start, Enter Knight's starting location in algebraic notation:, , , , , , , , b3
i := InStr(tour, start)
If i=0
{
	Msgbox Error, please try again.
	Reload
}
; Output: move sequence
Msgbox % tour := SubStr(tour, i) . SubStr(tour, 1, i-1)

; Animation
tour .= SubStr(tour, 1, 3)
, CellSize := 30 ; pixels
, Width := Height := 9*CellSize
, TopLeftX := (A_ScreenWidth - Width) // 2
, TopLeftY := (A_ScreenHeight - Height) // 2
Gui, -Caption +E0x80000 +LastFound +AlwaysOnTop +ToolWindow +OwnDialogs
Gui, Show, NA ; show board (currently transparent)
hwnd1 := WinExist() ; required for Gdip
OnMessage(0x201, "WM_LBUTTONDOWN")
, hbm := CreateDIBSection(Width, Height)
, hdc := CreateCompatibleDC()
, obm := SelectObject(hdc, hbm)
, G := Gdip_GraphicsFromHDC(hdc)
, Gdip_SetSmoothingMode(G, 4)

Loop 1 ; remove '1' and uncomment next line to loop infinitely
{
;Gdip_GraphicsClear(G) ; uncomment to loop infinitely
cOdd := "0xFFFFCE9E" ; create brushes
, cEven := "0xFFD18B47"
, pBrushOdd := Gdip_BrushCreateSolid(cOdd)
, pBrushEven := Gdip_BrushCreateSolid(cEven)

Loop 64 ; layout board
{
	Row := mod(A_Index-1,8)+1
	, Col := (A_Index-1)//8+1
	, Gdip_FillRectangle(G, mod(Row+Col,2) ? pBrushOdd : pBrushEven, Col * CellSize + 1, Row * CellSize + 1, CellSize - 2, CellSize - 2)
}
Gdip_DeleteBrush(pBrushOdd) ; cleanup memory
, Gdip_DeleteBrush(pBrushEven)
, UpdateLayeredWindow(hwnd1, hdc, TopLeftX, TopLeftY, Width, Height) ; update board

, pPen := Gdip_CreatePen(0x66FF0000, CellSize/10) ; create pen
, Algebraic := SubStr(tour,1,2) ; get starting coordinates
, x := (Asc(SubStr(Algebraic, 1, 1))-96+0.5)*CellSize
, y := (9.5-SubStr(Algebraic, 2, 1))*CellSize

Loop 64 ; trace path
{
	Sleep, 0.5*1000
	xold := x, yold := y ; a line has start and end points
	, Algebraic := SubStr(tour,(A_Index)*3+1,2) ; get new coordinates
	, x := (Asc(SubStr(Algebraic, 1, 1))-96+0.5)*CellSize
	, y := (9.5-SubStr(Algebraic, 2, 1))*CellSize
	, Gdip_DrawLine(G, pPen, xold, yold, x, y)
	, UpdateLayeredWindow(hwnd1, hdc, TopLeftX, TopLeftY, Width, Height) ; update board
}
Gdip_DeletePen(pPen)
}
Return

GuiEscape:
	ExitApp

Exit:
	Gdip_Shutdown(pToken)
	ExitApp

WM_LBUTTONDOWN()
{
	If (A_Gui = 1)
	PostMessage, 0xA1, 2
}
Output:

For start at b3

b3 d2 c4 a5 b7 d8 e6 d4 b5 c7 a8 b6 c8 a7 c6 b8 a6 b4 d5 e3 d1 b2 a4 c5 d7 f8 h7 f6 g8 h6 f7 h8 g6 e7 f5 h4 g2 e1 d3 e5 g4 f2 h1 g3 f1 h2 f3 g1 h3 g5 e4 d6 e8 g7 h5 f4 e2 c1 a2 c3 b1 a3 c2 a1 

... plus an animation.

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")
    }
}

output:

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

BASIC

ANSI BASIC

Translation of: BBC BASIC
File:Knights Tour.gif
Works with: Decimal BASIC

ANSI BASIC does not allow function parameters to be passed by reference, so X and Y were made global variables.

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

BBC BASIC

      VDU 23,22,256;256;16,16,16,128
      VDU 23,23,4;0;0;0;
      OFF
      GCOL 4,15
      FOR x% = 0 TO 512-128 STEP 128
        RECTANGLE FILL x%,0,64,512
      NEXT
      FOR y% = 0 TO 512-128 STEP 128
        RECTANGLE FILL 0,y%,512,64
      NEXT
      GCOL 9
      
      DIM Board%(7,7)
      X% = 0
      Y% = 0
      Total% = 0
      REPEAT
        Board%(X%,Y%) = TRUE
        IF Total% DRAW X%*64+32,Y%*64+32 ELSE MOVE X%*64+32,Y%*64+32
        Total% += 1
      UNTIL NOT FNchoosemove(X%, Y%)
      IF Total%<>64 STOP
      REPEAT WAIT 1 : UNTIL FALSE
      END
      
      DEF FNchoosemove(RETURN X%, RETURN Y%)
      LOCAL M%, newx%, newy%
      M% = 9
      PROCtrymove(X%+1, Y%+2, M%, newx%, newy%)
      PROCtrymove(X%+1, Y%-2, M%, newx%, newy%)
      PROCtrymove(X%-1, Y%+2, M%, newx%, newy%)
      PROCtrymove(X%-1, Y%-2, M%, newx%, newy%)
      PROCtrymove(X%+2, Y%+1, M%, newx%, newy%)
      PROCtrymove(X%+2, Y%-1, M%, newx%, newy%)
      PROCtrymove(X%-2, Y%+1, M%, newx%, newy%)
      PROCtrymove(X%-2, Y%-1, M%, newx%, newy%)
      IF M%=9 THEN = FALSE
      X% = newx% : Y% = newy%
      = TRUE
      
      DEF PROCtrymove(X%, Y%, RETURN M%, RETURN newx%, RETURN newy%)
      LOCAL N%
      IF NOT FNvalidmove(X%,Y%) THEN ENDPROC
      IF FNvalidmove(X%+1,Y%+2) N% += 1
      IF FNvalidmove(X%+1,Y%-2) N% += 1
      IF FNvalidmove(X%-1,Y%+2) N% += 1
      IF FNvalidmove(X%-1,Y%-2) N% += 1
      IF FNvalidmove(X%+2,Y%+1) N% += 1
      IF FNvalidmove(X%+2,Y%-1) N% += 1
      IF FNvalidmove(X%-2,Y%+1) N% += 1
      IF FNvalidmove(X%-2,Y%-1) N% += 1
      IF N%>M% THEN ENDPROC
      IF N%=M% IF RND(2)=1 THEN ENDPROC
      M% = N%
      newx% = X% : newy% = Y%
      ENDPROC
      
      DEF FNvalidmove(X%,Y%)
      IF X%<0 OR X%>7 OR Y%<0 OR Y%>7 THEN = FALSE
      = NOT(Board%(X%,Y%))

Bracmat

  ( knightsTour
  =     validmoves WarnsdorffSort algebraicNotation init solve
      , x y fieldsToVisit
    .   ~
      |   ( validmoves
          =   x y jumps moves
            .   !arg:(?x.?y)
              & :?moves
              & ( jumps
                =   dx dy Fs fxs fys fx fy
                  .   !arg:(?dx.?dy)
                    & 1 -1:?Fs
                    & !Fs:?fxs
                    &   whl
                      ' ( !fxs:%?fx ?fxs
                        & !Fs:?fys
                        &   whl
                          ' ( !fys:%?fy ?fys
                            &     (   (!x+!fx*!dx.!y+!fy*!dy)
                                    : (>0:<9.>0:<9)
                                  | 
                                  )
                                  !moves
                              : ?moves
                            )
                        )
                )
              & jumps$(1.2)
              & jumps$(2.1)
              & !moves
          )
        & ( init
          =   fields x y
            .   :?fields
              & 0:?x
              &   whl
                ' ( 1+!x:<9:?x
                  & 0:?y
                  &   whl
                    ' ( 1+!y:<9:?y
                      & (!x.!y) !fields:?fields
                      )
                  )
              & !fields
          )
        & init$:?fieldsToVisit
        & ( WarnsdorffSort
          =   sum moves elm weightedTerms
            .   ( weightedTerms
                =   pos alts fieldsToVisit moves move weight
                  .     !arg:(%?pos ?alts.?fieldsToVisit)
                      &   (   !fieldsToVisit:!pos
                            & (0.!pos)
                          |   !fieldsToVisit:? !pos ?
                            & validmoves$!pos:?moves
                            & 0:?weight
                            &   whl
                              ' ( !moves:%?move ?moves
                                & (   !fieldsToVisit:? !move ?
                                    & !weight+1:?weight
                                  | 
                                  )
                                )
                            & (!weight.!pos)
                          | 0
                          )
                        + weightedTerms$(!alts.!fieldsToVisit)
                    | 0
                )
              & weightedTerms$!arg:?sum
              & :?moves
              &   whl
                ' ( !sum:(#.?elm)+?sum
                  & !moves !elm:?moves
                  )
              & !moves
          )
        & ( solve
          =   pos alts fieldsToVisit A Z tailOfSolution
            .   !arg:(%?pos ?alts.?fieldsToVisit)
              &   (   !fieldsToVisit:?A !pos ?Z
                    & ( !A !Z:&
                      |   solve
                        $ ( WarnsdorffSort$(validmoves$!pos.!A !Z)
                          . !A !Z
                          )
                      )
                  | solve$(!alts.!fieldsToVisit)
                  )
                : ?tailOfSolution
              & !pos !tailOfSolution
          )
        & ( algebraicNotation
          =   x y
            .     !arg:(?x.?y) ?arg
                &   str$(chr$(asc$a+!x+-1) !y " ")
                    algebraicNotation$!arg
              | 
          )
        & @(!arg:?x #?y)
        & asc$!x+-1*asc$a+1:?x
        &   str
          $ (algebraicNotation$(solve$((!x.!y).!fieldsToVisit)))
  )
& out$(knightsTour$a1);
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

C

For an animated version using OpenGL, see Knight's tour/C.

The following draws on console the progress of the horsie. Specify board size on commandline, or use default 8.

#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include <unistd.h>

typedef unsigned char cell;
int dx[] = { -2, -2, -1, 1, 2,  2,  1, -1 };
int dy[] = { -1,  1,  2, 2, 1, -1, -2, -2 };

void init_board(int w, int h, cell **a, cell **b)
{
	int i, j, k, x, y, p = w + 4, q = h + 4;
	/* b is board; a is board with 2 rows padded at each side */
	a[0] = (cell*)(a + q);
	b[0] = a[0] + 2;

	for (i = 1; i < q; i++) {
		a[i] = a[i-1] + p;
		b[i] = a[i] + 2;
	}

	memset(a[0], 255, p * q);
	for (i = 0; i < h; i++) {
		for (j = 0; j < w; j++) {
			for (k = 0; k < 8; k++) {
				x = j + dx[k], y = i + dy[k];
				if (b[i+2][j] == 255) b[i+2][j] = 0;
				b[i+2][j] += x >= 0 && x < w && y >= 0 && y < h;
			}
		}
	}
}

#define E "\033["
int walk_board(int w, int h, int x, int y, cell **b)
{
	int i, nx, ny, least;
	int steps = 0;
	printf(E"H"E"J"E"%d;%dH"E"32m[]"E"m", y + 1, 1 + 2 * x);

	while (1) {
		/* occupy cell */
		b[y][x] = 255;

		/* reduce all neighbors' neighbor count */
		for (i = 0; i < 8; i++)
			b[ y + dy[i] ][ x + dx[i] ]--;

		/* find neighbor with lowest neighbor count */
		least = 255;
		for (i = 0; i < 8; i++) {
			if (b[ y + dy[i] ][ x + dx[i] ] < least) {
				nx = x + dx[i];
				ny = y + dy[i];
				least = b[ny][nx];
			}
		}

		if (least > 7) {
			printf(E"%dH", h + 2);
			return steps == w * h - 1;
		}

		if (steps++) printf(E"%d;%dH[]", y + 1, 1 + 2 * x);
		x = nx, y = ny;
		printf(E"%d;%dH"E"31m[]"E"m", y + 1, 1 + 2 * x);
		fflush(stdout);
		usleep(120000);
	}
}

int solve(int w, int h)
{
	int x = 0, y = 0;
	cell **a, **b;
	a = malloc((w + 4) * (h + 4) + sizeof(cell*) * (h + 4));
	b = malloc((h + 4) * sizeof(cell*));

	while (1) {
		init_board(w, h, a, b);
		if (walk_board(w, h, x, y, b + 2)) {
			printf("Success!\n");
			return 1;
		}
		if (++x >= w) x = 0, y++;
		if (y >= h) {
			printf("Failed to find a solution\n");
			return 0;
		}
		printf("Any key to try next start position");
		getchar();
	}
}

int main(int c, char **v)
{
	int w, h;
	if (c < 2 || (w = atoi(v[1])) <= 0) w = 8;
	if (c < 3 || (h = atoi(v[2])) <= 0) h = w;
	solve(w, h);

	return 0;
}

C#

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;
		}
	}
}

C++

Works with: C++11

Uses Warnsdorff's rule and (iterative) backtracking if that fails.

#include <iostream>
#include <iomanip>
#include <array>
#include <string>
#include <tuple>
#include <algorithm>
using namespace std;

template<int N = 8>
class Board 
{
public:
    array<pair<int, int>, 8> moves;
    array<array<int, N>, N> data;

    Board() 
    {
        moves[0] = make_pair(2, 1);
        moves[1] = make_pair(1, 2);
        moves[2] = make_pair(-1, 2);
        moves[3] = make_pair(-2, 1);
        moves[4] = make_pair(-2, -1);
        moves[5] = make_pair(-1, -2);
        moves[6] = make_pair(1, -2);
        moves[7] = make_pair(2, -1);
    }

    array<int, 8> sortMoves(int x, int y) const 
    {
        array<tuple<int, int>, 8> counts;
        for(int i = 0; i < 8; ++i) 
        {
            int dx = get<0>(moves[i]);
            int dy = get<1>(moves[i]);

            int c = 0;
            for(int j = 0; j < 8; ++j) 
            {
                int x2 = x + dx + get<0>(moves[j]);
                int y2 = y + dy + get<1>(moves[j]);

                if (x2 < 0 || x2 >= N || y2 < 0 || y2 >= N)
                    continue;
                if(data[y2][x2] != 0)
                    continue;

                c++;
            }

            counts[i] = make_tuple(c, i);
        }

        // Shuffle to randomly break ties
        random_shuffle(counts.begin(), counts.end());

        // Lexicographic sort
        sort(counts.begin(), counts.end());

        array<int, 8> out;
        for(int i = 0; i < 8; ++i)
            out[i] = get<1>(counts[i]);
        return out;
    }

    void solve(string start) 
    {
        for(int v = 0; v < N; ++v)
            for(int u = 0; u < N; ++u)
                data[v][u] = 0;

        int x0 = start[0] - 'a';
        int y0 = N - (start[1] - '0');
        data[y0][x0] = 1;

        array<tuple<int, int, int, array<int, 8>>, N*N> order;
        order[0] = make_tuple(x0, y0, 0, sortMoves(x0, y0));

        int n = 0;
        while(n < N*N-1) 
        {
            int x = get<0>(order[n]);
            int y = get<1>(order[n]);

            bool ok = false;
            for(int i = get<2>(order[n]); i < 8; ++i) 
            {
                int dx = moves[get<3>(order[n])[i]].first;
                int dy = moves[get<3>(order[n])[i]].second;

                if(x+dx < 0 || x+dx >= N || y+dy < 0 || y+dy >= N)
                    continue;
                if(data[y + dy][x + dx] != 0) 
                    continue;

                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));
                ok = true;
                break;
            }

            if(!ok) // Failed. Backtrack.
            {
                data[y][x] = 0;
                --n;
            }
        }
    }

    template<int N>
    friend ostream& operator<<(ostream &out, const Board<N> &b);
};

template<int N>
ostream& operator<<(ostream &out, const Board<N> &b) 
{
    for (int v = 0; v < N; ++v) 
    {
        for (int u = 0; u < N; ++u) 
        {
            if (u != 0) out << ",";
            out << setw(3) << b.data[v][u];
        }
        out << endl;
    }
    return out;
}

int main() 
{
    Board<5> b1;
    b1.solve("c3");
    cout << b1 << endl;

    Board<8> b2;
    b2.solve("b5");
    cout << b2 << endl;

    Board<31> b3; // Max size for <1000 squares
    b3.solve("a1");
    cout << b3 << endl;
    return 0;
}

Output:

 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

 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

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

Common Lisp

Works with: clisp version 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.

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.

For some reason, the interactive part does not work with SBCL, but it works fine with CLISP.

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;;   Solving the knight's tour.                     ;;;
;;;   Warnsdorff's rule with random tie break.       ;;;
;;;   Optionally outputs a closed tour.              ;;;
;;;   Options from interactive prompt.               ;;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

(defparameter *side* 8)

(defun generate-chessboard (n)
  (loop for i below n append
    (loop for j below n collect (complex i j))))

(defparameter *chessboard*
  (generate-chessboard *side*))

(defun complex->algebraic (n)
;; returns a string like "b2"
  (concatenate 'string
    ;; 'a' is char #97: add it to the offset
    (string (character  (+ 97 (realpart n))))
    ;; indices start at 0, but algebraic starts at 1
    (string (digit-char (+ 1  (imagpart n))))))

(defun algebraic->complex (string)
;; takes a string like "e4"
  (let ((row (char string 0))
        (col (char string 1)))
    (complex (- (char-code row) 97)
             (- (digit-char-p col) 1))))

(defconstant *knight-directions*
  (list
    (complex  1  2)
    (complex  2  1)
    (complex  1 -2)
    (complex  2 -1)
    (complex -1  2)
    (complex -2  1)
    (complex -1 -2)
    (complex -2 -1)))

(defun find-legal-moves (moves-list)
  ;; 2. the move must not be on a case already visited
  (remove-if (lambda (m) (member m moves-list))
    ;; 1. the move must be within the chessboard
    (intersection
      (mapcar (lambda (i) (+ (car moves-list) i)) *knight-directions*)
      *chessboard*)))


;; Select between two moves by Warnsdorff's rule:
;; pick the one with the lowest index or else
;; randomly break the tie.
;; Takes a cons in the form (n . #C(x y)).
;; This will be the sorting rule for picking the next move.
(defun w-rule (a b)
 (cond ((< (car a) (car b)) t)
       ((> (car a) (car b)) nil)
       ((= (car a) (car b))
         (zerop (random 2)))))

;; For every legal move in a given position,
;; look forward one move and return a cons
;; in the form (n . #C(x y)) where n is
;; how many next free moves follow the first move.
(defun return-weighted-moves (moves)
  (let ((candidates (find-legal-moves moves)))
    (loop for mv in candidates collect
      (cons
        (list-length (find-legal-moves (cons mv moves)))
        mv))))

;; Given a list of weighted moves (as above),
;; pick one according to the w-rule
(defun pick-among-weighted-moves (moves)
  ;; prune dead ends one move early
  (let ((possible-moves
          (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)
Output:
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

Clojure

Using warnsdorff's rule

(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)))))))
Output:
(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

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.

graph_tours = (graph, max_num_solutions) ->
  # graph is an array of arrays
  # graph[3] = [4, 5] means nodes 4 and 5 are reachable from node 3
  #
  # Returns an array of tours (up to max_num_solutions in size), where
  # each tour is an array of nodes visited in order, and where each
  # tour visits every node in the graph exactly once.
  #
  complete_tours = []
  visited = (false for node in graph)
  dead_ends = ({} for node in graph)
  tour = [0]
  
  valid_neighbors = (i) ->
    arr = []
    for neighbor in graph[i]
      continue if visited[neighbor]
      continue if dead_ends[i][neighbor]
      arr.push neighbor
    arr
    
  next_square_to_visit = (i) ->
    arr = valid_neighbors i
    return null if arr.length == 0

    # We traverse to our neighbor who has the fewest neighbors itself.
    fewest_neighbors = valid_neighbors(arr[0]).length
    neighbor = arr[0]
    for i in [1...arr.length]
      n = valid_neighbors(arr[i]).length
      if n < fewest_neighbors
        fewest_neighbors = n
        neighbor = arr[i]
    neighbor
  
  while tour.length > 0
    current_square = tour[tour.length - 1]
    visited[current_square] = true
    next_square = next_square_to_visit current_square
    if next_square?
      tour.push next_square
      if tour.length == graph.length
        complete_tours.push (n for n in tour) # clone
        break if complete_tours.length == max_num_solutions
      # pessimistically call this a dead end
      dead_ends[current_square][next_square] = true
      current_square = next_square
    else
      # we backtrack
      doomed_square = tour.pop()
      dead_ends[doomed_square] = {}
      visited[doomed_square] = false
  complete_tours
  

knight_graph = (board_width) ->
  # Turn the Knight's Tour into a pure graph-traversal problem
  # by precomputing all the legal moves.  Returns an array of arrays,
  # where each element in any subarray is the index of a reachable node.
  index = (i, j) ->
    # index squares from 0 to n*n - 1
    board_width * i + j
  
  reachable_squares = (i, j) ->
    deltas = [
      [ 1,  2]
      [ 1, -2]
      [ 2,  1]
      [ 2, -1]
      [-1,  2]
      [-1, -2]
      [-2,  1]
      [-2, -1]
    ]
    neighbors = []
    for delta in deltas
      [di, dj] = delta
      ii = i + di
      jj = j + dj
      if 0 <= ii < board_width
        if 0 <= jj < board_width
          neighbors.push index(ii, jj)
    neighbors
  
  graph = []
  for i in [0...board_width]
    for j in [0...board_width] 
      graph[index(i, j)] = reachable_squares i, j
  graph
  
illustrate_knights_tour = (tour, board_width) ->
  pad = (n) ->
    return " _" if !n?
    return " " + n if n < 10
    "#{n}"
    
  console.log "\n------"
  moves = {}
  for square, i in tour  
    moves[square] = i + 1
  for i in [0...board_width]
    s = ''
    for j in [0...board_width]
      s += "  " + pad moves[i*board_width + j]
    console.log s
    
BOARD_WIDTH = 8
MAX_NUM_SOLUTIONS = 100000

graph = knight_graph BOARD_WIDTH
tours = graph_tours graph, MAX_NUM_SOLUTIONS
console.log "#{tours.length} tours found (showing first and last)"
illustrate_knights_tour tours[0], BOARD_WIDTH
illustrate_knights_tour tours.pop(), BOARD_WIDTH

output

> time coffee knight.coffee 
100000 tours found (showing first and last)

------
   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

------
   1   4  41  20  63   6  61  22
  34  19   2   5  42  21  44   7
   3  40  35  64  37  62  23  60
  18  33  38  47  56  43   8  45
  39  14  57  36  49  46  59  24
  32  17  48  55  58  27  50   9
  13  54  15  30  11  52  25  28
  16  31  12  53  26  29  10  51

real	0m29.741s
user	0m25.656s
sys	0m0.253s

D

Fast Version

Translation of: C++
import std.stdio, std.algorithm, std.random, std.range,
       std.conv, std.typecons, std.typetuple;

int[N][N] knightTour(size_t N=8)(in string start)
in {
    assert(start.length >= 2);
} body {
    static struct P { int x, y; }

    immutable P[8] moves = [P(2,1), P(1,2), P(-1,2), P(-2,1),
                            P(-2,-1), P(-1,-2), P(1,-2), P(2,-1)];
    int[N][N] data;

    int[8] sortMoves(in int x, in int y) {
        int[2][8] counts;
        foreach (immutable i, immutable ref d1; moves) {
            int c = 0;
            foreach (immutable ref d2; moves) {
                immutable p = P(x + d1.x + d2.x, y + d1.y + d2.y);
                if (p.x >= 0 && p.x < N && p.y >= 0 && p.y < N &&
                    data[p.y][p.x] == 0)
                    c++;
            }
            counts[i] = [c, i];
        }

        counts[].randomShuffle; // Shuffle to randomly break ties.
        counts[].sort(); // Lexicographic sort.

        int[8] result = void;
        transversal(counts[], 1).copy(result[]);
        return result;
    }

    immutable p0 = P(start[0] - 'a', N - to!int(start[1 .. $]));
    data[p0.y][p0.x] = 1;

    Tuple!(int, int, int, int[8])[N * N] order;
    order[0] = tuple(p0.x, p0.y, 0, sortMoves(p0.x, p0.y));

    int n = 0;
    while (n < (N * N - 1)) {
        immutable int x = order[n][0];
        immutable int y = order[n][1];
        bool ok = false;
        foreach (immutable i; order[n][2] .. 8) {
            immutable P d = moves[order[n][3][i]];
            if (x+d.x < 0 || x+d.x >= N || y+d.y < 0 || y+d.y >= N)
                continue;

            if (data[y + d.y][x + d.x] == 0) {
                order[n][2] = i + 1;
                n++;
                data[y + d.y][x + d.x] = n + 1;
                order[n] = tuple(x+d.x,y+d.y,0,sortMoves(x+d.x,y+d.y));
                ok = true;
                break;
            }
        }

        if (!ok) { // Failed. Backtrack.
            data[y][x] = 0;
            n--;
        }
    }

    return data;
}

void main() {
    foreach (immutable i, side; TypeTuple!(5, 8, 31, 101)) {
        immutable form = "%(%" ~ text(side ^^ 2).length.text ~ "d %)";
        foreach (ref row; ["c3", "b5", "a1", "a1"][i].knightTour!side)
            writefln(form, row);
        writeln();
    }
}
Output:
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

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

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

Shorter Version

Translation of: Haskell
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));
}
Output:
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

Delphi

Works with: Delphi version 6.0

Brute force method. Takes a long time for most solutions, so some optimization should be used. However, it has nice graphics.


{ 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;
Output:

EasyLang

Backtracking, whereby the paths with the fewest branches are tracked first.

Run it

sys topleft
dirs[][] = [ [ 1 2 ] [ 1 -2 ] [ 2 1 ] [ 2 -1 ] [ -1 2 ] [ -1 -2 ] [ -2 -1 ] [ -2 1 ] ]
global brd[][] size .
func cntmoves m[] .
   for d = 1 to len dirs[][]
      rn = m[1] + dirs[d][1]
      cn = m[2] + dirs[d][2]
      if rn >= 1 and rn <= size and cn >= 1 and cn <= size and brd[rn][cn] = 0
         n += 1
      .
   .
   return n
.
proc sortmoves . m[][] .
   for i = 1 to len m[][]
      cnt[] &= cntmoves m[i][]
   .
   for i = 1 to len cnt[] - 1
      for j = i + 1 to len cnt[]
         if cnt[j] < cnt[i]
            swap cnt[j] cnt[i]
            swap m[j][] m[i][]
         .
      .
   .
.
func solve r c cnt .
   if cnt > size * size
      return 1
   .
   movs[][] = [ ]
   for d = 1 to len dirs[][]
      rn = r + dirs[d][1]
      cn = c + dirs[d][2]
      if rn >= 1 and rn <= size and cn >= 1 and cn <= size and brd[rn][cn] = 0
         movs[][] &= [ rn cn ]
      .
   .
   sortmoves movs[][]
   for i = 1 to len movs[][]
      rn = movs[i][1]
      cn = movs[i][2]
      brd[rn][cn] = cnt
      if solve rn cn (cnt + 1) = 1
         return 1
      .
      brd[rn][cn] = 0
   .
   return 0
.
proc prepare . .
   brd[][] = [ ]
   len brd[][] size
   for r to size
      len brd[r][] size
   .
.
proc printbrd . .
   numfmt 0 3
   if size > 10
      numfmt 0 4
   .
   for r to size
      for c to size
         write brd[r][c]
      .
      print ""
   .
.
size = 8
r0 = random size
c0 = random size
prepare
brd[r0][c0] = 1
found = solve r0 c0 2
if found = 1
   printbrd
   print ""
else
   print "no solutions found: (" & r0 & " " & c0 & ")"
.
# 
proc showgraf . .
   sc = 100 / size
   linewidth sc / 15
   col[] = [ 777 333 ]
   for r = 0 to size - 1
      for c = 0 to size - 1
         color col[(r + c) mod1 2]
         move sc * c sc * r
         rect sc sc
      .
   .
   move 0 / 0 0
   for i to size * size
      for r = 1 to size
         for c = 1 to size
            if brd[r][c] = i
               color 600
               x = c * sc - sc / 2
               y = r * sc - sc / 2
               line x y
               color 880
               circle sc / 10
            .
         .
      .
   .
.
if found = 1
   showgraf
.
Output:
28 25 10 57 38 23  8  5
 11 58 27 24  9  6 37 22
 26 29 60 45 56 39  4  7
 59 12 55 52 41 44 21 36
 30 53 42 61 46 51 40  3
 13 62 47 54 43 18 35 20
 48 31 64 15 50 33  2 17
 63 14 49 32  1 16 19 34

EchoLisp

The algorithm uses iterative backtracking and Warnsdorff's heuristic. It can output closed or non-closed tours.

(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))))


Output:
(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
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).

(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)))


Closed path on a 12x12 board: [1]

Open path on a 24x24 board: [2]

Elixir

Translation of: Ruby
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)
Output:
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
 

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
        }

Link to live demo: https://dmcbane.github.io/knights-tour/

Erlang

Again I use backtracking. It seemed easier this time.

-module( knights_tour ).

-export( [display/1, solve/1, task/0] ).

display( Moves ) ->
	%% The knigh walks the moves {Position, Step_nr} order.
	%% Top left corner is {$a, 8}, Bottom right is {$h, 1}.
	io:fwrite( "Moves:" ),
	lists:foldl( fun display_moves/2, erlang:length(Moves), lists:keysort(2, Moves) ),
	io:nl(),
	[display_row(Y, Moves) || Y <- lists:seq(8, 1, -1)].

solve( First_square ) ->
    try
    bt_loop( 1, next_moves(First_square), [{First_square, 1}] )

    catch
    _:{ok, Moves} -> Moves

    end.

task() ->
	io:fwrite( "Starting {a, 1}~n" ),
	Moves = solve( {$a, 1} ),
	display( Moves ).



bt( N, Move, Moves ) -> bt_reject( is_not_allowed_knight_move(Move, Moves), N, Move, [{Move, N} | Moves] ).

bt_accept( true, _N, _Move, Moves ) -> erlang:throw( {ok, Moves} );
bt_accept( false, N, Move, Moves ) -> bt_loop( N, next_moves(Move), Moves ).

bt_loop( N, New_moves, Moves ) -> [bt( N+1, X, Moves ) || X <- New_moves].

bt_reject( true, _N, _Move, _Moves ) -> backtrack;
bt_reject( false, N, Move, Moves ) -> bt_accept( is_all_knights(Moves), N, Move, Moves ).

display_moves( {{X, Y}, 1}, Max ) ->
	io:fwrite(" ~p. N~c~p", [1, X, Y]),
	Max;
display_moves( {{X, Y}, Max}, Max ) ->
	io:fwrite(" N~c~p~n", [X, Y]),
	Max;
display_moves( {{X, Y}, Step_nr}, Max ) when Step_nr rem 8 =:= 0 ->
	io:fwrite(" N~c~p~n~p. N~c~p", [X, Y, Step_nr, X, Y]),
	Max;
display_moves( {{X, Y}, Step_nr}, Max ) ->
	io:fwrite(" N~c~p ~p. N~c~p", [X, Y, Step_nr, X, Y]),
	Max.

display_row( Row, Moves ) ->
	[io:fwrite(" ~2b", [proplists:get_value({X, Row}, Moves)]) || X <- [$a, $b, $c, $d, $e, $f, $g, $h]],
	io:nl().

is_all_knights( Moves ) when erlang:length(Moves) =:= 64 -> true;
is_all_knights( _Moves ) -> false.

is_asymetric( Start_column, Start_row, Stop_column, Stop_row ) ->
	erlang:abs( Start_column - Stop_column ) =/= erlang:abs( Start_row - Stop_row ).

is_not_allowed_knight_move( Move, Moves ) ->
	no_such_move =/= proplists:get_value( Move, Moves, no_such_move ).

next_moves( {Column, Row} ) ->
	[{X, Y} || X <- next_moves_column(Column), Y <- next_moves_row(Row), is_asymetric(Column, Row, X, Y)].

next_moves_column( $a ) -> [$b, $c];
next_moves_column( $b ) -> [$a, $c, $d];
next_moves_column( $g ) -> [$e, $f, $h];
next_moves_column( $h ) -> [$g, $f];
next_moves_column( C ) -> [C - 2, C - 1, C + 1, C + 2].

next_moves_row( 1 ) -> [2, 3];
next_moves_row( 2 ) -> [1, 3, 4];
next_moves_row( 7 ) -> [5, 6, 8];
next_moves_row( 8 ) -> [6, 7];
next_moves_row( N ) -> [N - 2, N - 1, N + 1, N + 2].
Output:
17> knights_tour:task().
Starting {a, 1}
Moves: 1. Na1 Nb3 2. Nb3 Na5 3. Na5 Nb7 4. Nb7 Nc5 5. Nc5 Na4 6. Na4 Nb2 7. Nb2 Nc4
8. Nc4 Na3 9. Na3 Nb1 10. Nb1 Nc3 11. Nc3 Na2 12. Na2 Nb4 13. Nb4 Na6 14. Na6 Nb8 15. Nb8 Nc6
16. Nc6 Na7 17. Na7 Nb5 18. Nb5 Nc7 19. Nc7 Na8 20. Na8 Nb6 21. Nb6 Nc8 22. Nc8 Nd6 23. Nd6 Ne4
24. Ne4 Nd2 25. Nd2 Nf1 26. Nf1 Ne3 27. Ne3 Nc2 28. Nc2 Nd4 29. Nd4 Ne2 30. Ne2 Nc1 31. Nc1 Nd3
32. Nd3 Ne1 33. Ne1 Ng2 34. Ng2 Nf4 35. Nf4 Nd5 36. Nd5 Ne7 37. Ne7 Ng8 38. Ng8 Nh6 39. Nh6 Nf5
40. Nf5 Nh4 41. Nh4 Ng6 42. Ng6 Nh8 43. Nh8 Nf7 44. Nf7 Nd8 45. Nd8 Ne6 46. Ne6 Nf8 47. Nf8 Nd7
48. Nd7 Ne5 49. Ne5 Ng4 50. Ng4 Nh2 51. Nh2 Nf3 52. Nf3 Ng1 53. Ng1 Nh3 54. Nh3 Ng5 55. Ng5 Nh7
56. Nh7 Nf6 57. Nf6 Ne8 58. Ne8 Ng7 59. Ng7 Nh5 60. Nh5 Ng3 61. Ng3 Nh1 62. Nh1 Nf2 63. Nf2 Nd1

 20 15 22 45 58 47 38 43
 17  4 19 48 37 44 59 56
 14 21 16 23 46 57 42 39
  3 18  5 36 49 40 55 60
  6 13  8 29 24 35 50 41
  9  2 11 32 27 52 61 54
 12  7 28 25 30 63 34 51
  1 10 31 64 33 26 53 62

ERRE

Taken from ERRE distribution disk. Comments are in Italian.

! **********************************************************************
! *                                                                    *
! *     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
Output:
            ***    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! ***

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
Output:

Knights Tour FreeBasic image

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...

Fōrmulæ

Fōrmulæ programs are not textual, visualization/edition of programs is done showing/manipulating structures but not text. Moreover, there can be multiple visual representations of the same program. Even though it is possible to have textual representation —i.e. XML, JSON— they are intended for storage and transfer purposes more than visualization and edition.

Programs in Fōrmulæ are created/edited online in its website.

In this page you can see and run the program(s) related to this task and their results. You can also change either the programs or the parameters they are called with, for experimentation, but remember that these programs were created with the main purpose of showing a clear solution of the task, and they generally lack any kind of validation.

Fortran

FORTRAN 77

Translation of: ATS
Works with: gfortran version 11.2.1
Works with: f2c
C-----------------------------------------------------------------------
C
C     Find Knights Tours.
C
C     Using Warnsdorffs 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' knights 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-----------------------------------------------------------------------
Output:

$ echo "c5 2 T" | ./knights_tour

 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

Fortran 95

Works with: gfortran version 11.2.1
Translation of: ATS
!-----------------------------------------------------------------------
!
!     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

!-----------------------------------------------------------------------
Output:

$ echo "c5 2 T" | ./knights_tour

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

Fortran 2008

Works with: gfortran version 11.2.1

(This one is not a translation of my ATS implementation. I wrote it earlier.)

!!!
!!! 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

$ ./knights_tour a1 b2 c3

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

Go

Warnsdorf's rule

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
}
Output:
  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

Ant colony

/* 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. */
    
package main

import (
    "fmt"
    "math/rand"
    "sync" 
    "time"
)
    
const boardSize = 8 
const nSquares = boardSize * boardSize
const completeTour = nSquares - 1
    
// task input: starting square.  These are 1 based, but otherwise 0 based
// row and column numbers are used througout the program.
const rStart = 2
const cStart = 3

// pheromone representation read by ants
var tNet = make([]float64, nSquares*8)

// row, col deltas of legal moves
var drc = [][]int{{1, 2}, {2, 1}, {2, -1}, {1, -2},
    {-1, -2}, {-2, -1}, {-2, 1}, {-1, 2}}

// get square reached by following edge k from square (r, c)
func dest(r, c, k int) (int, int, bool) {
    r += drc[k][0]
    c += drc[k][1]
    return r, c, r >= 0 && r < boardSize && c >= 0 && c < boardSize
}

// struct represents a pheromone amount associated with a move
type rckt struct {
    r, c, k int
    t       float64
}

func main() {
    fmt.Println("Starting square:  row", rStart, "column", cStart)
    // initialize board
    for r := 0; r < boardSize; r++ {
        for c := 0; c < boardSize; c++ {
            for k := 0; k < 8; k++ { 
                if _, _, ok := dest(r, c, k); ok {
                    tNet[(r*boardSize+c)*8+k] = 1e-6
                }
            }
        }
    }

    // waitGroups for ant release clockwork
    var start, reset sync.WaitGroup
    start.Add(1)
    // channel for ants to return tours with pheremone updates
    tch := make(chan []rckt)

    // create an ant for each square
    for r := 0; r < boardSize; r++ {
        for c := 0; c < boardSize; c++ {
            go ant(r, c, &start, &reset, tch)
        }
    }

    // accumulator for new pheromone amounts
    tNew := make([]float64, nSquares*8)

    // each iteration is a "cycle" as described in the paper
    for {
        // evaporate pheromones
        for i := range tNet {
            tNet[i] *= .75
        }

        reset.Add(nSquares) // number of ants to release
        start.Done()        // release them
        reset.Wait()        // wait for them to begin searching
        start.Add(1)        // reset start signal for next cycle

        // gather tours from ants
        for i := 0; i < nSquares; i++ {
            tour := <-tch
            // watch for a complete tour from the specified starting square
            if len(tour) == completeTour &&
                tour[0].r == rStart-1 && tour[0].c == cStart-1 {

                // task output:  move sequence in a grid.
                seq := make([]int, nSquares)
                for i, sq := range tour {
                    seq[sq.r*boardSize+sq.c] = i + 1
                }
                last := tour[len(tour)-1]
                r, c, _ := dest(last.r, last.c, last.k)
                seq[r*boardSize+c] = nSquares
                fmt.Println("Move sequence:")
                for r := 0; r < boardSize; r++ {
                    for c := 0; c < boardSize; c++ {
                        fmt.Printf(" %3d", seq[r*boardSize+c])
                    }
                    fmt.Println()
                }
                return // task only requires finding a single tour
            }
            // accumulate pheromone amounts from all ants
            for _, move := range tour {
                tNew[(move.r*boardSize+move.c)*8+move.k] += move.t
            }
        }
    
        // update pheromone amounts on network, reset accumulator
        for i, tn := range tNew {
            tNet[i] += tn
            tNew[i] = 0
        }
    }
}   

type square struct {
    r, c int
}

func ant(r, c int, start, reset *sync.WaitGroup, tourCh chan []rckt) {
    rnd := rand.New(rand.NewSource(time.Now().UnixNano()))
    tabu := make([]square, nSquares)
    moves := make([]rckt, nSquares)
    unexp := make([]rckt, 8)
    tabu[0].r = r
    tabu[0].c = c

    for {
        // cycle initialization
        moves = moves[:0]
        tabu = tabu[:1]
        r := tabu[0].r
        c := tabu[0].c

        // wait for start signal
        start.Wait()
        reset.Done()

        for {
            // choose next move
            unexp = unexp[:0]
            var tSum float64
        findU:
            for k := 0; k < 8; k++ {
                dr, dc, ok := dest(r, c, k)
                if !ok {
                    continue
                }
                for _, t := range tabu {
                    if t.r == dr && t.c == dc {
                        continue findU
                    }
                }
                tk := tNet[(r*boardSize+c)*8+k]
                tSum += tk
                // note:  dest r, c stored here
                unexp = append(unexp, rckt{dr, dc, k, tk})
            }
            if len(unexp) == 0 {
                break // no moves
            }
            rn := rnd.Float64() * tSum
            var move rckt
            for _, move = range unexp {
                if rn <= move.t {
                    break
                }
                rn -= move.t
            }

            // move to new square
            move.r, r = r, move.r
            move.c, c = c, move.c
            tabu = append(tabu, square{r, c})
            moves = append(moves, move)
        }

        // compute pheromone amount to leave
        for i := range moves {
            moves[i].t = float64(len(moves)-i) / float64(completeTour-i)
        }

        // return tour found for this cycle
        tourCh <- moves
    }
}

Output:

Starting square:  row 2 column 3
Move sequence:
  64  33  36   3  54  49  38  51
  35   4   1  30  37  52  55  48
  32  63  34  53   2  47  50  39
   5  18  31  46  29  20  13  56
  62  27  44  19  14  11  40  21
  17   6  15  28  45  22  57  12
  26  61   8  43  24  59  10  41
   7  16  25  60   9  42  23  58

Haskell

import Data.Bifunctor (bimap)
import Data.Char (chr, ord)
import Data.List (intercalate, minimumBy, sort, (\\))
import Data.Ord (comparing)
import Control.Monad (join)

---------------------- KNIGHT'S TOUR ---------------------

type Square = (Int, Int)

knightTour :: [Square] -> [Square]
knightTour moves
  | null possibilities = reverse moves
  | otherwise = knightTour $ newSquare : moves
  where
    newSquare =
      minimumBy
        (comparing (length . findMoves))
        possibilities
    possibilities = findMoves $ head moves
    findMoves = (\\ moves) . knightOptions

knightOptions :: Square -> [Square]
knightOptions (x, y) =
  knightMoves >>= go . bimap (+ x) (+ y)
  where
    go move
      | uncurry (&&) (both onBoard move) = [move]
      | otherwise = []

knightMoves :: [(Int, Int)]
knightMoves =
  ((>>=) <*> (\deltas n -> deltas >>= go n)) [1, 2, -1, -2]
  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
Output:
e5 -> f7 -> h8 -> g6 -> h4 -> g2 -> e1 -> f3
g1 -> h3 -> g5 -> h7 -> f8 -> d7 -> b8 -> a6
b4 -> a2 -> c1 -> d3 -> b2 -> d1 -> f2 -> h1
g3 -> h5 -> g7 -> e8 -> f6 -> g8 -> h6 -> g4
h2 -> f1 -> e3 -> f5 -> e7 -> c8 -> a7 -> c6
d8 -> b7 -> a5 -> b3 -> a1 -> c2 -> d4 -> e2
f4 -> e6 -> c5 -> a4 -> b6 -> a8 -> c7 -> d5
c3 -> e4 -> d6 -> b5 -> a3 -> b1 -> d2 -> c4

Icon and Unicon

This implements Warnsdorff's algorithm using unordered sets.

  • The board must be square (it has only been tested on 8x8 and 7x7). Currently the maximum size board (due to square notation) is 26x26.
  • Tie breaking is selectable with 3 variants supplied (first in list, random, and Roth's distance heuristic).
  • A debug log can be generated showing the moves and choices considered for tie breaking.

The algorithm doesn't always generate a complete tour.

link printf

procedure main(A)
ShowTour(KnightsTour(Board(8)))
end 

procedure KnightsTour(B,sq,tbrk,debug)  #: Warnsdorff’s algorithm

/B := Board(8)                          # create 8x8 board if none given
/sq := ?B.files || ?B.ranks             # random initial position (default)
sq2fr(sq,B)                             # validate initial sq
if type(tbrk) == "procedure" then  
   B.tiebreak := tbrk                   # override tie-breaker
if \debug then write("Debug log : move#, move : (accessibility) choices")

choices := []                           # setup to track moves and choices
every (movesto := table())[k := key(B.movesto)] := copy(B.movesto[k])  

B.tour := []                            # new tour
repeat {
   put(B.tour,sq)                       # record move
    
   ac := 9                              # accessibility counter > maximum
   while get(choices)                   # empty choices for tiebreak
   every delete(movesto[nextsq := !movesto[sq]],sq) do {  # make sq unavailable
      if ac >:= *movesto[nextsq] then   # reset to lower accessibility count
         while get(choices)             # . re-empty choices      
      if ac = *movesto[nextsq] then
         put(choices,nextsq)            # keep least accessible sq and any ties
      } 
   
   if \debug then {                     # move#, move, (accessibility), choices
      writes(sprintf("%d. %s : (%d) ",*B.tour,sq,ac)) 
      every writes(" ",!choices|"\n")                 
      }
   sq := B.tiebreak(choices,B) | break  # choose next sq until out of choices
   }
return B  
end

procedure RandomTieBreaker(S,B)                   # random choice
return ?S                   
end

procedure FirstTieBreaker(S,B)                    # first one in the list
return !S                   
end

procedure RothTieBreaker(S,B)                    # furthest from the center
if *S = 0 then fail                              # must fail if []
every fr := sq2fr(s := !S,B) do {
   d := sqrt(abs(fr[1]-1 - (B.N-1)*0.5)^2 + abs(fr[2]-1 - (B.N-1)*0.5)^2)
   if (/md := d) | ( md >:= d) then msq := s     # save sq 
   }
return msq  
end

record board(N,ranks