Search code examples
loopshaskellknights-tour

Knights tour in haskell getting a loop


I'm in the process of coding the knight's tour function, and I'm as far as this where I'm getting an infinte loop in my ghci:

type Field = (Int, Int)

nextPositions:: Int -> Field -> [Field]
nextPositions n (x,y) = filter onBoard  
    [(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)]  
    where onBoard (x,y) = x `elem` [1..n] && y `elem` [1..n]

type Path = [Field]

knightTour :: Int -> Field -> [Path]
knightTour n start = [posi:path | (posi,path) <- tour (n*n)]
                         where tour 1 = [(start, [])]
                               tour k = [(posi', posi:path) | (posi, path) <- tour (k-1), posi' <- (filter (`notElem` path) (nextPositions n posi))]

F.e. knightTour 10 (4,4) does not give an output! Any advise?


Solution

  • I think one of the main problems is checking if you have visited a square. This takes too much time. You should look for a data structure that makes that more efficient.

    For small boards, for example up to 8×8, you can make use of a 64-bit integer for that. A 64-bit can be seen as 64 booleans that each can represent whether the knight already has visited that place.

    we thus can implement this with:

    {-# LANGUAGE BangPatterns #-}
    
    import Data.Bits(testBit, setBit)
    import Data.Word(Word64)
    
    testPosition :: Int -> Word64 -> (Int, Int) -> Bool
    testPosition !n !w (!r, !c) = testBit w (n*r + c)
    
    setPosition :: Int -> (Int, Int) -> Word64 -> Word64
    setPosition !n (!r, !c) !w = setBit w (n*r + c)
    
    nextPositions :: Int -> Word64 -> (Int, Int) -> [(Int, Int)]
    nextPositions !n !w (!x, !y) = [ c
      | c@(x', y') <- [(x-1,y-2), (x-1,y+2), (x+1,y-2), (x+1,y+2), (x-2,y-1), (x-2,y+1), (x+2,y-1), (x+2,y+1)]
      , x' >= 0
      , y' >= 0
      , x' < n
      , y' < n
      , not (testPosition n w c)
      ]
    
    knightTour :: Int -> (Int, Int) -> [[(Int, Int)]]
    knightTour n p0 = go (n*n-1) (setPosition n p0 0) p0
        where go 0 _ _ = [[]]
              go !k !w !ps = [
                  (ps':rs)
                | ps' <- nextPositions n w ps
                , rs <- go (k-1) (setPosition n ps' w) ps'
                ]
    
    main = print (knightTour 6 (1,1))
    

    If I compile this with the -O2 flag and run this locally for a 5×5 board where the knight starts at (1,1), all the solutions are generated in 0.32 seconds. For a 6×6 board, it takes 2.91 seconds to print the first solution, but it takes forever to find all solutions that start at (1,1). For an 8×8 board, the first solution was found in 185.76 seconds:

    [(0,3),(1,5),(0,7),(2,6),(1,4),(0,2),(1,0),(2,2),(3,0),(4,2),(3,4),(4,6),(5,4),(6,2),(5,0),(3,1),(2,3),(3,5),(2,7),(0,6),(2,5),(1,3),(0,1),(2,0),(3,2),(2,4),(0,5),(1,7),(3,6),(4,4),(5,6),(7,7),(6,5),(7,3),(6,1),(4,0),(5,2),(7,1),(6,3),(7,5),(6,7),(5,5),(4,7),(6,6),(7,4),(5,3),(7,2),(6,0),(4,1),(3,3),(2,1),(0,0),(1,2),(0,4),(1,6),(3,7),(4,5),(5,7),(7,6),(6,4),(4,3),(5,1),(7,0)]
    

    It is however not a good idea to solve this with a brute force approach. If we assume an average branching factor of ~6 moves, then for a 6×6 board, we have already 1.031×1028 possible sequences we have to examine for a 6×6 board.

    It is better to work with a divide and conquer approach. It is easy to split a board like 8×8 into four 4×4 boards. Then you determine places where you can hop from one board to another, and then you solve the subproblems for a 4×4 board. For small boards, you can easily store the solutions to go from any square to any other square on a 4×4 board, and then reuse these for all quadrants, so you save computational effort, by not calculating this a second time, especially since you do not need to store symmetrical queries multiple times. If you know how to go from (1,0) to (2,3) on a 4×4 board, you can easily use this to go from (3,0) to (2,3) on the same board, just by mirroring this.