11 part 2 done

This commit is contained in:
pingu 2024-12-11 10:28:20 +01:00
parent a20210b96f
commit ad760a6c83
2 changed files with 18 additions and 17 deletions

View File

@ -122,6 +122,7 @@ executable 11
-- other-extensions: -- other-extensions:
build-depends: base ^>=4.18.2.1 build-depends: base ^>=4.18.2.1
, split , split
, containers
hs-source-dirs: app hs-source-dirs: app
default-language: GHC2021 default-language: GHC2021
executable 12 executable 12

View File

@ -1,37 +1,37 @@
{-# LANGUAGE LambdaCase #-}
module Main where module Main where
import Data.Functor import Data.Functor
import Data.List.Split import Data.List.Split
import Data.IntMap (IntMap)
import qualified Data.IntMap as IM
parse :: String -> [Int] parse :: String -> IntMap Int
parse = (read <$>) . words parse = foldr (flip (IM.insertWith (+)) 1 . read) mempty . words
rules :: [(Int -> Bool, Int -> [Int])] rules :: [(Int -> Bool, Int -> IntMap Int)]
rules = rules =
[ [
((==0), const [1]) ((==0), const (IM.singleton 1 1))
,(even . length . show, \a -> let b = show a; s = length b in chunksOf (s `div` 2) b <&> read) ,(even . length . show,
,(const otherwise, pure . (*2024)) \a -> let b = show a; s = length b in
foldr (flip (IM.insertWith (+)) 1 . read) mempty (chunksOf (s `div` 2) b))
,(const otherwise, (`IM.singleton` 1) . (*2024))
] ]
applyRule :: Int -> [Int] applyRule :: Int -> IntMap Int
applyRule i = head . filter (/= mempty) $ rules >>= \(f,g) -> if f i then pure $ g i else pure mempty applyRule i = head . filter (/= mempty) $ rules >>= \(f,g) -> if f i then pure $ g i else pure mempty
step :: [Int] -> [Int] step :: IntMap Int -> IntMap Int
step = (applyRule =<<) step = IM.foldrWithKey (\s c n -> IM.unionWith (+) n ((c*) <$> applyRule s)) mempty
applyAmount :: Int -> a -> (a -> a) -> a applyAmount :: Int -> a -> (a -> a) -> a
applyAmount 0 a _ = a applyAmount 0 a _ = a
applyAmount n a f = f $ applyAmount (n-1) a f applyAmount n a f = f $ applyAmount (n-1) a f
solve1 :: [Int] -> Int solve :: Int -> IntMap Int -> Int
solve1 = length . flip (applyAmount 25) step solve i = sum . IM.elems . flip (applyAmount i) step
solve2 :: [Int] -> Int
solve2 = undefined
main :: IO () main :: IO ()
main = readFile "inputs/11" <&> parse >>= \i -> main = readFile "inputs/11" <&> parse >>= \i ->
print (solve1 i) >> print (solve 25 i) >>
print (solve2 i) print (solve 75 i)