Skip to content

Instantly share code, notes, and snippets.

@mjgpy3
Last active December 11, 2020 17:39
Show Gist options
  • Save mjgpy3/63a0d6fe011fe84f459cc6a09a106516 to your computer and use it in GitHub Desktop.
Save mjgpy3/63a0d6fe011fe84f459cc6a09a106516 to your computer and use it in GitHub Desktop.
aoc-2020-day11
conway of 2 dimensions
initial state at ./y2020d11.txt
where '.' means 'floor'
and 'L' means 'empty'
and '#' means 'occupied'
cells transition
from empty to occupied if (neighbors occupied) = 0
from occupied to empty if (neighbors occupied) >= 4
otherwise a cell is unchanged
solution
first_repeated_generation
| positions occupied
| count
module Main where
import qualified Data.Map.Strict as M
import qualified Data.Set as S
import Data.Bifunctor
import Control.Monad (guard)
import Data.List (partition)
emptySeats ls = S.fromList $ do
(y, line) <- zip [0..] ls
(x, cell) <- zip [0..] line
guard $ cell == 'L'
pure (x, y)
deltas =
[
(-1, 1),
(0, 1),
(1, 1),
(-1, 0),
(1, 0),
(-1, -1),
(0, -1),
(1, -1)
]
visibleFrom (x, y) seats (maxX, maxY) =
go $ zip deltas $ map (bimap (+ x) (+ y)) deltas
where
go [] = []
go values =
let
inGrid = filter ((\(_, (x, y)) -> x >= 0 && y >= 0 && x <= maxX && y <= maxY)) values
(hits, misses) = partition ((`S.member` seats) . snd) inGrid
in
map snd hits ++ go (map (\(delta@(dx, dy), (x', y')) -> (delta, (dx+x', dy+y'))) misses)
toGrid maxes seats = M.fromList $ do
cell <- S.toList seats
case visibleFrom cell seats maxes of
[] -> []
vs -> [(cell, (False, vs))]
firstStableGeneration grid =
let
next = nextGeneration grid
in
if next == grid
then next
else firstStableGeneration next
where
nextGeneration lastGen = M.fromList $ do
(cell, (occupied, visibleCells)) <- M.toList lastGen
let occupiedVisible = length $ filter fst $ map (lastGen M.!) visibleCells
let setState state = [(cell, (state, visibleCells))]
case (occupied, occupiedVisible) of
(False, 0) -> setState True
(True, count) | count >= 5 -> setState False
_ -> setState occupied
main = do
raw <- lines <$> readFile "./y2020d11.txt"
let maxes = (length (head raw) - 1, length raw - 1)
print $ length $ filter (fst . snd) $ M.toList $ firstStableGeneration $ toGrid maxes $ emptySeats raw
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment