aoc2025

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

Main.hs (2172B)


      1 module Main (main) where
      2 
      3 import Common.Util (count)
      4 import Control.Applicative
      5 import Data.ByteString qualified as BS
      6 import Sparsec
      7 import System.Exit (die)
      8 
      9 --------------------------------------------------------------------------------
     10 -- Solution
     11 
     12 -- It would be better to use an interval tree or similar data structure.
     13 
     14 newtype Ingredient = Ingredient Int deriving (Eq, Ord, Num, Enum, Show)
     15 data Range = Range Ingredient Ingredient deriving (Show)
     16 data Input = Input [Range] [Ingredient] deriving (Show)
     17 
     18 size :: Range -> Int
     19 size (Range (Ingredient l) (Ingredient u)) = max (u - l + 1) 0
     20 
     21 remove :: Range -> Range -> [Range]
     22 remove (Range p q) (Range l u) = [Range l (min u (p - 1)), Range (max (q + 1) l) u]
     23 
     24 disjointify :: [Range] -> [Range]
     25 disjointify = foldr (\r rs -> r : filter ((> 0) . size) (remove r =<< rs)) []
     26 
     27 contains :: Range -> Ingredient -> Bool
     28 contains (Range l u) i = l <= i && i <= u
     29 
     30 part1 :: Input -> Int
     31 part1 (Input rs is) = count (\i -> any (`contains` i) rs) is
     32 
     33 part2 :: Input -> Int
     34 part2 (Input rs _) = sum . map size . disjointify $ rs
     35 
     36 --------------------------------------------------------------------------------
     37 -- Parsing
     38 
     39 newtype ParseError = ErrorUtf8 Loc deriving (Show)
     40 instance Utf8Error ParseError where
     41     utf8Error = ErrorUtf8
     42 type P a = Parse ParseError a
     43 
     44 manyLines :: P a -> P [a]
     45 manyLines p = many (p <* char '\n')
     46 
     47 twoSepBy :: (a -> b -> c) -> P a -> P () -> P b -> P c
     48 twoSepBy f pa psep pb = (\a () b -> f a b) <$> pa <*> psep <*> pb
     49 
     50 pIngredient :: P Ingredient
     51 pIngredient = Ingredient . fromIntegral <$> natural 10
     52 
     53 pRange :: P Range
     54 pRange = twoSepBy Range pIngredient (char '-') pIngredient
     55 
     56 pInput :: P Input
     57 pInput = twoSepBy Input (manyLines pRange) (char '\n') (manyLines pIngredient)
     58 
     59 --------------------------------------------------------------------------------
     60 -- Main
     61 
     62 getInput :: IO Input
     63 getInput = do
     64     raw <- BS.getContents
     65     case runParse pInput raw locZero of
     66         Ok input _ _ -> pure input
     67         Fail -> die "parse failure"
     68         Error e -> die $ "parse error: " ++ show e
     69 
     70 main :: IO ()
     71 main = do
     72     input <- getInput
     73     print . part1 $ input
     74     print . part2 $ input