commit e28c90bfbcb4378736d1d56f178cdec2edceebde
parent 9055130b57981dc524ed74ec3d496df5d29738f9
Author: Robert Russell <robert@rr3.xyz>
Date: Sun, 7 Dec 2025 20:25:11 -0800
Abstract out some common code
Diffstat:
10 files changed, 88 insertions(+), 92 deletions(-)
diff --git a/04/Common b/04/Common
@@ -0,0 +1 @@
+../lib/Common
+\ No newline at end of file
diff --git a/04/Main.hs b/04/Main.hs
@@ -1,44 +1,18 @@
module Main (main) where
+import Common.Cellular (Cellular)
+import Common.Cellular qualified as C
+import Common.Matrix (Matrix)
+import Common.Matrix qualified as M
+import Common.Util (count)
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)
@@ -48,16 +22,16 @@ kernel = [(-1, -1), (-1, 0), (-1, 1), (0, -1), (0, 1), (1, -1), (1, 0), (1, 1)]
forklift :: Cellular State State
forklift =
- self >>= \case
+ C.self >>= \case
Blank -> pure Blank
Removed -> pure Removed
- Filled -> bool Filled Removed . (< 4) . count (== Just Filled) <$> traverse neighbor kernel
+ Filled -> bool Filled Removed . (< 4) . count (== Just Filled) <$> traverse C.neighbor kernel
part1 :: Matrix State -> Int
-part1 = M.count (== Removed) . step forklift
+part1 = M.count (== Removed) . C.step forklift
part2 :: Matrix State -> Int
-part2 = M.count (== Removed) . stabilize forklift
+part2 = M.count (== Removed) . C.stabilize forklift
--------------------------------------------------------------------------------
-- Parsing
diff --git a/04/Matrix.hs b/04/Matrix.hs
@@ -1,48 +0,0 @@
-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/05/Common b/05/Common
@@ -0,0 +1 @@
+../lib/Common
+\ No newline at end of file
diff --git a/05/Common.hs b/05/Common.hs
@@ -0,0 +1 @@
+../lib/Common.hs
+\ No newline at end of file
diff --git a/05/Main.hs b/05/Main.hs
@@ -1,17 +1,12 @@
module Main (main) where
+import Common.Util (count)
import Control.Applicative
import Data.ByteString qualified as BS
import Sparsec
import System.Exit (die)
--------------------------------------------------------------------------------
--- Util
-
-count :: (a -> Bool) -> [a] -> Int
-count p = length . filter p
-
---------------------------------------------------------------------------------
-- Solution
-- It would be better to use an interval tree or similar data structure.
diff --git a/06/Main.hs b/06/Main.hs
@@ -9,9 +9,6 @@ import Sparsec
import System.Exit (die)
--------------------------------------------------------------------------------
--- Util
-
---------------------------------------------------------------------------------
-- Solution
data Operator = Add | Mul deriving (Show)
diff --git a/lib/Common/Cellular.hs b/lib/Common/Cellular.hs
@@ -0,0 +1,22 @@
+module Common.Cellular (Cellular, neighbor, self, step, stabilize) where
+
+import Common.Matrix (Matrix)
+import Common.Matrix qualified as M
+import Common.Util (untilFixed)
+import Control.Monad.Reader
+import Data.Maybe (fromJust)
+
+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)
diff --git a/lib/Common/Matrix.hs b/lib/Common/Matrix.hs
@@ -0,0 +1,39 @@
+module Common.Matrix (Matrix, nrows, ncols, generate, fromList, (!?), count) where
+
+import Common.Util (consensus)
+import Data.Vector (Vector)
+import Data.Vector qualified as V
+
+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/lib/Common/Util.hs b/lib/Common/Util.hs
@@ -0,0 +1,11 @@
+module Common.Util (count, consensus, untilFixed) where
+
+count :: (a -> Bool) -> [a] -> Int
+count p = length . filter p
+
+consensus :: (Eq a) => [a] -> Maybe a
+consensus [] = Nothing
+consensus (x : xs) = if all (== x) xs then Just x else Nothing
+
+untilFixed :: (Eq a) => (a -> a) -> a -> a
+untilFixed f x = let x' = f x in if x' == x then x' else untilFixed f x'