
On Sat, Feb 23, 2013 at 04:39:53PM +0100, Emanuel Koczwara wrote:
Hi,
Note: Following code is a solution for a problem from hackerrank.com (Category: Artifical Intelligence / Single Player Games / Bot saves princess).
Looks pretty good overall. One note is that using lists of lists for Grid and Heuristic will be slow, especially Heuristic since you do lots of repeated lookups. For small grids it really doesn't make much difference, but if you wanted to run it on larger grids you might notice. Since both the Grid and Heuristic values are created once and then used in a read-only fasion, this is a perfect opportunity to use arrays: see http://hackage.haskell.org/packages/archive/array/latest/doc/html/Data-Array... Using read-only arrays is really quite simple (as opposed to read/write arrays which require a monad of some sort). -Brent
Here is my first Haskell code! Short explanation of the problem: it's standard path finding problem, we have a matrix where 'm' denotes the bot, 'p' denotes the princess and '-' is for empty space.
Sample input (grid size followed by the grid itself, where each row is separated by new line):
3 --- -m- p--
Sample output:
DOWN LEFT
Here is the code:
module Main where
import Data.List import Data.Maybe
type Size = Int
type Grid = [String]
type Path = [Move]
type Heuristic = [[Int]]
type Position = (Int,Int)
data Move = LEFT | RIGHT | UP | DOWN deriving Show
getSize :: IO Size getSize = readLn
getGrid :: Size -> IO Grid getGrid s = sequence $ replicate s getLine
getHeuristic :: Size -> Position -> Heuristic getHeuristic s p = map (getHeuristic' s p) [0..s-1]
getHeuristic' :: Size -> Position -> Int -> [Int] getHeuristic' s p y = map (getHeuristic'' p y) [0..s-1]
getHeuristic'' :: Position -> Int -> Int -> Int getHeuristic'' (x2, y2) y1 x1 = abs (x1 - x2) + (abs (y1 - y2))
getPos :: Char -> Size -> Grid -> Position getPos c s g = (i `mod` s, i `div` s) where g' = concat g i = fromJust $ elemIndex c g'
getSteps :: Size -> Heuristic -> Position -> Position -> Path getSteps s h b p | b == p = [] | otherwise = let (m,b') = getStep s h b in m : (getSteps s h b' p)
getStep :: Size -> Heuristic -> Position -> (Move,Position) getStep s h b = head $ sortBy compareCost (getAvailableSteps s h b) where compareCost (_,(x1,y1)) (_,(x2,y2)) = compare (h !! y1 !! x1) (h !! y2 !! x2)
getAvailableSteps :: Size -> Heuristic -> Position -> [(Move,Position)] getAvailableSteps s h (x,y) = up ++ down ++ left ++ right where up = if y > 0 then [(UP, (x, y - 1))] else [] down = if y < (s - 1) then [(DOWN, (x, y + 1))] else [] left = if x > 0 then [(LEFT, (x - 1, y))] else [] right = if x < (s - 1) then [(RIGHT, (x + 1, y))] else []
main :: IO () main = do size <- getSize grid <- getGrid size let botPos = getPos 'm' size grid princessPos = getPos 'p' size grid heuristic = getHeuristic size princessPos result = getSteps size heuristic botPos princessPos mapM_ print result
Please point out all my mistakes.
Emanuel
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners