遍历游戏状态 space :搜索越多,结果越差

Traversing game state space : more search leads to bad results

我从 codereview 交叉发布这个问题,因为我发现它没有响应。

此问题可在 hackerrank ai 找到。我不是在寻求解决方案,而是试图找出我的策略或代码有什么问题。

我正在尝试解决一个我认为是 TSP on a 2-D grid 的问题。所以,我正在努力获得最好的结果。但是,向前看 1 步比向前看 2 步产生更好的结果。

问题是我必须以最少的移动次数清理二维网格上的脏块 UP, DOWN, LEFT, RIGHT, CLEAN

另一件重要的事情是我采取行动,然后 restarted 处理新的网格状态和我的新位置。所以我必须再次 运行 算法。这也意味着我必须避免陷入循环,这在单进程的情况下很容易避免,但在进程的多个实例的情况下需要通过算法来保证。

简而言之,我只需要next_move在我的过程中。

所以基本策略是找到离我当前位置最近的脏单元格。

为了向前看 1 步,我会做:对于每个脏单元格,找到最接近被占用的脏单元格的脏单元格。对于 2 步,对于每个脏单元格,进行 1 步查找并找到最佳移动。对于多个步骤也是如此。

但是,当我只进行 1 步查找时我得到更高的分数,但 2 步查找时分数较低。分数由 (200 - steps_taken) 计算得出。所以,我认为我的 code/strategy 有问题。

输入格式:

b 表示网格中的机器人。 - 是干净的细胞。 d 是脏单元格。

第一行是机器人位置的一对整数。这使得网格中的 b 变得多余。如果机器人当前站在一个脏单元格上,d 将出现在网格中的那个单元格上。

第二行是网格的尺寸。

第三个输入是行形式的网格。请参阅下面的示例输入。

我的Haskell代码是:

module Main where
import Data.List 
import Data.Function (on)
import Data.Ord

-- slits up a string 
-- ** only used in IO. 
split sep = takeWhile (not . null) . unfoldr (Just . span (/= sep) . dropWhile (== sep))
-- ** only used in IO
getList :: Int -> IO [String]
getList n = if n==0 then return [] else do i <- getLine; is <- getList(n-1); return (i:is)

-- find positions of all dirty cells in the board
getAllDirtyCells :: (Int, Int) -> [String] -> [(Int, Int)]
getAllDirtyCells (h, w) board = [(x, y) | x <- [0..(h-1)], y <- [0..(w - 1)]
                               , ((board !! x) !! y) == 'd']

-- finally get the direction to print ;
-- first argument is my-position and second arg is next-position.
getDir :: (Int, Int) -> (Int, Int) -> String
getDir (x, y) (a, b) | a == x && y == b = "CLEAN"
                     | a < x = "UP"
                     | x == a && y < b = "RIGHT"
                     | x == a = "LEFT"
                     | otherwise = "DOWN"

-- only used in IO for converting strin gto coordinate.
getPos :: String -> (Int, Int)
getPos pos = let a = map (\x -> read x :: Int) (words pos)
             in ((a !! 0) , (a !! 1))


-- manhattan Distance :  sum of difference of x and y coordinates
manhattanDis :: (Int, Int) -> (Int, Int) -> Int
manhattanDis (a, b) (x, y) = (abs (a - x) + (abs (b - y)))

-- sort the positions from (botX, botY) position on manhattan-distance.
-- does not returns the cost.
getSortedPos :: (Int, Int) -> [(Int, Int)] -> [(Int, Int)]
getSortedPos (botX, botY) points = map (\x -> (snd x)) $ 
                                   sortBy (comparing fst)  -- compare on the basis of cost.
                                              [(cost, (a, b)) | 
                                                     (a, b) <- points, 
                                                     cost <- [manhattanDis (a,b) (botX, botY)]]
-- exclude the point `v` from the list `p`
excludePoint :: (Ord a) => [a] -> a -> [a]
excludePoint [] _ = []
excludePoint p v = [x | x <- p , x /= v]

-- playGame uses the nearest-node-policy. 
-- we start playing game when we are not going more deep. 
-- more about that in findBestMove
-- game is to reduce the nodes to one node with the total cost ;
-- reduction : take the next shortest node from the current-node.
playGame :: (Int, Int) -> [(Int, Int)] -> [(Int, Int)]
playGame pos [] = [pos]
playGame startPos points = let nextPos = (head (getSortedPos startPos points))
                           in (nextPos : playGame nextPos (excludePoint points nextPos))

-- sum up cost of all the points as they occur.
findCost :: [(Int, Int)] -> Int
findCost seq = sum $ map (\x -> (manhattanDis (fst x) (snd x))) $ zip seq (tail seq)

-- find the position which gives the smallest overall cost.
smallestCostMove :: [(Int, (Int, Int))] -> (Int, (Int, Int))
smallestCostMove [] = (0, (100, 100))
smallestCostMove [x] = x
smallestCostMove (x:y:xs) | (fst x) <= (fst y) = smallestCostMove (x : xs)
                          | otherwise = smallestCostMove (y : xs)                      

-- This is actual move-finder. It does the lookups upto `level` deep.
-- from startpoint, take each point and think it as starting pos and play the game with it.
-- this helps us in looking up one step.
-- when level is 0, just use basic `playGame` strategy. 
findBestMove :: (Int, Int) -> [(Int, Int)] -> Int -> (Int, (Int, Int))
findBestMove startPos  points level 
                                    -- returns the move that takes the smallest cost i.e. total distances.
                                    | level == 0 = smallestCostMove $ 
                                                     -- return pair of (cost-with-node-x-playGame, x)
                                                     map (\x -> (findCost (startPos : (x : (playGame x (excludePoint points x)))), 
                                                                x)) 
                                                         points
                                    | otherwise  = smallestCostMove $ 
                                                     map (\x -> 
                                                           -- return pair of (cost-with-node-x, x)
                                                            ( (findCost (startPos : [x])) + 
                                                              -- findBestMove returns the pair of (cost, next-move-from-x)
                                                              (fst (findBestMove x (excludePoint points x) (level - 1))),
                                                             x)) 
                                                         points

-- next_move is our entry point. go only 2 level deep for now, as it can be time-expensive.
next_move :: (Int, Int) -> (Int, Int) -> [String] ->  String
next_move pos dim board = let boardPoints = (getAllDirtyCells dim board)
                              numPoints = (length boardPoints)
                              -- ** Important : This is my question :
                              -- change the below `deep` to 1 for better results. 
                              deep = if (numPoints > 3) 
                                     then 2 
                                     else if (numPoints == 1) 
                                          then 1 
                                          else (numPoints - 1)                                
                          in if pos `elem` boardPoints 
                             then getDir pos pos
                             else getDir pos $ snd $ findBestMove pos boardPoints deep


main :: IO()
main = do
    -- Take input
   b <- getLine
   i <- getLine
   -- bot contains (Int, Int) : my-coordinates. like (0,0)
   let botPos = (read $ head s::Int,read $ head $ tail s::Int) where s = split (' ') b
   -- dimOfBoard contains dimension of board like (5,5)
   let dimOfBoard = (read $ head s::Int, read $ head $ tail s::Int) where s = split (' ') i
   board <- getList (fst dimOfBoard)
   putStrLn $ next_move botPos dimOfBoard board

我控制 deep 我可以如何使用变量 deep

样板为:

0 0
5 5
b---d
-d--d
--dd-
--d--
----d

一共有三个答案:

输出 :

RIGHT or DOWN or LEFT

重要: 再次使用 new boardmy bot new position 调用新进程,直到我清除所有脏单元格。

我做错了什么?

经过大量工作后,我找到了一个确定最佳路径的示例 通过 findBestMove 在级别 1 returns 比调用时更糟糕的路径 级别设置为 0:

 points = [(6,8),(9,7),(9,4),(4,10),(4,6),(7,10),(5,7),(2,4),(8,8),(6,5)]
 start: (1,10)

  level = 0:
    cost: 31
    path: [(1,10),(4,10),(7,10),(5,7),(6,8),(8,8),(9,7),(9,4),(6,5),(4,6),(2,4)]

  level = 1:
    cost: 34
    path: [(1,10),(2,4),(6,5),(6,8),(5,7),(4,6),(4,10),(7,10),(8,8),(9,7),(9,4)]

问题是 playGame 只探索了可能的最佳着法之一。 我发现如果你探索所有的,你的算法会变得更稳定 最好的可能动作是这样的:

 greedy start [] = 0
 greedy start points =
   let sorted@((d0,_):_) = sort [ (dist start x, x) | x <- points ]
       nexts = map snd $ takeWhile (\(d,_) -> d == d0) sorted
   in d0 + minimum [ greedy n (delete n points)  | n <- nexts ]

这里greedy结合了findCostplayGame。通过只看 排序列表 playGame 中的第一步取决于排序算法 以及点的顺序。

你也可以这样写bestMove

 bestMove _ start [] = (0,start)
 bestMove depth start points
   | depth == 0 = minimum [ (d0+d,x) | x <- points,
                              let d0 = dist start x,
                              let d = greedy x (delete x points) ]
   | otherwise  = minimum [ (d0+d,x) | x <- points,
                              let d0 = dist start x,
                              let (d,_) = bestMove (depth-1) x (delete x points  ) ]

这更清楚地突出了两种情况之间的对称性。

这是我用来查找和显示上述板的最佳路径的代码: http://lpaste.net/121294 要使用它,只需将您的代码放入名为 Ashish.

的模块中

最后我的直觉告诉我,你的方法可能不是一个好的方法 解决问题。你在做什么类似于 A*-algorithm playGame 扮演启发式函数的角色。然而, 为了使 A* 起作用,启发式函数不应过高估计 最短的距离。但是 playGame 总是给你一个上限 最短的距离。无论如何 - 这是需要考虑的事情。