Skip to content

Commit

Permalink
cleanup
Browse files Browse the repository at this point in the history
  • Loading branch information
glguy committed Dec 8, 2024
1 parent 05931bc commit 9155d5e
Show file tree
Hide file tree
Showing 2 changed files with 52 additions and 29 deletions.
2 changes: 1 addition & 1 deletion solutions/solutions.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -1151,4 +1151,4 @@ executable sln_2024_07
executable sln_2024_08
import: day
main-is: 2024/08.hs
build-depends: containers
build-depends: array, containers
79 changes: 51 additions & 28 deletions solutions/src/2024/08.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,42 +8,65 @@ Maintainer : emertens@gmail.com
<https://adventofcode.com/2024/day/8>
>>> :{
:main + "............
........0...
.....0......
.......0....
....0.......
......A.....
............
............
........A...
.........A..
............
............
"
:}
14
34
-}
module Main (main) where

import Advent (getInputMap)
import Advent.Coord (coordRow, coordCol, Coord (C))
import Control.Monad (guard)
import Data.List (nub, tails)
import Advent (getInputArray)
import Advent.Coord (Coord(C))
import Data.Array.Unboxed (assocs, bounds, inRange)
import Data.List (tails)
import Data.Map qualified as Map
import Data.Set qualified as Set

-- | >>> :main
-- 303
-- 1045
main :: IO ()
main =
do input <- getInputMap 2024 8
let locs = Map.filter (\x -> length x > 1)
$ Map.fromListWith (++) [(v, [k]) | (k,v) <- Map.assocs input, v /= '.']
print $ length $ nub $
do posns <- Map.elems locs
x:ys <- tails posns
y <- ys
node <- [y + (y - x), x + (x - y)]
guard (Map.member node input)
pure node
print $ length $ nub $ concat (Map.elems locs) ++
do posns <- Map.elems locs
x:ys <- tails posns
y <- ys
z <- Map.keys input
guard (inlined x y z)
[z,x,y]

inlined :: Coord -> Coord -> Coord -> Bool
inlined x y z
| coordCol x == coordCol z = coordCol x == coordCol y
| otherwise = coordCol z /= coordCol y && slope z x == slope y x
do input <- getInputArray 2024 8
let antennaGroups = Map.elems (Map.fromListWith (++) [(v, [k]) | (k, v) <- assocs input, v /= '.'])
print (length (Set.fromList
[ node
| antennaGroup <- antennaGroups
, x:ys <- tails antennaGroup
, y <- ys
, node <- [2 * y - x, 2 * x - y]
, inRange (bounds input) node
]))
print (length (Set.fromList
[ node
| antennaGroup <- antennaGroups
, x:ys <- tails antennaGroup
, y <- ys
, node <- nodeLine (inRange (bounds input)) x y
]))

slope :: Coord -> Coord -> Rational
slope (C y1 x1) (C y2 x2) = fromIntegral (y2-y1) / fromIntegral (x2-x1)
-- | Generate all the points on the line defined by two coordinates
-- that fit inside a bounding box predicate.
nodeLine :: (Coord -> Bool) -> Coord -> Coord -> [Coord]
nodeLine p a b =
takeWhile p (iterate (step +) a) ++
takeWhile p (iterate (subtract step) (a - step))
where
C dy dx = a - b
com | dx == 0 || dy == 0 = 1
| otherwise = gcd dy dx
step = C (dy `quot` com) (dx `quot` com)

0 comments on commit 9155d5e

Please sign in to comment.