Skip to content

Commit

Permalink
slightly nicer 14
Browse files Browse the repository at this point in the history
  • Loading branch information
glguy committed Dec 15, 2024
1 parent 1a32578 commit 9392ac6
Show file tree
Hide file tree
Showing 2 changed files with 39 additions and 18 deletions.
1 change: 1 addition & 0 deletions solutions/solutions.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -1177,3 +1177,4 @@ executable sln_2024_13
executable sln_2024_14
import: day
main-is: 2024/14.hs
build-depends: containers
56 changes: 38 additions & 18 deletions solutions/src/2024/14.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# Language QuasiQuotes #-}
{-# Language QuasiQuotes, ImportQualifiedPost, LambdaCase, BlockArguments #-}
{-|
Module : Main
Description : Day 14 solution
Expand All @@ -10,33 +10,53 @@ Maintainer : emertens@gmail.com
To find the answer to part 2 I tried a bunch of stuff.
What actually worked was finding pictures with many adjacent
pixels. Since this is just a wild guess I didn't bother
committing it into the repo.
pixels. I then updated my solution to find pictures without
overlapping pixels, which seemed to uniquely identify the answer.
-}
module Main where
module Main (main) where

import Advent (counts, format)
import Advent.Coord (Coord(C), drawCoords, mapCoord, zipCoord)
import Control.Monad (when)
import Data.Foldable (for_)
import Data.Set qualified as Set

room :: Coord
room = C 103 101

main :: IO ()
main =
do input <- [format|2024 14 (p=%d,%d v=%d,%d%n)*|]
print (product (counts (concatMap (toQuad . step 100) input)))
putStrLn (drawCoords (map (step 7051) input))

toQuad :: Coord -> [Int]
toQuad (C y x)
| x < midX, y < midY = [1]
| x > midX, y < midY = [2]
| x < midX, y > midY = [3]
| x > midX, y > midY = [4]
| otherwise = []
print (product (counts (concatMap (toQuad . runBot 100) input)))

-- search for non-overlapping pictures. the picture has to loop after 103*101 steps.
for_ [0 .. 103 * 101 - 1] \i ->
do let pic = map (runBot i) input
when (hasNoOverlap pic)
do putStr (drawCoords pic)
print i

-- | Predicate for lists of coordinates that do not overlap
hasNoOverlap :: [Coord] -> Bool
hasNoOverlap = go Set.empty
where
C midY midX = mapCoord (`div` 2) room

step :: Int -> (Int, Int, Int, Int) -> Coord
step n (x, y, dx, dy) = zipCoord mod (C (y + n * dy) (x + n * dx)) room
go seen = \case
[] -> True
x : xs -> Set.notMember x seen && go (Set.insert x seen) xs

-- | Figure out what quadrant a coordinate is in, if any.
toQuad :: Coord -> [(Ordering, Ordering)]
toQuad (C y x) =
[ (xo, yo)
| let C midY midX = mapCoord (`div` 2) room
, let xo = compare x midX, xo /= EQ
, let yo = compare y midY, yo /= EQ
]

-- | Run a bot for a certain number of time steps and find its endpoint.
runBot ::
Int {- ^ time steps -} ->
(Int, Int, Int, Int) {- ^ location and velocity -} ->
Coord {- ^ destination -}
runBot n (x, y, dx, dy) = zipCoord mod (C (y + n * dy) (x + n * dx)) room

0 comments on commit 9392ac6

Please sign in to comment.