I don’t have a fancy summary for today’s challenge: really, all that had to be done was implement. This post is a literate Haskell program.
{-# LANGUAGE LambdaCase #-}
import Data.Foldable (foldl')
import Data.Set (Set,member,insert,delete)
import qualified Data.Set as Set
The puzzle input is provided as concatenated hex-grid steps. The first thing to do is split them up for easier consumption. Luckily enough, they form a valid prefix code, so I can greedily process and decode them.
splitDirs :: String -> [Dir]
= []
splitDirs [] 'e': ds) = E : splitDirs ds
splitDirs ('s':'e':ds) = SE : splitDirs ds
splitDirs ('s':'w':ds) = SW : splitDirs ds
splitDirs ('w': ds) = W : splitDirs ds
splitDirs ('n':'w':ds) = NW : splitDirs ds
splitDirs ('n':'e':ds) = NE : splitDirs ds splitDirs (
Next I need to recognize which paths lead up to the same tile so I can count it as flipped back instead of count both as flipped once. There are multiple ways to do this. I just introduced a coordinate pair in a system where they’d uniquely identify a tile. (the “odd-r” one, except I order them row first)
type Pos = (Int,Int)
data Dir = E | SE | SW | W | NW | NE deriving (Enum,Bounded)
Now to write the walking function once and for all. This is the most
likely place to trip. Straight east/west movement is easy enough to
write. The others… need a bit of thought. Simple checks include:
north/south symmetry says the j parameter must be the same between
Nx
and Sx
; east/west symmetry says
xE
should be one more than xW
on the j dimension; the row offset rule
says moving vertically from an even row should result in one less than
moving from an odd row.
walk :: Pos -> Dir -> Pos
= \case
walk (i,j) E -> (i ,j+1)
SE | even i -> (i+1,j )
| odd i -> (i+1,j+1)
SW | even i -> (i+1,j-1)
| odd i -> (i+1,j )
W -> (i ,j-1)
NW | even i -> (i-1,j-1)
| odd i -> (i-1,j )
NE | even i -> (i-1,j )
| odd i -> (i-1,j+1)
With this out of the way, I can summarize a path as a position.
type Path = [Dir]
pathToPos :: Path -> Pos
= foldl' walk (0,0) pathToPos
This lets me maintain a set of flipped-to-black tiles.
type TileSet = Set Pos
flipTiles :: [Pos] -> TileSet
= foldl' xorInsert Set.empty flipTiles
Using a small helper to flip a set element.1
xorInsert :: Ord a => Set a -> a -> Set a
| member e s = delete e s
xorInsert s e | otherwise = insert e s
Surprise! Part 2 is a cellular automaton!
It doesn’t really have anything specific going for it, I can re-use my function from day 17 directly:
step :: Conway v => Env v -> Env v = foldMap life (activeCubes <> fringe) where step activeCubes = foldMap neighbors activeCubes fringe = case rule (isActive cube) (countNeighbors cube) of life cube True -> singleton cube False -> mempty = cube `member` activeCubes isActive cube = length . Set.filter isActive . neighbors countNeighbors
Mmm… maybe I’ll edit it just a bit.
step :: TileSet -> TileSet
= foldMap life (blackTiles <> fringe) where
step blackTiles = foldMap neighbors blackTiles
fringe = case rule (isActive cube) (countNeighbors cube) of
life cube True -> Set.singleton cube
False -> mempty
= cube `member` blackTiles
isActive cube = length . Set.filter isActive . neighbors countNeighbors
Much better; I hope you didn’t blink. I’ll still need to transcribe the rule from the statement…
rule :: Bool -> Int -> Bool
True = (`elem` [1,2])
rule False = (== 2) rule
…and the neighborhood function,
neighbors :: Pos -> Set Pos
= Set.fromList $ walk p <$> allDirs neighbors p
…using the usual universe
helper.
allDirs :: [Dir]
= [minBound..maxBound] allDirs
And… that’s it! Here’s the main
wrapper for
completeness.
main :: IO ()
= do
main <- map splitDirs . lines <$> readFile "day24.in"
input let tiling = flipTiles $ pathToPos <$> input
print $ Set.size tiling
print $ Set.size $ iterate step tiling !! 100
This concludes today’s solution. I’m afraid there wasn’t much to learn from it, but at least I can demonstrate the pieces fit together nicely.
See you soon!