Skip to content

Commit

Permalink
wibble
Browse files Browse the repository at this point in the history
  • Loading branch information
glguy committed Dec 3, 2023
1 parent b082318 commit 47e6ed4
Showing 1 changed file with 11 additions and 12 deletions.
23 changes: 11 additions & 12 deletions solutions/src/2023/03.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,9 +30,8 @@ module Main where
import Data.Map (Map)
import Data.Map qualified as Map
import Data.Char (isDigit)
import Data.List (find)

import Advent (getInputMap)
import Advent (getInputMap, ordNub)
import Advent.Coord (Coord, left, neighbors, right)

-- | Parse the input schematic and print answers to both parts.
Expand All @@ -43,23 +42,23 @@ import Advent.Coord (Coord, left, neighbors, right)
main :: IO ()
main =
do input <- getInputMap 2023 3
let
let
lkp i = Map.findWithDefault '.' i input

-- Map of each part in the schematic to the list of adjacent part numbers
partMap :: Map Coord [Int]
partMap = Map.fromListWith (++)
partNumbers :: Map Coord [Int]
partNumbers = Map.fromListWith (++)
[ (part, [read (map lkp cs)])
| (c,n) <- Map.assocs input
, isDigit n
, not (isDigit (lkp (left c)))
, isDigit n, not (isDigit (lkp (left c))) -- left-boundary of number
, let cs = takeWhile (isDigit . lkp) (iterate right c)
, Just part <- [find (isSymbol . lkp) (concatMap neighbors cs)]
, part <- ordNub (concatMap neighbors cs)
, isPart (lkp part)
]

print (sum (fmap sum partMap))
print (sum [a * b | (c, [a,b]) <- Map.assocs partMap, '*' == lkp c])
print (sum (fmap sum partNumbers))
print (sum [a * b | (c, [a,b]) <- Map.assocs partNumbers, '*' == lkp c])

-- | Things that aren't digits or periods.
isSymbol :: Char -> Bool
isSymbol x = not (isDigit x) && x /= '.'
isPart :: Char -> Bool
isPart x = not (isDigit x) && x /= '.'

0 comments on commit 47e6ed4

Please sign in to comment.