aoc2025

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

Main.hs (2261B)


      1 module Main (main) where
      2 
      3 import Common.Cellular (Cellular)
      4 import Common.Cellular qualified as C
      5 import Common.Matrix (Matrix)
      6 import Common.Matrix qualified as M
      7 import Common.Util ((.:))
      8 import Control.Applicative
      9 import Data.ByteString qualified as BS
     10 import Data.Functor
     11 import Data.Maybe
     12 import Sparsec
     13 import System.Exit (die)
     14 
     15 --------------------------------------------------------------------------------
     16 -- Solution
     17 
     18 data State = Source | Void Int | Splitter Int deriving (Eq, Show)
     19 
     20 strength :: State -> Int
     21 strength = \case
     22     Source -> 1
     23     Void n -> n
     24     Splitter _ -> 0
     25 
     26 reflectance :: State -> Int
     27 reflectance = \case
     28     Source -> 0
     29     Void _ -> 0
     30     Splitter n -> n
     31 
     32 topPower :: Cellular State Int
     33 topPower = maybe 0 strength <$> C.neighbor (-1, 0)
     34 
     35 sidePower :: Cellular State Int
     36 sidePower = sum . map (maybe 0 reflectance) <$> traverse C.neighbor [(0, -1), (0, 1)]
     37 
     38 tachyon :: Cellular State State
     39 tachyon =
     40     C.self >>= \case
     41         Source -> pure Source
     42         Void _ -> Void .: (+) <$> topPower <*> sidePower
     43         Splitter _ -> Splitter <$> topPower
     44 
     45 part1 :: Matrix State -> Int
     46 part1 = M.count ((> 0) . reflectance) . C.stabilize tachyon
     47 
     48 part2 :: Matrix State -> Int
     49 part2 m = sum . fmap strength . fromJust . M.row (M.nrows m - 1) . C.stabilize tachyon $ m
     50 
     51 --------------------------------------------------------------------------------
     52 -- Parsing
     53 
     54 data ParseError = ErrorUtf8 Loc | ErrorMatrix deriving (Show)
     55 instance Utf8Error ParseError where
     56     utf8Error = ErrorUtf8
     57 type P a = Parse ParseError a
     58 
     59 pCell :: P State
     60 pCell = char 'S' $> Source <|> char '.' $> Void 0 <|> char '^' $> Splitter 0
     61 
     62 pRow :: P [State]
     63 pRow = many pCell <* char '\n'
     64 
     65 pMatrix :: P (Matrix State)
     66 pMatrix =
     67     many pRow >>= \rs -> case M.fromList rs of
     68         Just m -> pure m
     69         Nothing -> err ErrorMatrix
     70 
     71 --------------------------------------------------------------------------------
     72 -- Main
     73 
     74 getInput :: IO (Matrix State)
     75 getInput = do
     76     raw <- BS.getContents
     77     case runParse pMatrix raw locZero of
     78         Ok input _ _ -> pure input
     79         Fail -> die "parse failure"
     80         Error e -> die $ "parse error: " ++ show e
     81 
     82 main :: IO ()
     83 main = do
     84     input <- getInput
     85     print . part1 $ input
     86     print . part2 $ input