Day 9
This commit is contained in:
parent
82f519da96
commit
22fb204de0
|
@ -0,0 +1,34 @@
|
||||||
|
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
|
|
@ -0,0 +1,47 @@
|
||||||
|
module Day9_1 where
|
||||||
|
import System.IO (openFile, IOMode (ReadMode), hClose, hGetContents)
|
||||||
|
import Data.Char (digitToInt)
|
||||||
|
import Data.List (sort)
|
||||||
|
|
||||||
|
-- i gave up on my original solution
|
||||||
|
-- this isn't very original and is influcenced by other people's solutions
|
||||||
|
-- i'm sorry
|
||||||
|
|
||||||
|
columns :: String -> Int
|
||||||
|
columns str = maximum $ map length $ lines str
|
||||||
|
|
||||||
|
xy :: Int -> Int -> [[Int]] -> (Int, Int) -> Int
|
||||||
|
xy w h arr (x, y)
|
||||||
|
| x < 0 || x >= w = 9
|
||||||
|
| y < 0 || y >= h = 9
|
||||||
|
| otherwise = arr !! y !! x
|
||||||
|
|
||||||
|
-- left, right, up, down from current coord
|
||||||
|
neigh :: (Int, Int) -> [(Int, Int)]
|
||||||
|
neigh (x, y) = [(x - 1, y), (x + 1, y), (x, y - 1), (x, y + 1)]
|
||||||
|
|
||||||
|
basin :: Int -> Int -> [[Int]] -> [(Int, Int)] -> [(Int, Int)] -> [(Int, Int)]
|
||||||
|
basin w h ints acc [] = acc
|
||||||
|
basin w h ints acc (x:xs)
|
||||||
|
| pos x == 9 || x `elem` acc = basin w h ints acc xs
|
||||||
|
| otherwise = basin w h ints (x:acc) (xs ++ neigh x)
|
||||||
|
where pos = xy w h ints
|
||||||
|
|
||||||
|
main :: IO ()
|
||||||
|
main = do
|
||||||
|
input <- openFile "inputs/9.txt" ReadMode
|
||||||
|
contents <- hGetContents input
|
||||||
|
|
||||||
|
let ints = map (map digitToInt) $ lines contents
|
||||||
|
|
||||||
|
let width = columns contents
|
||||||
|
let height = length ints
|
||||||
|
|
||||||
|
let coordMap = [ (x, y) | x <- [0..width-1], y <- [0..height-1] ]
|
||||||
|
let pos = xy width height ints
|
||||||
|
|
||||||
|
let lowest = [ coord | coord <- coordMap, and [neighbor > pos coord | neighbor <- pos <$> neigh coord] ]
|
||||||
|
|
||||||
|
print . product . take 3 . reverse . sort $ map (length . basin width height ints [] . pure) lowest
|
||||||
|
|
||||||
|
hClose input
|
Loading…
Reference in New Issue