aoc2025

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

Main.hs (1904B)


      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 (count)
      8 import Control.Applicative
      9 import Data.Bool
     10 import Data.ByteString qualified as BS
     11 import Data.Functor
     12 import Sparsec
     13 import System.Exit (die)
     14 
     15 --------------------------------------------------------------------------------
     16 -- Solution
     17 
     18 data State = Blank | Removed | Filled deriving (Eq, Show)
     19 
     20 kernel :: [(Int, Int)]
     21 kernel = [(-1, -1), (-1, 0), (-1, 1), (0, -1), (0, 1), (1, -1), (1, 0), (1, 1)]
     22 
     23 forklift :: Cellular State State
     24 forklift =
     25     C.self >>= \case
     26         Blank -> pure Blank
     27         Removed -> pure Removed
     28         Filled -> bool Filled Removed . (< 4) . count (== Just Filled) <$> traverse C.neighbor kernel
     29 
     30 part1 :: Matrix State -> Int
     31 part1 = M.count (== Removed) . C.step forklift
     32 
     33 part2 :: Matrix State -> Int
     34 part2 = M.count (== Removed) . C.stabilize forklift
     35 
     36 --------------------------------------------------------------------------------
     37 -- Parsing
     38 
     39 data ParseError = ErrorUtf8 Loc | ErrorMatrix deriving (Show)
     40 instance Utf8Error ParseError where
     41     utf8Error = ErrorUtf8
     42 type P a = Parse ParseError a
     43 
     44 pCell :: P State
     45 pCell = char '.' $> Blank <|> char '@' $> Filled
     46 
     47 pRow :: P [State]
     48 pRow = many pCell <* char '\n'
     49 
     50 pMatrix :: P (Matrix State)
     51 pMatrix =
     52     many pRow >>= \rs -> case M.fromList rs of
     53         Just m -> pure m
     54         Nothing -> err ErrorMatrix
     55 
     56 --------------------------------------------------------------------------------
     57 -- Main
     58 
     59 getInput :: IO (Matrix State)
     60 getInput = do
     61     raw <- BS.getContents
     62     case runParse pMatrix raw locZero of
     63         Ok m _ _ -> pure m
     64         Fail -> die "parse failure"
     65         Error e -> die $ "parse error: " ++ show e
     66 
     67 main :: IO ()
     68 main = do
     69     input <- getInput
     70     print . part1 $ input
     71     print . part2 $ input