Commit 74880223 by Stuart Kurtz

Day 11

parent 382124ee
4438624262
6263251864
2618812434
2134264565
1815131247
2612457325
8585767584
7217134556
2825456563
8248473584
\ No newline at end of file
module Main where
import Data.Array
import qualified Data.Set as S
type Position = (Int,Int)
loadArray :: String -> Array Position Int
loadArray s = array bds [ ((cx,rx),read [val])
| (rx,row) <- zip [1..] rows
, (cx,val) <- zip [1..] row
]
where
rows = lines s
nx = length (head rows)
ny = length rows
bds = ((1,1),(nx,ny))
showArray :: Array Position Int -> String
showArray arr = unlines [ [ head . show $ arr ! (x,y)
| x <- [xMin..xMax]
]
| y <- [yMin..yMax]
] where
((xMin,yMin),(xMax,yMax)) = bounds arr
neighbors :: Array Position a -> Position -> [Position]
neighbors arr (x,y) =
[ (x',y')
| x' <- [x-1..x+1], y' <- [y-1..y+1]
, inRange (bounds arr) (x',y')
, (x',y') /= (x,y)
]
step :: (Array Position Int,Int) -> (Array Position Int,Int)
step (as,nflashes) = iter S.empty . incr $ as where
incr = ((+1) <$>)
iter :: S.Set Position -> Array Position Int -> (Array Position Int,Int)
iter hasFlashed arr
| S.null newFlash = (discharge arr,nflashes + S.size hasFlashed)
| otherwise = iter mightFlash $ accum (+) arr
[ (n,1) | p <- S.toList newFlash, n <- neighbors arr p ]
where
mightFlash = S.fromList [ p | p <- range (bounds arr), arr ! p > 9]
newFlash = mightFlash S.\\ hasFlashed
discharge :: Array Position Int -> Array Position Int
discharge = (reset <$>) where
reset v
| v > 9 = 0
| otherwise = v
allDischarged :: Array Position Int -> Bool
allDischarged = all (==0) . elems
main :: IO ()
main = pure ()
main = do
arr <- loadArray <$> readFile "data/energy.txt"
let sync = length . takeWhile (not . allDischarged . fst). iterate step $ (arr,0)
print sync
\ No newline at end of file
5483143223
2745854711
5264556173
6141336146
6357385478
4167524645
2176841721
6882881134
4846848554
5283751526
\ No newline at end of file
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or sign in to comment