Day 14 was a day where I didn't see part 2 coming. Part 1 was a pretty simple simulation, part 2 was … a journey.

Data structures

The robot is a simple record, and I keep all them in a list. Nothing fancy, but I thought that the structure was just over the limit where using lenses was a good idea.

type Position = V2 Int -- x, y

data Robot = Robot { _pos :: Position
                   , _vel :: Position
                   }
  deriving (Show, Eq, Ord)
makeLenses ''Robot

Reading the data was simple, and I also created a quick routine to show the layout of robots.

robotsP = robotP `sepBy` endOfLine
robotP = Robot <$> ("p=" *> posP) <* " " <*> ("v=" *> posP)
posP = V2 <$> signed decimal <* "," <*> signed decimal

showGrid :: [Robot] -> String
showGrid robots = unlines $ fmap (showRow robots) [0..(bounds^._y)-1]
  where showRow robots y = [showCell robots (V2 x y) | x <- [0..(bounds^._x)-1]]
        showCell robots p = if null $ countR robots p then '.' else intToDigit $ length $ countR robots p
        countR robots p = filter (==p) $ fmap (^.pos) robots

Part 1: simulation

The core is the move function, that moves a robot for one second. It's a combination of a step and then the teleport to handle the wrapping.

move :: Robot -> Robot
move = teleport . step 
  where 
    teleport :: Robot -> Robot
    teleport r = r & pos . _x .~ (r ^. pos . _x `mod` bounds ^. _x)
                   & pos . _y .~ (r ^. pos . _y `mod` bounds ^. _y)
    step :: Robot -> Robot
    step r = r & pos .~ (r ^. pos ^+^ r ^. vel)

Calculating the safety factor of a set of robots is also a fairly direct translation of the problem statement (even if I had to be careful about the inequalities).

safetyFactor :: [Robot] -> Int
safetyFactor = product . quadrants 

quadrants :: [Robot] -> [Int]
quadrants robots = [lu, ru, lb, rb]
  where u = filter isUpper robots
        b = filter isLower robots
        lu = length $ filter isLeft u
        ru = length $ filter isRight u
        lb = length $ filter isLeft b
        rb = length $ filter isRight b

isLeft, isRight, isUpper, isLower :: Robot -> Bool
isLeft  robot = robot ^. pos . _x < (bounds ^. _x `div` 2)
isRight robot = robot ^. pos . _x > (bounds ^. _x `div` 2)
isUpper robot = robot ^. pos . _y < (bounds ^. _y `div` 2)
isLower robot = robot ^. pos . _y > (bounds ^. _y `div` 2)

Finally, I do the first hundred steps of simulation.

part1 :: [Robot] -> Int
part1 robots = safetyFactor $ (!! 100) $ iterate (fmap move) robots

Part 2

Part 2 wasn't really a computational problem. There was a good post on Reddit about using the chinese remainder theorem to predict the correct frame, but I couldn't get the numbers to work.

Instead, I did a more prosaic approach. I thought about what was distinctive about pictures of christmas trees, and I thought about the diagonal lines that make up the outline.

Christmas tree from Creazilla, CC0 licence.

I wrote a function that would look for diagonals (from lower-left to upper-right).

diagonals :: (Int, [Robot]) -> (Int, [Position])
diagonals (i, robots) = 
  (i, [ V2 x y 
      | x <- [0..(bounds^._x)-1], y <- [0..(bounds^._y)-1]
      , V2 x y `elem` robotPoss
      , V2 (x-1) (y+1) `elem` robotPoss
      , V2 (x-2) (y+2) `elem` robotPoss
      ] )
  where robotPoss = fmap (^.pos) robots

Then I generated frames and kept the ones with many diagonals.

print $ filter (\(i, ds) -> length ds > 20) $ fmap diagonals $ zip [0..] $ take 10000 $ iterate (fmap move) robots

That told me which frame I needed.

putStrLn $ showGrid $ (!! xxxx) $ iterate (fmap move) robots

And this is the tree.

.1111111111111111111111111111111.
.1.............................1.
.1.............................1.
.1.............................1.
.1.............................1.
.1..............1..............1.
.1.............111.............1.
.1............11111............1.
.1...........1111111...........1.
.1..........111111111..........1.
.1............11111............1.
.1...........1111111...........1.
.1..........111111111..........1.
.1.........11111111111.........1.
.1........1111111111111........1.
.1..........111111111..........1.
.1.........11111111111.........1.
.1........1111111111111........1.
.1.......111111111111111.......1.
.1......11111111111111111......1.
.1........1111111111111........1.
.1.......111111111111111.......1.
.1......11111111111111111......1.
.1.....1111111111111111111.....1.
.1....111111111111111111111....1.
.1.............111.............1.
.1.............111.............1.
.1.............111.............1.
.1.............................1.
.1.............................1.
.1.............................1.
.1.............................1.
.1111111111111111111111111111111.

Addendum

Someone on Reddit pointed out that the part 1 solution was a hint for the part 2 solution. The "safety factor" is minimised when many of the robots are in the same quadrant, and that is when the Christmas tree image appears. Therefore, generating the first ten thousand frames and finding the smallest safety factor will identify the correct frame.

part2 robots = fst $ minimumBy (compare `on` snd) 
                   $ take 10000 
                   $ zip [0..] 
                   $ fmap safetyFactor 
                   $ iterate (fmap move) robots

That takes about half a second to complete.

Code

You can get the code from my locally-hosted Git repo, or from Codeberg.