Skip to content

Commit

Permalink
2024-11
Browse files Browse the repository at this point in the history
  • Loading branch information
glguy committed Dec 11, 2024
1 parent 1706f61 commit 9ee35f2
Show file tree
Hide file tree
Showing 4 changed files with 72 additions and 9 deletions.
20 changes: 11 additions & 9 deletions common/src/Advent/Input.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ module Advent.Input where

import Advent.Coord (Coord(..), coordLines)
import Data.Array.Unboxed qualified as A
import Data.List (findIndex)
import Data.Map (Map)
import Data.Map.Strict qualified as SMap
import System.Environment (getArgs)
Expand All @@ -38,22 +39,23 @@ getRawInput y d =
"+":input:_ -> pure input
fn:_ -> readFile fn

-- | Default input filename given a day number
inputFileName :: Int {- ^ day -} -> FilePath
inputFileName = printf "inputs/%02d.txt"

-- | Load input file as a list of lines.
getInputLines :: Int {- ^ year -} -> Int {- ^ day -} -> IO [String]
getInputLines y d = lines <$> getRawInput y d

-- | Load input file as a rectangular array of characters.
getInputArray :: Int {- ^ year -} -> Int {- ^ day -} -> IO (A.UArray Coord Char)
getInputArray y d =
do xs <- getInputLines y d
pure $! A.listArray (C 0 0, C (length xs - 1) (length (head xs) - 1)) (concat xs)
do xs <- getInputLines y d
w <- case xs of
[] -> fail "getInputArray: empty grid"
x : xs ->
case findIndex (\y -> length y /= w) xs of
Just i -> fail ("getInputArray: bad length on line " ++ show (i+2))
Nothing -> pure w
where w = length x
pure $! A.listArray (C 0 0, C (length xs - 1) (w - 1)) (concat xs)

-- | Load input file as a 2-dimensional map of characters.
getInputMap :: Int {- ^ year -} -> Int {- ^ day -} -> IO (Map Coord Char)
getInputMap y d =
do xs <- getInputLines y d
pure $! SMap.fromList (coordLines xs)
getInputMap y d = SMap.fromList . coordLines <$> getInputLines y d
1 change: 1 addition & 0 deletions inputs/2024/11.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
2 72 8949 0 981038 86311 246 7636740
5 changes: 5 additions & 0 deletions solutions/solutions.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -1162,3 +1162,8 @@ executable sln_2024_10
import: day
main-is: 2024/10.hs
build-depends: array, containers

executable sln_2024_11
import: day
main-is: 2024/11.hs
build-depends: containers
55 changes: 55 additions & 0 deletions solutions/src/2024/11.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,55 @@
{-# Language QuasiQuotes, ImportQualifiedPost #-}
{-|
Module : Main
Description : Day 11 solution
Copyright : (c) Eric Mertens, 2024
License : ISC
Maintainer : [email protected]
<https://adventofcode.com/2024/day/11>
This solution runs efficiently by remembering how many of each stone
there are and blinking all of that same kind of stone all at once.
While the problem does state that order is preserved, the question
it asks about the stones does not depend on order, so we forget that
order!
>>> :main + "125 17\n"
55312
65601038650482
-}
module Main (main) where

import Advent (format, times)
import Data.Map (Map)
import Data.Map.Strict qualified as Map

-- | >>> :main
-- 202019
-- 239321955280205
main :: IO ()
main =
do input <- [format|2024 11 %u& %n|]
print (solve 25 input)
print (solve 75 input)

-- | Compute the number of stones resulting from a starting set of stones
-- and a number of blink iterations.
solve :: Int -> [Int] -> Int
solve n input = sum (times n blinks (Map.fromListWith (+) [(i, 1) | i <- input]))

-- | Blink all the stones at once. Stone numbers are mapped to multiplicity.
blinks :: Map Int Int -> Map Int Int
blinks stones = Map.fromListWith (+) [(stone', n) | (stone, n) <- Map.assocs stones, stone' <- blink stone]

-- | Blink a single stone and figure out what stones it turns into.
blink :: Int -> [Int]
blink 0 = [1] -- 0 -> 1
blink n -- split in half if even length
| let str = show n
, let len = length str
, even len
, (l, r) <- splitAt (len `quot` 2) str
= [read l, read r]
blink n = [n * 2024] -- otherwise multiply by 2024

0 comments on commit 9ee35f2

Please sign in to comment.