commit 41a87c1f4049fa0c5a672a487af93e28e8a72701
parent 6c1ca59c6bda7e4efd96acee910a613ae69eb651
Author: Robert Russell <robert@rr3.xyz>
Date: Sun, 7 Dec 2025 16:46:08 -0800
Solve 04
Diffstat:
7 files changed, 294 insertions(+), 0 deletions(-)
diff --git a/.gitmodules b/.gitmodules
@@ -1,3 +1,6 @@
[submodule "sparsec"]
path = lib/sparsec
url = git@rr3.xyz:sparsec
+[submodule "lib/naturals"]
+ path = lib/naturals
+ url = git@rr3.xyz:naturals
diff --git a/04/Main.hs b/04/Main.hs
@@ -0,0 +1,97 @@
+module Main (main) where
+
+import Control.Applicative
+import Control.Monad.Reader
+import Data.Bool
+import Data.ByteString qualified as BS
+import Data.Functor
+import Data.Maybe
+import Matrix (Matrix)
+import Matrix qualified as M
+import Sparsec
+import System.Exit (die)
+
+--------------------------------------------------------------------------------
+-- Util
+
+count :: (a -> Bool) -> [a] -> Int
+count p = length . filter p
+
+untilFixed :: (Eq a) => (a -> a) -> a -> a
+untilFixed f x = let x' = f x in if x' == x then x' else untilFixed f x'
+
+--------------------------------------------------------------------------------
+-- Cellular Automata
+
+newtype Cellular s a = Cellular (Reader (Matrix s, Int, Int) a)
+ deriving (Functor, Applicative, Monad)
+
+neighbor :: (Int, Int) -> Cellular s (Maybe s)
+neighbor (di, dj) = Cellular $ asks \(m, i, j) -> m M.!? (i + di, j + dj)
+
+self :: Cellular s s
+self = fromJust <$> neighbor (0, 0)
+
+step :: Cellular s s -> Matrix s -> Matrix s
+step (Cellular c) m = M.generate (M.nrows m) (M.ncols m) \(i, j) -> c `runReader` (m, i, j)
+
+stabilize :: (Eq s) => Cellular s s -> Matrix s -> Matrix s
+stabilize c = untilFixed (step c)
+
+--------------------------------------------------------------------------------
+-- Solution
+
+data State = Blank | Removed | Filled deriving (Eq, Show)
+
+kernel :: [(Int, Int)]
+kernel = [(-1, -1), (-1, 0), (-1, 1), (0, -1), (0, 1), (1, -1), (1, 0), (1, 1)]
+
+forklift :: Cellular State State
+forklift =
+ self >>= \case
+ Blank -> pure Blank
+ Removed -> pure Removed
+ Filled -> bool Filled Removed . (< 4) . count (== Just Filled) <$> traverse neighbor kernel
+
+part1 :: Matrix State -> Int
+part1 = M.count (== Removed) . step forklift
+
+part2 :: Matrix State -> Int
+part2 = M.count (== Removed) . stabilize forklift
+
+--------------------------------------------------------------------------------
+-- Parsing
+
+data ParseError = ErrorUtf8 Loc | ErrorMatrix deriving (Show)
+instance Utf8Error ParseError where
+ utf8Error = ErrorUtf8
+type P a = Parse ParseError a
+
+pCell :: P State
+pCell = char '.' $> Blank <|> char '@' $> Filled
+
+pRow :: P [State]
+pRow = many pCell <* char '\n'
+
+pMatrix :: P (Matrix State)
+pMatrix =
+ many pRow >>= \rs -> case M.fromList rs of
+ Just m -> pure m
+ Nothing -> err ErrorMatrix
+
+--------------------------------------------------------------------------------
+-- Main
+
+getInput :: IO (Matrix State)
+getInput = do
+ raw <- BS.getContents
+ case runParse pMatrix raw locZero of
+ Ok m _ _ -> pure m
+ Fail -> die "parse failure"
+ Error e -> die $ "parse error: " ++ show e
+
+main :: IO ()
+main = do
+ input <- getInput
+ print . part1 $ input
+ print . part2 $ input
diff --git a/04/Matrix.hs b/04/Matrix.hs
@@ -0,0 +1,48 @@
+module Matrix (Matrix, nrows, ncols, generate, fromList, (!?), count) where
+
+import Data.Vector (Vector)
+import Data.Vector qualified as V
+
+--------------------------------------------------------------------------------
+-- Util
+
+consensus :: (Eq a) => [a] -> Maybe a
+consensus [] = Nothing
+consensus (x : xs) = if all (== x) xs then Just x else Nothing
+
+--------------------------------------------------------------------------------
+-- Matrix
+
+data Matrix a = Matrix Int Int (Vector a) deriving (Eq, Show)
+
+instance Functor Matrix where
+ fmap f (Matrix nr nc vs) = Matrix nr nc (f <$> vs)
+
+nrows :: Matrix a -> Int
+nrows (Matrix nr _ _) = nr
+
+ncols :: Matrix a -> Int
+ncols (Matrix _ nc _) = nc
+
+valuesRowMajor :: Matrix a -> Vector a
+valuesRowMajor (Matrix _ _ vs) = vs
+
+generate :: Int -> Int -> ((Int, Int) -> a) -> Matrix a
+generate nr nc f = Matrix nr nc (V.generate (nr * nc) (f . (`divMod` nc)))
+
+fromList :: [[a]] -> Maybe (Matrix a)
+fromList [] = Just $ Matrix 0 0 V.empty
+fromList l = do
+ let nr = length l
+ nc <- consensus (length <$> l)
+ let vs = V.concat (V.fromList <$> l)
+ Just $ Matrix nr nc vs
+
+(!?) :: Matrix a -> (Int, Int) -> Maybe a
+Matrix nr nc vs !? (i, j) =
+ if 0 <= i && i < nr && 0 <= j && j < nc
+ then Just $ vs V.! (i * nc + j)
+ else Nothing
+
+count :: (a -> Bool) -> Matrix a -> Int
+count p = V.length . V.filter p . valuesRowMajor
diff --git a/04/input.txt b/04/input.txt
@@ -0,0 +1,138 @@
+@@.@.@.@.@@@...@@...@@@@@.@@@.@@@@@@@.@@..@@@@@@.@..@@.@.@@..@..@@@@@@@@.@@.@.@@@@.@@@@@@@@...@@@@.@..@@.@@@@@@.@@..@....@..@@..@@@@@@@.@@
+@.@@@@@.@@..@@.@@.@@@.@@@@@@@...@@@@.@@@@.@@@.@...@.@@@@@@@@@@@@..@.@@@.@@@..@@@@@.....@..@..@@@.@@.@@@@@.@.@...@@@@.@.@.@@.@@@@.@@@..@@.@
+.......@@@..@@@@@@@.@..@@@.@@@@@.@@.@@@@.@@@.@@@.@@@..@@...@@....@@@..@@@@@@@@..@@@..@@@.@@@@@...@.@@@.@@@.@@@@@@@..@@@@@@@..@@@@.@@@@@@@.
+@.@.@@@@@.@.@@@@...@@@@@@.@@.@@.@@.@.@..@..@..@..@@@....@@@..@.@@@.@@@@.@@.@.@@@..@.@@@@.@.@@@@.@...@@.@@@..@@@@...@@@.@.@.@@..@.@..@@.@@.
+...@@@@@@@@@@@@.@..@@@.@@@@@@@@@.@@@@@.@..@@@@@@@@.@@@@@@@@.@..@..@@.@@@@.@@@@.....@@@@.@@@@@@.@@@.@.@.@@@@@..@@@..@.@..@.@@@.@@@.@@@.@@@@
+@@@@.@@@@.@@@@@@@.@.@@@.@@@.@..@.@..@@@@@.@....@.@@@@@..@@.@@@.@@.@.@@.@@@@.@@@.@@@@@@...@@.@@@.@@.@.@@@@.@.@@@@.@@@@@..@@@.@@..@@@.@@.@@.
+.@@@@@@@@@@@@@@@@.@@..@.@@.@@@@@@.@.@@@@@.@@@@@.@@.@.@@@.@@.@@@@@@.@@@..@.@@....@@.@@@..@.@@..@@.@@@@@@@@@@..@.....@@.@@.@@@@..@@.@@@@..@.
+@.@@@@.@.@@@..@.@@@@@.@.@@@@@@@@@@@.@..@.@@.@..@@@@.@@..@...@..@@@@@@@@.@@@@.@@@@@.@.@@@@.@.@..@@@@@@@@...@@@@.@.@..@@.@@...@@@@@...@..@.@
+@@.@@..@@@@.@@.@@..@..@.@...@@@@..@@@...@.@@@@@@@.....@.@...@@@@@.@.@@.@@...@@@@@..@@@..@@.@@.@@@@.@@.@.@@.@.@...@@..@@@..@@.@@@@.....@@@@
+@.@@@@..@.@@@.@@@..@.@@@@.@.@@..@@@.@..@.@.@@.@...@@.@@.@.@@@.@@@@.@.@@@@..@.@@..@@.@@@@@@..@.@@@@@@@@@.@.@@@@..@@@@@..@@.@....@@.@@@@@@@.
+...@..@@.@.@@.@@@.@@@.@@@@@@@.@.@@@@...@@@@..@@@.@@..@.@.@@.@.@.@..@.@@@.@@@@.@@@..@.@@.@.@.@@.@...@@.@@...@@@@@@@@@@@@@@.@@@.@@.@@@..@@@@
+.@@@.....@@...@@@.@@.@@@@.@@.@@@.@@@@@@..@@@@@.@@@@@@@@.@.@.@..@.@.@@@...@@@@@......@..@.@..@.@@@...@.@@.@@.@.@@.@@@..@.@.@..@@..@@@@@@...
+.@.@.@@..@@@@@.@@@@@@@.@@@@@.@.@@@@...@@...@...@@@@@.@.@@..@.@@@...@@@@@@@@@@@@@@@@.@@@@.@@@..@@@@@@@@@.@@.@@@@@@@@@.@.....@..@@@@@@.@.@@@
+@@..@@@@@..@@..@@@@@@@.@@.@..@...@@@@@@..@@.@@@@..@@@@@@...@..@.@@@@.@.@.@@@@.@@@@.@@@@..@@.@@.@...@@@...@@@@@.@.@@@.@@@.@@@.@@@..@@@@@.@@
+@.@@@..@@@@@.@@@.@@@@.@@@..@@@.@@@.@@..@@.........@@.@.@..@@@.@@@@@@@.@@@.@.@@@@@.@.@@@@@.@@@@.@@.@@.@.@@@.@@@@.@@@@.@@@..@@.@.@@.@...@.@@
+.@@.@.@@@.@@@@...@@.@@.@@.@@@.@@.@..@@.@..@@@@@.@@..@..@@@@.@.@.@@..@@.@@@.@@@@...@@@@.@@@..@@@@.@@..@@@@@@.@@@@.@@@@@@@@@@@.@.@@..@@@.@..
+@...@@@..@.@..@@@..@@..@@@@@.@.@..@@.@@@@@@@@@@@@@.@..@.@@@@@@@.@@@.@@@..@.@...@@.@..@@@.@..@@@@@@@@@.@@@@.@.@@..@@@@@@..@.@@@.@@@@@@@@.@.
+@.@@@.@.@@@@....@@@.@@.@@.@.@@@.@.@..@.@@@@@.@@@.@@@.@.@.@@.@.@@@@.@.@.@@..@@.@@.@@@.@@@@@@@@@....@@@@....@@@.@@@@@.@@.@@@@.@@.@@@.@.@@@.@
+@.@@@@...@@.@.@..@@.@@@@@@@@@@@@@@@@.@...@@@@.@@@@@@@@.@..@.@@@..@.....@.@@@.@@@..@@.@@@@.@@..@.@.@.@@@..@@@@@@@.@@@...@@..@.@@@@@...@@@@@
+@@@..@..@.@@@@@.@@...@@..@.@@@@@...@..@.@@@.@@..@@@.@.@@@@@@@.@.@@....@@@@.@..@@.@..@..@@@@@@.@@@@.@@..@.@@@@.@@..@@@@@.@...@.@..@.@.@@@@@
+@@@.@@.@@@@@.@@@.@@@.@@.@..@@@.@.@@@.@.@@@@@@.@@@@@@@@@@.@@@..@@@@@@@.@@@..@@.@.@@.@@.@@.@@.@..@.@.@@.@..@.@@@@@@.@.@....@.@.@@..@@...@@@@
+@@@.@@@@@@.@..@@...@.@.@@@@.......@.@.@@.@...@@@@..@.@@.@...@.@@..@.@.@@..@.@@.@@@...@.@..@@@@..@@.@@@@.....@.@@..@@@..@@@..@@@@@.@.@@..@@
+@@...@@@@@.@@.@@@.@@@.@@@.@@@@@@@@.@.@@@@.@@...@@..@.@.@.@@.@@@.@@@.@@@.@..@@@@@..@.@@...@@@@.@@@@.@...@.@@.@.@.@@.@.@.@..@@.@@@@@@@@@..@.
+.@..@@@.@.@@@@@.@@@@..@.@@@.@@.@@@.@.@@@@@@@.@@..@@@@@@@@.@@@...@.@.@@@.@...@@@.@@@@@.@.@...@@@.@..@@@.@@..@@@@.@@@@.@@@@@@@@.@@.@@.@@@@@@
+@@@@.@@....@@@.@@@@.@.@@@@@..@@@@..@@@@@@@....@@@.@@.@.@@@@@@@..@@.@@.@.@@@...@@@@@@.@@@.@.@@..@@@..@@@@@..@@.@@@@@@.@@.@@.@@@.@.@.@@@@...
+@@@@@@..@@@@@@..@..@.@@@.@@..@@@@..@@@@@@..@@@.@@@@@.....@.@@..@@@@@.@..@@...@.@@.@@@..@@@@@@@.@@..@@@@@@.....@.@@..@@@@@.@.@@@.@@@..@@..@
+@@..@@@@@..@@.@@@@..@@.@.@..@@@@...@@.@@@....@@@@@.@.@@.@..@@..@@@@.@@@.@@@.@@@@@..@@.@@@@@.@@@@@@.@@@.@@@@.@@@.@@.......@@@@@..@@@..@.@@.
+@....@@.@..@@@.@.@..@..@.@.@@@.@@@.@.@@@.@@.@@@@.@.@@@@@@.@@.@@@.@.@@@...@.@.@@@.@@.@@@.@@..@@..@.@@@@@@...@@@.....@.@@@@@@@@.@@.@@@@@@@@@
+@@@.@@@@@@@..@.@@.@.@@.@@@@@.@@..@.@@.@@@.@@@@@@..@@@@@@.@@.@@@@@@@@@@.@.@@@@.@.@@@.@..@@@@.....@.@....@@@.@@@.@@@@..@@@@@.@.@..@..@.....@
+.@@..@@.@...@@@@@...@.@@@.@@@.@@@...@@@..@@.@@.@....@@@@@@.@@@.@..@@@.@@.@@@@@.@.@.@@.@@.@@@@@@@@...@@@@..@@.@@@@....@.@@@@@@@@@@...@@@@@@
+..@@@..@@.@.@.@@@.@..@.@@..@@@@@@.@@@@@@@.@..@@@@@..@@@@@@@@@@.@...@@..@@@.@@..@@...@@@@@.@@.@..@@@..@.@@@..@..@.@@@@@.@....@.@.@@@..@..@@
+@.@.@@.@.@..@@@@@.@.@@.@@@.@..@@.@@@.@@@@@...@@@@.@..@.@@.@@.@@.@@..@@@.@.@@@@.@@...@@.@.@@@.@.@@@@.@..@.@@@@@@.@@@@@@@@@@@@@@@.@@.@.@..@@
+@@@@@@.@.@@@.@@@.@.@..@.@@...@@@..@@@@..@@..@.@@@@@@@@...@.@..@@.@@.@..@@@@@.@@@.@.@.@...@.@...@...@@@@@@@@@@..@@@.@@.@.@@@@..@@@@@@...@.@
+@@..@.@@@@@.@.@@@....@.@..@.....@@@@@@.@@.@.@@.@@..@.@@@@@.@..@@@@@.@@@.@@@@@..@@@..@@@@@@.@@@@.@@@.@@....@..@.@@..@.@....@..@.@@.@@@@@@@@
+@.@@.@.@@@.@..@@@.@@@@@@@@.@@..@@.@@@@@.@.@@@@.@.@...@.@@@...@@@@..@@@@@@.@.@@@@@@.@@@.@@@..@@..@@@@@@@@..@@@.@@..@@@@@@@.@.@@.@@..@.@.@..
+@@@.@.@@..@@@@@......@@@@.@.@@@@.@@@@@@@.@..@@..@..@.@@@@@@@.@@@.@@@@.@@.@@@..@.@@..@@@.@.@@.@@.@.@@@@@@.@@@@@@@..@@@@@@..@.@.@@@@@@@@@..@
+@.....@@...@@@@.@@@.@..@@@.@@@.@.@@......@.@@@@@@@@.@@.@@@@@@..@@...@@..@@@@@.@.@...@@@.@@@..@@@.@.@@@@@@@@.@@@@@@@.@.@.@...@.@.@@@.@.@@..
+..@.@@@.@@@@@...@..@@@@@@@@@@@@@.@@..@..@@@..@@.@@@...@..@@@..@@..@.@.@.@@@..@.@@...@@.@@@@.@@@.@@@@..@.@...@@@@.@@@@.@@..@@@@@@@..@@@@.@@
+@@..@...@@.@@@@@@...@@@.@@@@..@..@@@@@@@@@@@@.@@@@@.@.@@@@@..@@.@.@@@@@@..@@.@@.@@.@@.@@...@@@@.@...@@@@.@..@@@@@@@.@.@@@..@.@@@@.@.@....@
+.@@.@.@@.@@.@@@.@@@@.@@@@@@.@.@.@..@@@@@.@@@@.@@@@@.@.@@.@@@@.@@.@@.@@...@@@@..@....@@@@...@@...@@..@.@@.@...@@@.@.@@..@.@.@.@@.@.@@.@.@@@
+@@.@@.@@@....@@@@@@@@@.@.@@@.@@@@@@.@@@.@@@@@@@..@@@@.@.@..@..@@@..@@@@...@@@@@@@@@.@@@.@@@@@@@@@@@@@.@@.@.@@.@.@@@@@@@@@@.@@@......@..@@@
+@...@@.@@@@..@..@@@....@.@@.@.@@.@@@...@@@@@@@@.@@.@@@@..@@@@.@@@@@..@@.@..@@@@..@@@@.@@@..@@@@@...@@.@@@@.@...@.@@@@@@@@@@.@@@@@@@@@.@.@@
+@@@@.@@@@@@@@..@@@@.@..@.@@@@@@@@@.@...@.@@@.@..@@@..@@.@@@@@@@@.@@@@@@@....@@.@.@@@@@.@.@..@.@@@@..@@@.@@@@@@.@@@@@@@...@...@.@.@@@@@@@@.
+.@@@@.@@.@@@@@@@@@@@@@.@@@@.@@.@@@@.@@.@...@@@@..@.@@.@.@@@@@.@...@@.@.@@@@.@@@.@@...@@@@@.@@.@..@@@@@.@@@@@@.@....@@@..@@.@.@....@..@.@..
+@@@@@@@.@@..@.@.@.@.@.@@@@@@@..@@.@@@@@@@@.@.@.@@@@@@@@@.@@@..@@@@@@@.@.@.@@.@@.@@@.@@.@@@@@@@@...@@@.@@...@@.@@.@@@@.@@@@.@..@@@@..@.@@.@
+@...@@@@...@@@@@@@@..@@@@.@.@.@@@@.@@..@@@@..@.@@@@@@.@@..@@........@@@@@@@..@@@.@@@@..@@@@@..@..@@....@@....@..@@@@@@.@@@@@@.@@@@@@@.@@@@
+@...@.@.@@@@@.@...@@.@.@.@@@.@@.@@@...@@@@@@@@.@.@..@.@.@.@@@.@@@@@..@@@@@.@@.@@@.@@.@@.@@@@@.@...@@.@@@..@...@.@@@@@@@@@.....@@@.@@@.@.@@
+..@@@@..@@.@@..@.@@..@.@....@@@.@.@..@...@@.@@..@@@@@.@@..@@@.@@@@@@@.@@.@.@@@@@@.@..@@@@@@.@@@@@@.@.@..@@@.@@@@..@..@@.@@@@@@@.@@.@@..@@.
+@.@@..@@@.@.@@@@@..@..@@.@@@@@..@@..@@@...@..@@@@.@..@@@.@@@@.@@@@@@@@@@@.@..@@@..@@@@@@@.@@@@@.@@@@.@.@@@@@.@@@.@@@@.@@.@@.@@.@@@.@@@.@@.
+@...@.@@@@.@@@@..@@@.@@@..@.@@@@@@@@@@.@@@@@@.@..@@@@@@@@@@.@@@@@.@.@..@@@@@@..@@.@@@@@@.@@@@...@....@.@@.@@.@@.@@@@@..@@@@.....@@@.@.@@@.
+@@.@@@@@@@.@@@@@@..@.@@@.@@..@@@@@@.@@@.@..@@.@@.@@@@@.@.@@@@@@@.@@@...@@..@@@@@@@@@@@@@.@@..@@@....@@@@@..@.@@.@@..@@@@@.@@@@.@@@@@@@@@@@
+.@@@@@@.@@@.@.@@@@..@@@.@.@@@@@@.@.@@..@@@.@..@@.@...@.@...@@.@.@@@..@.@@..@@@.@@@.@@@@.@@@..@.@@..@@@@@@@@...@.@.@@@@@@..@@.@@@@.@@@@@@..
+@.@.@@@@@@@@.@@...@@@.@@.@..@@@@@@@@.@@@...@.@..@@@.@@@..@@.@.@@.@@@@.@.@@.@@@..@@@@.@..@@@@@@.@@@@.@...@@@.@@@@@@@@.@@@....@@.@.@...@.@.@
+.@.@@..@@@@.@@@@@@..@@.@..@@@@...@@@@...@@.@@@@.@@@@@@@@@@@.@@.@@@@@@@@...@@...@@@.@@.@@@@@@@@@@...@..@@@@@....@@@@@@@..@@@..@@@@@@@....@.
+@@@@@@@...@@@...@@@@..@@@.@..@@@....@@@.@.@@@@.@.@@@.@@@@.@@@@@.@.@@@..@.@@@.@..@@.@.@@@.@@@..@@@@@.@@@@@@@@@.@...@@@.@@@.@@@...@@@@@@@@@.
+@.@.@@.@.@@.@.@...@...@@@...@@.@@.@@@@@@@.@@@..@@@@@.@.@@@.@.@.@.@@.@@.@@.@@.@.@@.@.@..@@@@@@@..@.@.@@..@@.@.....@@@@@@@.@@@@..@@@.@@..@@.
+..@@@@@.@@@...@@@.@.@@@@@@@@@@..@@@@@@.@@@...@@..@@.@.@@@...@@@.@@@@@.@@.@@.@.@@@..@@.@@@@@..@@@@@@@.@@@@.@@.@@@@.@.@@@.@@@.@@@@@@@@.@...@
+..@@@@.@.....@.@@.@@@@@..@@.@@.@..@.@@@..@@.@@@......@@@@@.@@.@@@@@.@@@.@@..@@@..@....@.@.@@..@@@@@...@.@@.@.@@@@.@.@.@@@@@@.@.@@.@@@@@@.@
+.@@..@@@..@@.@@.@@@..@@..@@..@@@.@@@@@...@..@.@...@@@.@@@@.@.@@@@....@@@@@@.@@@@@.@@..@@..@@@.@@@@@@@@@@@.@@.@.@@@@@.@..@@@.@....@@@@@..@@
+@.@@@...@.@.@.@@@.@@@@@@.@..@@@@@@@@@@@@@@@.@..@@@@...@@.@.@@@@@@@@.....@.@@@@@.@@.@@@..@@@@@@@@.@@@@..@@.@@...@@..@@@@@.@@.@@@@.@@@.@@@@.
+...@..@@@@@@.@@.@@..@@.@@.@@@@@@.@..@@@@.@@..@.@.@@...@@@.@....@...@.@@.@@@.@@@@.@@..@@@@.@.@...@.@@...@..@.@@@@.@@@.@@@.@.@@@@@.@.....@@@
+@@@@@@@.@.@@..@@@.@@@@@..@..@@@@@..@....@@..@@.@@@@@.@@.@@@@.@.@@@@@.@.@@@@...@@@@.@...@@@@.@@@@@@@@@..@@@.@.....@.@@@@.@@.@@@.@@@@@.@@@@@
+@@@@@@@.....@@@@.@@@.@@..@@.@..@@@@..@.@.@@@@@....@@@.@@@@@.@.@.@.@@@..@..@@.@..@@.@@.@@.@.@@.@..@@@@@@.@.@.@@@.@@@@@@.@.@.@@.@....@@@..@@
+..@@@.@@.@@@...@@@@@@@..@@@.@@.@.@.@@@@@@@@@@@.@@@.@@@@@@@@..@.@@@@@....@@@@@@@@..@..@.@@@..@..@@@.@@@..@@@@@@@..@@.@@@.@@@@@@@@@@@.@@@.@.
+@@@..@@@.@@@@.@@@.@@@@@@.@@@@@@@.@@@@@@@@@@.@.@.@@@.@@.@@@@.@@@@.@@@@@@.@@@.@@@@@.@@@@.@@@@.@@.@@@@.@.@@@.@...@@.@@.@.@@.@.@@@...@@...@.@.
+@.@@.@@@.@@@.@@..@@.@@..@.@@.@.@.@.@..@@..@.@@@.@.@@@@.@@@@.@.@@@.@.@@@@@.@@@.@@@@@..@.@.@.@.@.@@@@@..@@@.@@@@@@@.@@@@@@@@.@@@@..@...@.@.@
+@@@@.@.@@@@@@.@.@@@@@@.@.@.@@@.@@@..@.@.@@.@.....@@@@@.@@@@@@.@.@.@@@@@...@..@@@.@@@.@..@@@@.@@.@@.@...@..@@.@@.@@.@@@@.@@.@@@@@@@@@@@@@@@
+@@@@@@@@.@.......@@@@@@@.@.@.@@@@.@@@@@@.@.@@@@@@..@.@@@@@@.@@@@..@@.@..@@@...@@.@@@@@.@..@@@@..@.@@@@.@@..@..@@..@@@..@@.@.@.@...@@@.@.@@
+@.@.@.@@@@.@@.@@@@@@@@@@.@@.@@@@.@@@@@@@.@..@..@@.@@@..@@@@...@@.@@@@@...@.@..@.@..@@@@@@...@@@@@.@@.@@@@@@@@.@@@...@@@@@..@@.@...@@.@@@@@
+.@@@..@@.@@.@@@@.@@@@@@@@...@@@@@@.@@@@..@@.@@.@....@@@@@@.@@.@.@@@@@@.@@@.@@@.@..@@@@..@.@.@@.@@..@@@@@@@@@@.@.@....@@@@.@.@....@@@@@.@.@
+.@@@@@.@@@.@.@.@.@@@.@@@@.@.@.@@@@.@@..@.@@@.@@.@@.@.@@.@@.@@@@..@.@@.@.....@@@@.@@@.@.@@.@@@.@@...@@@..@...@.@...@..@@@@@.@@@..@.@@@@.@@@
+@.@.@@.@@@.@@..@@@@.@..@@@@@@.@@.......@.@....@@@.@.@@.@@@@@@@..@@.@@@..@@@@@.@.@@@@@@..@@@@.@.@..@@....@....@@.@@@@@.@@.@@.@.@@.@.@@@..@@
+@@@@@@...@@..@.@@@@@@@.@@.@@@@@@@@@@@@..@@...@.@@@@@.@@@@@@..@@..@@@@@@..@.@@@@@@.@@@@@@.@.@..@@.@@@@@@..@@.@..@@@@@@.@.@@.@@...@@@.@..@@.
+.@@.@.@@@@@..@@.@@@..@.@.@..@.@@@@.@@@@@.@@@@@..@..@.@@.@@@@.@.@.@@@.@@@.@@@@.@@.@@..@..@....@@@.@@@@@@@@@@@.@@.@@@@@.@..@@@@@@.@.@.@.@@@.
+@@..@@@..@@@@@.@@@@@.@@@.@@@..@.@.@@@@@..@@.@@@@@@@@@.@.@@@.@@@..@@.@...@@@@@...@@@@@@@.@@@@.@@@@@.@.@@..@@@@.@@.@@@@@@@@@..@.@.@@.@@.@@@.
+...@.@@.@..@@@@@.@@..@@@.@.@@@@@@@.@@.@@@@@.@@@@...@@...@@.@.@@..@@@@@@.@@...@@@@@@..@@...@@@.@.@@.@@@@@..@.@@@.@@..@.@@@.@.@@@@.@...@@@@@
+@@@@@@@.@..@@@.@@@@@@@@@.@@..@@@@@.@.@@@@@@@.@@@.@...@@@@@@@.@@@@.@@.@@.@@@.@@@@@.@..@@.@@@@@.@..@.@@@@@..@...@@@@.@..@@..@@@@@.@.@@..@..@
+@@@@@@@..@@@.@@@@..@@@..@.@....@@@.@.....@..@@@..@@@@@@@@@@@@.@@.@.@@@@@@@@@@@@..@.@@@@@....@@@.....@@....@.@@@@...@@@@..@@.@@..@@.@@@@@@@
+.@..@@@.@.@@@@.@.@@@@.@.@..@.@@@@..@@..@...@@@..@.@..@..@@@@@.@@@@@@@.@.@@@..@.@@..@@.@.@..@.@@.......@..@@@@@....@@.@.@@@..@....@@@@....@
+@.@@@@@.@.@@@@@@....@..@@@..@@@@@..@..@@@.@..@..@..@.@@@@@.@@@..@@.@@@@....@@@.@@.@@.@@@.@@...@@@.@@@.@@@@@.@.@@@...@.@@@@.@@@..@@.@@.@@@@
+@...@.@.@..@@@@@@@@@.@@.@@@.@@..@@@@@.@@@..@@@@@@.@@@@..@.@.@@@..@..@.@@@@..@.@.@@@.@@@.@@@@.@@@..@@.@@.@@..@@..@..@@@@@@@@.@@.@@@@@@.@@@@
+@.@@@@@..@@@@.@@.@@@@@@.@@..@.@@@@.@.@@@@@@@@@.@@.@@@@@@@.@@@@@@@.@@@@.@.@@.@@.@@.@@@@.@..@@.@....@@@@.@@.@@@@..@@..@@@.@@@@.@@@@@@@...@@.
+.@@....@@.@@....@@@@@@@@@.@@@@...@@@@@@@@@@..@@@@@@@@.@@@@@.@...@@@.@@.@@@@.@@@@@@@.@@@@.@@@@@.@@@.@.@@.@@.@.@.@.@@@@.@@.@...@@@.@@.@@@.@@
+@..@@.@@@.@.@...@@.@@.@.@@.@@@@@.@@@..@@@@@@@@@@@....@@.@@@..@.@@@@@@@..@.@..@.@@.......@@@.@@@.@.@@..@.@.@.@@@@@...@@@@@@@@..@@.@@@....@.
+@@@@.@@..@.@@@@@...@@@@@.@@...@@.@@..@@@..@@@.@..@@@@@..@....@@.@@.@@@.@@@@@@.@@.@.@..@@@..@@.@@@.@@......@@@@@@.@.@@@.@@.@.@@.@@.@.@@.@.@
+@.@@@@@@@@@@@@.@@@.@...@@@.@@@@@@.@@@@.@@..@@@..@.@@@@@@@@.@@@.@@@@@@@..@@@@@@@@..@.@@.@.@@@@.@.@@.@@@.@@@@@.@@@@@@@@.@@@@@@@.@@.@@@@@...@
+@.@@@@@@@@.@@@@@@@@@..@@@@.@@@@@.@.@.@@.@@.@@@.@.@@..@.@@@@.@.@.@@@@@@@@@@@@@...@.@@.@@@.@.@@.@.@@@..@@@@@...@.@@@@@.@.@@@..@.@.@@@.@@..@@
+@@.@@@@..@@@@@@@.@.@@..@@@@@@.@@@.@@..@@@@..@@@@@@@.@@@.@.@@@@@@@@....@.@.@.@.@@.@@.@.@@.@.@@.@.@@@@@....@@.@.@..@.@@@@@@..@.@@@@@@@...@@.
+@@..@.@..@.@.@@.@@@@@@@..@..@@@@..@@@..@@@@@@.@@.@@@...@@...@.@...@@@@.@.@@@@@@.@.@@@@@@.@@.@.@@@.@@@..@..@@.@.@@@.@@..@@@@@@@@@@@..@.@@@.
+@.@@...@@.@@@@@@@@@@@..@@@.@@.@.@@@@@@@.@@.@@@@@@.@@.@..@.@..@.@@@@@@@@@@@@@@..@@@..@@@.@@@@.@@@.@@@...@@@.@.@.@.@.@..@..@@@@@@@..@.@@..@@
+@...@@@.@@@@@..@@..@..@@@@..@@.@@..@.@@@@.@@@..@.@@..@@@@@@@@.....@@.@@....@@@.@@@.@@.@@.@@@@@@.@@@@..@@@@.@..@@@@@@..@.@@@@@@.@@@@....@@.
+@.@...@@@@@@......@@@.@@.@@@@@@.@.@.@@@@@@@@@.@@.@@.@@@.@...@@..@@@@@@@..@@@.@@@@@@@@.@.@@.@@.@@@@..@@.@.@@.@.@.@@.@.@@@....@.@@@@@@..@.@@
+.@@@@.@@.@@@@@@@@@...@...@@@@..@@@.@@.@..@@.@@..@@@@@@.@.@@@.@@@....@@@.@.@...@.@.@@...@.@@@.@..@@@@@@@@@.@@....@@@..@@@@@@.@@@@@.@@@..@@@
+@@.@@..@.@@..@.@..@@.@@@@@@@.@.@@.@..@....@.@@@@@@.@@@@@.@..@.@@@@@.@@@.@@@@.@@@.@.@@@..@@.@@..@@..@@@.@@...@@@@@.@.@.@@@.@.@.@..@.@@.@@..
+@.@.@.@@@@..@@@@@@@@@@@..@@.@@@.@@...@@@@@..@@...@@@.....@@@@.@..@@@@@@@.@.@@.@.@@.@@.@@@@.@..@@.@@@@@@@..@@@@@.@..@@@@.@.@.@@@@..@@@...@.
+@@@@@.@@...@@@.@..@@@@@.@...@@@..@@...@.@@.@@@@@@@@@.@@@.@.@@@@@..@@@@@@..@.@@.@...@.@.@@@@..@@@.@@@@@@.@@@@@@@@.@@.@@.@@....@@@.@@@.@@@@@
+@.@..@@@@.@@@..@...@@@@.@.@@@@.@@@@@@@@@@@.@@.@.@@.@.@.@.@@....@@.@.@@..@@@@.@.@...@@@@@@@.@.@@@@.@.@@.@.......@.@@@.@.@.@@.@..@@@@@@..@.@
+.@.@@@.@@.@@@.@@@@@@@@@@.@@..@.@@...@.@.@@@@.@@@.@..@...@.@.@.@@@@.@@@@@@@....@.@.@@@@@.@@@@.@@@@.@.@@.@@...@@@@@@.@@.@@.@......@@@@@@@..@
+@@@@.@.@@..@@@@.@.@.@@@@@@.@@.@@.@@@@@@@..@.@.@@@@.@@@@@@@@.@.@@@.@...@..@@@@.@@@@@.@.@..@@@@@.@@@@@@@@@@.@@@@@.@@..@.@..@.@@@@@..@..@@@..
+@.@@.@..@..@@@@@@.@@@.@.@@.@@.@@.@@@@..@@.@...@.@@@@@.@@@.@.@.@@...@@@@@@@..@@.@@@....@@...@@.@@.@@@@@@.@.@...@@@.@.@@.@.@@..@@.@@@.@@.@@@
+@@@@@@@@.@@@.@@.@@@@@@..@@@@@@@..@@@@.@@@..@.@@@.@..@@.@@@@@.@@..@..@@..@@.@.@@@.@@@@@@@@@@@.@...@.@..@.@...@@..@.@.@@@.@@@@.@.@@..@@...@.
+@..@@@@@.@@@.@@..@.@.@@@.@.@....@@@.@@@@@@.@@@@.@@@@..@.@@@@..@.@..@.@..@.@.@.@@@@..@@......@@@@@....@.@.@@@@.@@@.@@@...@@@@.@@@@.@@.@@.@.
+@@@@.@.@@@@@@@@@.@.@@.@@@@@.@.@.@.@@@..@.@.@@..@...@@@@..@@@@@.@@@@.@@@@@@@@@@@@@@@.@@@..@.@@@.@@@@@@...@@@@...@@@@@.@@@@@@..@@@..@@.@@@.@
+@@@@.@@..@..@@@..@@@@@...@.@@....@@.@@@@@@@@......@@.@@..@@@@@.@@.@@@@@@@.@.@...@@@.@@@@.@..@..@@@@.@@@..@..@@.@@@@@.@@..@@@@@@@@@@@@....@
+@@..@@@@.@@@@....@@@.@@@@@@..@..@@@@.@@@@@@@@@@@@@@.@@@@.@..@.@.@@.@.@@@.@@..@.@@@.@@..@.@@@@.@...@@..@@.@.@.@@@@@@@..@@@@@@@@....@@@@@@.@
+.@@...@@@@@@...@.@@@.@@@@.@@.@..@@.@@@@@...@..@.@@.@...@@@@@@.@@@@@@@@@..@..@@@@@@@@@.@@.@.@@.@@@@@@@@...@@.@@@@...@.@@..@@.@@@.@.@.@@..@@
+@@@.@@.@@@.@@@.@.@@@.@@@@@@@@@.@.@@@@@@@.@.@...@.@...@@..@@.@@@.@@@@.@@...@@.@.@@@@.@@@@.@@.@@@@@@.@....@@@@.@..@...@..@@@@.@@@@@@.@@.@@@@
+.@@@.@@@.@.@@.@@@@..@.@@@@.@@.@@@...@.@@.@@@.@@@.@...@@@@@.@.@@@@.@@@@@@@@.@@@@@@.@@@...@.@...@@@.@@.@@.@@.@@..@.@@@@@.@@@@@@@@.@@.@@@@.@.
+.@@@@.@@..@.@@@@@.@@@@@@....@.@.@.@@@.@.@@@..@.@@..@...@@..@@@@@@..@@@@..@@.@@.@.@@@@@@@@@@@@.@@@.@@@@@@..@@@@.@@@.@.@@@@@@@@@@@@@@@..@@@@
+.@..@..@@@@@@...@@@@..@@@@.@.@.@@@@@@.@@@..@..@@@..@@...@@@@@@@.@@@@@.@@..@...@.@@.@...@@@...@@@@@@@@@..@@@@..@@@@.@.@@..@@@@@@@@..@@@..@.
+@@@@@...@@.@@...@@.@.@@@.@.@@@....@.@@@@.@@@.@.@@.@.@.@@...@@.@@@@.@@@@@@@@@.@..@.@.@@@..@@@@@.@@@@@@@@@.@@@.@@@..@.@..@...@.@.@..@@..@@@@
+@@.@.@@@@@..@@@@@@.....@.@@.@@@@@.@@..@@@@@@.@@@@@.@...@@..@@.@.@@@.@@@@.@@@@@@@.@@@@@@.@@@@@.@@.@@@.@@.@@...@.@@.@.@@@..@.@.@@@..@..@@@@@
+@@@@@@@@@...@@@@@.@@@.@.@.@.@@@@@@..@.@.@@@..@@@@@@@.@@@..@.@@@@@@..@@.@.....@.@@.@.@.@.@@@.@.@@@@@@@@@@.@.@@@@.@@@.....@@.@.@....@@.@@@..
+.@@@.@@.@@@.@..@@@@.@@@@.@@@@..@@@@.@@@@..@..@.@@@@...@@@@@.@@@@@..@@@@.@@@@..@@@@@@.@@@@..@@.@.@...@@@.@@@.....@@.@@...@..@@@.@.@@@.@@@@.
+.@@..@@@@@@.@@@@.@@..@@@..@@.@@@@@@@@.@@.@@@@@.@@@.@.@@..@@@.@...@@..@...@@.@@@@@@@@@@.@..@@@.@@@.@.@@@@@.@@@.@@@@.@@@@@@.@@.@@@..@.@@.@@@
+@@@@.@@@@@@@@.....@@@@@..@@@@@@@@@..@.@.@@.@........@@..@@...@@.@..@@@@@@@.@@...@@@@.@@@@....@@.@@@.@..@@..@.@@..@@@@@@@@@..@@....@.@.@@@.
+.@.@.@@....@..@@@@@@..@.@@@@@@@@@@@@@@..@@...@@@@@.@..@@@@@@.@@@@@@@@@.@.@@@@@@@..@@@@@@@@@.@@@..@..@@.@.@@@@......@..@@..@.@@..@.@@@....@
+@@@@.@@@@@@@@@..@@@@..@@@@@@@@@.@@@..@@.@@@@@@@..@@..@.@@@@@.@@@.@@..@@@@.@@@@@@..@@@@@.@@@....@.@@@@@.@@.@@@@....@..@.@@@@@@@@@.@@.@.@..@
+@@@.@@....@@@.@@@..@@@@@@@.@.@@@..@@@.@.@@@@@...@@@@.@.@@..@@.@@@.@..@@.@@@@@@@@.@.....@@.@.@@.@...@@..@.@@@.@@@.@@@.@@@@@@.@@@@@.@@@@@@@.
+@..@@@@..@.@@@@@@@@@@.@@..@@@@.@@@.@@@@.@@.@@@@@@@@@..@@.@@@.@.@..@@@@..@@.@@@.@@@@@@.@@@.@@.@@..@@@@@..@@@@@.@@..@.@@@.@..@@..@..@@@..@@@
+.@@@.@@.@@...@@@.@@@@@.@@@@.@@@..@.@.@...@.@.@.@@.@@@@@.@.@@@@.....@@.@@@@@@@@@@@@@..@@@@@@.@@@@@..@@@.@@@@@@.@@@.@@....@..@@@@.@@@@@@@..@
+@...@@@@@@@@@.....@..@@...@.@..@...@@@.@.@.@.@@@.@.@@.@..@@@@.@.@@.@.@.@@..@.@@.@@@.@@@@@...@@@@@..@@@@@@@..@@@@@@.@..@@@.@@@@@@.@@@@@@@@.
+@@@.@@.@@@@@@.@.@@@@..@.@@.@@@@@@@.@@@@.@@.@@@..@.@@@..@@@@@@@.@@@....@.@@.@@.@..@@@...@.@..@@@@@.@@@@@@.@.@@@...@...@.@@@@.@@@@@@.@@.@@@@
+.@@@..@@@..@@@@@@@@.@@..@...@@.@.@.@@.@@@.@@@@.@@@..@.@@.@.@.@@@@..@..@.@@@@.@@..@@@@@@@....@.@...@.@@.@@..@@..@@.@.@@.@.@.@.@@.@@@@@....@
+.@@.@@.@.@@@@@...@@@.@@.@@.@.@.@@.@.@@@@..@.@.@@@...@@@@.@@@@@@@@..@.@@..@.@@..@.@@.@..@.@@.@@.@@@@@.@.@@....@.@@@..@@.@@@@.@@@.@.@@@.@@@@
+@@@.@@@..@.@@..@@@.@@@.@@.@@@@..@@@.@..@@@..@@@@@.@.@.@.@@@@@.@@.@@..@@@...@.@@...@@@.@@@...@@.@..@.@@@...@@.@@@...@@@...@@@@..@@@@.@...@@
+..@...@.@@@.@@.....@.@@@@@..@@@.@.@@@@@@@@@@@@@@@.@..@@@@@.@...@@@@.@.@.@@.@.@.@@.@@.@@@@.@@@@@@@@@@@.@@@@.@@@..@.@@@.@..@@.@.@.@@.@.@@@@@
+@@.@@@@@@@@@@@@@@@@.@@.@@@.@@..@.@@@@@@..@@@.@.@.@@..@@@@@@..@@@@@@@@..@@@...@@@@@@@@.@@.@@@@.@@@@.@@@@@@@@.@..@@.@@@@@@@.@@@.@.@.@@@@..@@
+@@@@@@..@@.@@@.@.@..@@@.@@.@@.@@.@@@.@.@@.@@...@.....@@@.@.@.@@...@@@..@@.@@@@...@@.@@@@..@@@..@@.@@.@@@.@..@.@@@.@@.@@.@@@.@@..@@@.@@..@@
+@@@.@.@@@@.@@@@...@..@.@@.@..@@@.@@@@@@@.@@@@@..@.@..@.@.@@.@.@@@.@...@@@@@@@...@@@@@.@@.@@@.@@..@@..@....@..@.@.@.@@@@.@.@@@@@@...@@@@@@@
+.@.@.@@@.@.@@@@@@@@.@@@@@@..@@@.@..@..@@.@@@@..@@@.@.@@.@.@@@@.@.@@@@.@.@@..@@...@@@@@@@@@@.@@....@@@@@@@@@.@@@.@@@@....@@@..@@@@@@@.@@@..
+@.@.@@.@@...@@@@@@...@@@.....@@@@@@@@@@@@@@.@@.@@@@.@@...@@@@@@.@@.@@@@@@@@..@@@@@@..@@@.@@@.@.@.@@.@@@@@..@@..@@@..@..@.@@@@.@@@@@...@@..
+@.@@..@@@.@.@.@@@@@...@..@@.@.@....@.@@@@.@@...@@@@@..@@@@..@....@@.@@@@@.@@@@..@@.@@.@.@@..@@@@.@@.@@@@.@@.@@@@.@@.@@..@@.@@@.@..@..@@@..
+@@@@@@@@@@@@@@@..@@@@.@...@.@.@.@.@@@.@@@@...@@@..@.@..@...@@@@@@@..@..@.@@..@.@@@@.@@.@.@.......@@@@.@@@@..@.@@@@.@@@@..@@@.@@@@..@.@...@
+@..@@@@....@@.@...@..@@@@@...@.@@@@@..@@@@.@@..@...@@@@.@@.@.@@@@@@.@@@@@.@.@@@@.@.@.@@@@.@@.@@@.@@@@@.@.@@@@@.@.@@@@..@@.@..@..@@@@@.@.@@
+@.@..@..@@@.@@@.@.@@.@@@.@.@@@@...@@@@.@@@@..@@@..@...@@@@@@@@.@@@.@.@@@.@.@.@..@@@@@@@@@@@@@@@.@@.@.......@@@@..@@..@.@...@@..@@@...@@@.@
+@..@@@@@@@@@.@@.@@.@@@@@.@....@@.@@@@...@@@@.@.@@@.@@..@@@@..@..@.@@@@..@@@.@@@.@@@@.@..@@@@.@..@.@@..@@..@@.@@@@@@@@@.@....@.@@@@.@.@@@@@
+@@@@..@.@@@@@...@.@@@.@@@@.@...@.@@@@@..@..@@.@..@@@@..@@@.@@@@@@.@@@@@@.@@@@.@.@.@@@@@@@@..@.@..@@@.@@@@.@.@@@.@@@@@.@@...@@.@.@@.@.@.@@@
diff --git a/lib/naturals b/lib/naturals
@@ -0,0 +1 @@
+Subproject commit 441d32de3a512c9550c31d5f3f7b156bb9d8c64c
diff --git a/package.yaml b/package.yaml
@@ -34,7 +34,10 @@ default-extensions:
dependencies:
- base
- bytestring
+ - mtl
+ - naturals
- sparsec
+ - vector
executables:
01:
@@ -46,3 +49,6 @@ executables:
03:
source-dirs: ./03
main: Main.hs
+ 04:
+ source-dirs: ./04
+ main: Main.hs
diff --git a/stack.yaml b/stack.yaml
@@ -2,4 +2,5 @@ resolver: lts-23.23
packages:
- .
+ - lib/naturals
- lib/sparsec