Programming C, C++, Java, PHP, Ruby, Turing, VB
Computer Science Canada 
Programming C, C++, Java, PHP, Ruby, Turing, VB  

Username:   Password: 
 RegisterRegister   
 For templest :)
Index -> General Programming
View previous topic Printable versionDownload TopicSubscribe to this topicPrivate MessagesRefresh page View next topic
Author Message
wtd




PostPosted: Tue Mar 15, 2005 2:47 am   Post subject: For templest :)

To find the numbers of mines adjacent to letters on a map. Smile

code:
module MineSweeper where

import List
import IO
import Char
import Maybe

data Square = Mine | Safe | Letter Char  deriving (Show, Eq)
type Row = [Square]
type Grid = [Row]

getGrid :: FilePath -> IO Grid
getGrid fileName = do
  contents <- readFile fileName
  let (first:others) = lines contents
  let dimensions     = parseGridDimensions first
  return $ trimGrid dimensions $ createGrid $ others

parseGridDimensions :: Read a => String -> (a, a)
parseGridDimensions input = (n, m)
  where
    [(n, input')] = reads input
    [(m, _)     ] = reads input'

charToSquare :: Char -> Square
charToSquare ch =
  case ch of
    '.' -> Safe
    '*' -> Mine
    n   -> Letter n

createGrid :: [String] -> Grid
createGrid = map (map charToSquare)

trimGrid :: (Int, Int) -> Grid -> Grid
trimGrid (n, m) = map (take m) . take n

findLetters :: (Int, Int) -> Grid -> [(Char, (Int, Int))]
findLetters (_,_) [] = []
findLetters (n, m) ([]:r) = findLetters (n + 1, 0) r
findLetters coords@(n, m) ((x:xs):r) =
  case x of
    Letter ch -> (ch, coords) : findLetters (n, m + 1) (xs:r)
    _         -> findLetters (n, m + 1) (xs:r)

lettersPresent :: Grid -> [Char]
lettersPresent = fst . unzip . findLetters (0, 0)

adjacentCoords :: (Int, Int) -> (Int, Int) -> [(Int, Int)]
adjacentCoords s@(n, m) s'@(n', m') =
  [(n'', m'') | n'' <- [n' - 1 .. n' + 1],
                m'' <- [m' - 1 .. m' + 1],
                (n'', m'') /= (n', m') && inBounds s (n'', m'')]

getGridDimensions :: Grid -> (Int, Int)
getGridDimensions grid@(x:_) = (length grid, length x)

adjacentSquares :: (Int, Int) -> Grid -> [Square]
adjacentSquares s@(n, m) grid =
  map (`squareAt` grid) $ adjacentCoords (getGridDimensions grid) s

inBounds :: (Int, Int) -> (Int, Int) -> Bool
inBounds (n, m) (n', m') =
  n' >= 0 && n' < n && m' >= 0 && m' < m
   
squareAt :: (Int, Int) -> Grid -> Square
squareAt (n, m) grid = grid !! n !! m

countAdjacentMines :: (Int, Int) -> Grid -> Int
countAdjacentMines coords =
  length . filter (Mine ==) . adjacentSquares coords

getAdjacentMineCounts :: FilePath -> IO [(Char, Int)]
getAdjacentMineCounts fileName = do
  grid <- getGrid fileName
  let letterMap = findLetters (0, 0) grid
  let letters   = lettersPresent grid
  return [(l, countAdjacentMines (fromJust $ lookup l letterMap) grid) | l <- letters]
Sponsor
Sponsor
Sponsor
sponsor
Tony




PostPosted: Tue Mar 15, 2005 9:24 am   Post subject: (No subject)

what happened to using syntax= tags? What language is that in Confused
rizzix




PostPosted: Tue Mar 15, 2005 11:23 am   Post subject: (No subject)

"For Templest" what the heck? did someone edit ur post or...

anywayz i got the entire game here: http://www.compsci.ca/v2/viewtopic.php?p=74606#74606
wtd




PostPosted: Tue Mar 15, 2005 1:46 pm   Post subject: (No subject)

rizzix wrote:
"For Templest" what the heck? did someone edit ur post or...

anywayz i got the entire game here: http://www.compsci.ca/v2/viewtopic.php?p=74606#74606


We were having a discussion in IRC yesterday and the problem was:

given an input file like:

code:
4 4
..*.
A...
..B*
C*..


Find the number of mines, denoted by * surrounding each of the squares denoted by letters.

He was interested in seeing what my answer would be.

Oh, and Tony, it's in Haskell, so there's no syntax highlighting available.
wtd




PostPosted: Tue Mar 15, 2005 5:58 pm   Post subject: (No subject)


  1. Start a new module named MineSweeper.

    code:
    module MineSweeper where


  2. Import a few useful modules.

    code:
    import List
    import IO
    -- I realized this one isn't really necessary:
    -- import Char
    import Maybe


  3. Create a new data type called Square. Square can be represented by a Mine, a Safe spot, or a Letter representing some other character. Derive Show and Eq so they can be stringified for printing, and so that squares can be compared for equality.

    code:
    data Square = Mine | Safe | Letter Char deriving (Show, Eq)


  4. Create type Row and type Grid, which are basically just type synonyms for lists of Squares and lists of lists of Squares.

    code:
    type Row = [Square]
    type Grid = [Row]


  5. Get a grid given a FilePath (a String).

    code:
    getGrid :: FilePath -> IO Grid


    To do this, read the file's contents, then use the "lines" function to split that content into lines. Let the first line be called "first" and the rest be called "others." Use parseGridDimensions to parse the first line and get the height and width of the grid. Use createGrid to process the other lines and turn characters into Mine, Safe, or Letter values. Then use trimGrid to remove anything outside the bounds of the dimensions parsed earlier.

    code:
    getGrid fileName = do
      contents <- readFile fileName
      let (first:others) = lines contents
      let dimensions     = parseGridDimensions first
      return $ trimGrid dimensions $ createGrid others


  6. Generic parseGridDimensions function. Take a String and return two readable values. In this case Ints.

    code:
    parseGridDimensions :: Read a => String -> (a, a)


    The reads function parses the desired Int from the input String. We parse once, then parse the String remaining after the first parse.

    code:
    parseGridDimensions input = (n, m)
      where
        [(n, input')] = reads input
        [(m, _)     ] = reads input'


  7. Pretty simple. Takes a Char and converts it to a Square.

    code:
    charToSquare :: Char -> Square


    If ch is '.' return Safe. If ch is '*' then we get Mine. Otherwise we get a Letter value storing the input Char.

    code:
    charToSquare ch =
      case ch of
        '.' -> Safe
        '*' -> Mine
        n   -> Letter n


  8. Process a list of Strings into a Grid.

    code:
    createGrid :: [String] -> Grid


    Do this by mapping "map toSquare" to each String. "map toSquare" applies toSquare to each Char in a String and collects the result.

    The result of running this on "D.*." would be [Letter 'D', Safe, Mine, Safe].

    code:
    createGrid = map (map charToSquare)


  9. Trim unnecessary rows and columns from the Grid.

    code:
    trimGrid :: (Int, Int) -> Grid -> Grid


    Do this by first "take n", which grabs the first n rows from the Grid. Then, for each of those Rows, "take m", which grabs the first m elements in each Row.

    code:
    trimGrid (n, m) = map (take m) . take n


  10. Find all of the letters in the grid and the coordinates at which they're located, starting from some initial set of coordinates (0, 0).

    code:
    findLetters :: (Int, Int) -> Grid -> [(Char, (Int, Int))]


    If the grid to search is empty, then we don't care about the coordinates. Clearly there can be no Letters within.

    code:
    findLetters (_,_) [] = []


    If the first Row in the Grid is empty, continue searching with the remaining Rows. Increment n by 1 and set m to zero to indicates starting again one row down at .

    code:
    findLetters (n, m) ([]:r) = findLetters (n + 1, 0) r


    If the first element in the current Row is a Letter, then append the Char it contains and the current coordinates to the result of finding the latters in the remaining Rows. Increment the column (m) by 1.

    code:
    findLetters coords@(n, m) (((Letter ch):xs):r) =
      (ch, coords) : findLetters (n, m + 1) (xs:r)


    If the first element in the current grid is anything other than a letter, find the Letters in the remaining part of the Grid, incrementing the column count by 1.

    code:
    findLetters (n, m) ((_:xs):r) =
      findLetters (n, m + 1) (xs:r)


  11. Find the Letters present in the Grid.

    code:
    lettersPresent :: Grid -> [Char]


    To do this, first use the above findLetters function to find all of the letters and their coordinates. Then unzip that list, meaning you get two lists: one containing the Letters,and the other containing the coordinates. Use fst to just get the first list.

    code:
    lettersPresent = fst . unzip . findLetters (0, 0)


  12. Find all coordinates adjacent to the input coordinates based on input dimensions for the grid.

    code:
    adjacentCoords :: (Int, Int) -> (Int, Int) -> [(Int, Int)]


    Let n and m be the bounds of the Grid. Let n' and m' be the coordinates of the target. n'' and m'' are each coordinate between n' - 1 and n' + 1 and m' - 1 and m' + 1. Coordinates are only accepted if they do not match the target exactly, and are within the bounds of the Grid.

    code:
    adjacentCoords s@(n, m) s'@(n', m') =
      [(n'', m'') | n'' <- [n' - 1 .. n' + 1],
                    m'' <- [m' - 1 .. m' + 1],
                    (n'', m'') /= s' && inBounds s (n'', m'')]


  13. Get a Grid's dimensions.

    code:
    getGridDimensions :: Grid -> (Int, Int)


    Get the height and width of a Grid by calculating its length and the length of it's first Row.

    code:
    getGridDimensions grid@(x:_) = (length grid, length x)


  14. Collect all adjacent Squares to a set of target coordinates.

    code:
    adjacentSquares :: (Int, Int) -> Grid -> [Square]


    First collect all adjacentCoords. Then, for each of those collect the Square located at them.

    code:
    adjacentSquares s@(n, m) grid =
      map (`squareAt` grid) $ adjacentCoords (getGridDimensions grid) s


  15. Determine if a set of coordinates is within a set of bounds.

    code:
    inBounds :: (Int, Int) -> (Int, Int) -> Bool


    Let n and m be the bounds of the Grid. Let n' and m' be the coordinates being tested. Pretty easy to understand.

    code:
    inBounds (n, m) (n', m') =
      n' >= 0 && n' < n && m' >= 0 && m' < m


  16. Retrieve a Square at a particular set of coordinates within a Grid.

    code:
    squareAt :: (Int, Int) -> Grid -> Square


    Use the !! operator to do this. Consider "grid !! n !! m" similar to "grid[n][m]" in some other languages.

    code:
    squareAt (n, m) grid = grid !! n !! m


  17. Count adjacent Squares which are Mines.

    code:
    countAdjacentMines :: (Int, Int) -> Grid -> Int


    Find all adjacentSquares, filter it down to just those that are Mines, then count the resulting list.

    code:
    countAdjacentMines coords =
      length . filter (Mine ==) . adjacentSquares coords


  18. Bundle all of it up together to read a file, get the Grid it represents, find the letters within it, then count the mines adjacent to those letters.

    code:
    getAdjacentMineCounts :: FilePath -> IO [(Char, Int)]
    getAdjacentMineCounts fileName = do
      grid <- getGrid fileName
      let letterMap = findLetters (0, 0) grid
      let letters   = lettersPresent grid
      return [(l, countAdjacentMines (fromJust $ lookup l letterMap) grid) | l <- letters]
Display posts from previous:   
   Index -> General Programming
View previous topic Tell A FriendPrintable versionDownload TopicSubscribe to this topicPrivate MessagesRefresh page View next topic

Page 1 of 1  [ 5 Posts ]
Jump to:   


Style:  
Search: