aoc2025

Advent of Code 2025
git clone git://git.rr3.xyz/aoc2025
Log | Files | Refs | Submodules

Main.hs (3047B)


      1 module Main (main) where
      2 
      3 import Data.ByteString qualified as BS
      4 import Numeric.Natural (Natural)
      5 import Sparsec
      6 import System.Exit (die)
      7 
      8 --------------------------------------------------------------------------------
      9 -- Util
     10 
     11 divides :: Natural -> Natural -> Bool
     12 d `divides` n = d /= 0 && n `mod` d == 0
     13 
     14 numDigits :: Natural -> Natural -> Natural
     15 numDigits b = ceiling . logBase @Double (fromIntegral b) . fromIntegral
     16 
     17 digits :: Natural -> Natural -> [Natural]
     18 digits b _ | b < 2 = error "invalid base"
     19 digits _ 0 = []
     20 digits b n =
     21     let (q, r) = n `divMod` b
     22     in r : digits b q
     23 
     24 hasConsensus :: (Eq a) => [a] -> Bool
     25 hasConsensus [] = False
     26 hasConsensus (x : xs) = all (== x) xs
     27 
     28 --------------------------------------------------------------------------------
     29 -- Solution
     30 
     31 -- Idea: We say a number is k-silly iff its base-10 representation consists
     32 -- of k identical sequences of digits (this is effectively what we get from the
     33 -- problem statement). Equivalently, a number n is k-silly iff k divides the
     34 -- number d of base-10 digits in n and the digits in n's base-10^k
     35 -- representation are identical (this is isSillyA). Equivalently, a number n is
     36 -- k-silly iff k divides d and (11...11)_{10^(d/k)} divides n (this is
     37 -- isSillyB).
     38 --
     39 -- Part 1 asks us to sum all 2-silly numbers in the input ranges.
     40 -- Part 2 asks us to sum all numbers that are k-silly for some k >= 2.
     41 
     42 data Range = Range Natural Natural deriving (Show)
     43 
     44 isSillyA :: Natural -> Natural -> Bool
     45 isSillyA k n =
     46     let d = numDigits 10 n
     47     in k `divides` d && hasConsensus (digits (10 ^ (d `div` k)) n)
     48 
     49 isSillyB :: Natural -> Natural -> Bool
     50 isSillyB k n =
     51     let d = numDigits 10 n
     52         mask 1 = 1
     53         mask i = mask (i - 1) * 10 ^ (d `div` k) + 1
     54     in k `divides` d && mask k `divides` n
     55 
     56 isSilly :: Natural -> Natural -> Bool
     57 isSilly = isSillyB
     58 
     59 isAnySilly :: Natural -> Bool
     60 isAnySilly n = any (`isSilly` n) [2 .. numDigits 10 n]
     61 
     62 elems :: Range -> [Natural]
     63 elems (Range l u) = [l .. u]
     64 
     65 part1 :: [Range] -> Natural
     66 part1 = sum . filter (isSilly 2) . (>>= elems)
     67 
     68 part2 :: [Range] -> Natural
     69 part2 = sum . filter isAnySilly . (>>= elems)
     70 
     71 --------------------------------------------------------------------------------
     72 -- Parsing
     73 
     74 -- TODO: We ought to check that the ranges are well-formed (i.e., l <= u).
     75 
     76 newtype ParseError = ErrorUtf8 Loc deriving (Show)
     77 instance Utf8Error ParseError where
     78     utf8Error = ErrorUtf8
     79 type P a = Parse ParseError a
     80 
     81 pRange :: P Range
     82 pRange = (\l () u -> Range l u) <$> natural 10 <*> char '-' <*> natural 10
     83 
     84 pRanges :: P [Range]
     85 pRanges = someSepBy pRange (char ',') <* char '\n' <* eof
     86 
     87 --------------------------------------------------------------------------------
     88 -- Main
     89 
     90 getInput :: IO [Range]
     91 getInput = do
     92     raw <- BS.getContents
     93     case runParse pRanges raw locZero of
     94         Ok ranges _ _ -> pure ranges
     95         Fail -> die "parse failure"
     96         Error e -> die $ "parse error: " ++ show e
     97 
     98 main :: IO ()
     99 main = do
    100     input <- getInput
    101     print . part1 $ input
    102     print . part2 $ input