aoc2021/Day9.hs

34 lines
1.2 KiB
Haskell

module Day9 where
import System.IO (openFile, IOMode (ReadMode), hClose, hGetContents)
import Data.Char (digitToInt)
columns :: String -> Int
columns str = maximum $ map length $ lines str
indexOr :: Int -> [a] -> a -> a
indexOr i list j
| i `elem` [0..length list] = list !! i
| otherwise = j
compNeighbors :: [Int] -> Int -> Int -> [Int]
compNeighbors ints i width = [middle | all (middle <) [left, right, top, bottom]]
where middle = ints !! i
left = getLeft (i - 1)
right = getRight (i + 1)
top = indexOr (i - width) ints 9
bottom = indexOr (i + width) ints 9
-- make sure that we aren't wrapping around the line edge
getLeft x = if (i `mod` width) == 0 then 9 else indexOr (x :: Int) ints 9
getRight x = if (i `mod` width) == (width - 1) then 9 else indexOr (x :: Int) ints 9
main :: IO ()
main = do
input <- openFile "inputs/9.txt" ReadMode
contents <- hGetContents input
let width = columns contents
let ints = digitToInt <$> concat (lines contents)
print . sum . map ((+1) . head) . filter (/= []) $ [compNeighbors ints x width | x <- [0..length ints - 1]]
hClose input