aoc2025

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

Main.hs (1871B)


      1 module Main (main) where
      2 
      3 import Control.Applicative
      4 import Control.Arrow (first)
      5 import Data.ByteString qualified as BS
      6 import Data.Char (isDigit, ord)
      7 import Data.List (foldl')
      8 import Sparsec
      9 import System.Exit (die)
     10 
     11 --------------------------------------------------------------------------------
     12 -- Util
     13 
     14 lastMaxInRange :: (Ord a) => (Int, Int) -> [a] -> (a, Int)
     15 lastMaxInRange (l, u) = maximum . takeWhile ((< u) . snd) . drop l . flip zip [0 ..]
     16 
     17 --------------------------------------------------------------------------------
     18 -- Solution
     19 
     20 newtype Joltage = Joltage {unJoltage :: Int} deriving newtype (Eq, Ord, Num, Show)
     21 newtype Bank = Bank [Joltage] deriving (Show)
     22 
     23 bankJoltage :: Int -> Bank -> Joltage
     24 bankJoltage k (Bank js) =
     25     let f (acc, u) l = first (10 * acc +) . lastMaxInRange (l, u) . reverse $ js
     26     in fst . foldl' f (Joltage 0, maxBound) $ [k - 1, k - 2 .. 0]
     27 
     28 part1 :: [Bank] -> Int
     29 part1 = sum . map (unJoltage . bankJoltage 2)
     30 
     31 part2 :: [Bank] -> Int
     32 part2 = sum . map (unJoltage . bankJoltage 12)
     33 
     34 --------------------------------------------------------------------------------
     35 -- Parsing
     36 
     37 newtype ParseError = ErrorUtf8 Loc deriving (Show)
     38 instance Utf8Error ParseError where
     39     utf8Error = ErrorUtf8
     40 type P a = Parse ParseError a
     41 
     42 pJoltage :: P Joltage
     43 pJoltage = Joltage . subtract (ord '0') . ord <$> charIf isDigit
     44 
     45 pBank :: P Bank
     46 pBank = Bank <$> many pJoltage <* char '\n'
     47 
     48 pBanks :: P [Bank]
     49 pBanks = many pBank
     50 
     51 --------------------------------------------------------------------------------
     52 -- Main
     53 
     54 getInput :: IO [Bank]
     55 getInput = do
     56     raw <- BS.getContents
     57     case runParse pBanks raw locZero of
     58         Ok banks _ _ -> pure banks
     59         Fail -> die "parse failure"
     60         Error e -> die $ "parse error: " ++ show e
     61 
     62 main :: IO ()
     63 main = do
     64     input <- getInput
     65     print . part1 $ input
     66     print . part2 $ input