Done day 19
authorNeil Smith <NeilNjae@users.noreply.github.com>
Wed, 21 Dec 2022 11:24:26 +0000 (11:24 +0000)
committerNeil Smith <NeilNjae@users.noreply.github.com>
Wed, 21 Dec 2022 11:53:27 +0000 (11:53 +0000)
advent-of-code22.cabal
advent19/Main.hs [new file with mode: 0644]
data/advent19.txt [new file with mode: 0644]
data/advent19a.txt [new file with mode: 0644]
problems/day19.html [new file with mode: 0644]

index 74c5ea99eff72d5ea87d2d8fcb7cb1deff58faf0..d9def44be270d183803ee2367be75adfc4d1d375 100644 (file)
@@ -190,3 +190,13 @@ executable advent18
   import: common-extensions, build-directives
   main-is: advent18/Main.hs
   build-depends: text, attoparsec, containers, linear, lens
+
+executable advent19
+  import: common-extensions, build-directives
+  main-is: advent19/Main.hs
+  build-depends: text, attoparsec, containers, pqueue, mtl, lens, multiset, parallel, deepseq
+
+executable advent20
+  import: common-extensions, build-directives
+  main-is: advent20/Main.hs
+  build-depends: data-clist , lens
diff --git a/advent19/Main.hs b/advent19/Main.hs
new file mode 100644 (file)
index 0000000..b5cd5c4
--- /dev/null
@@ -0,0 +1,211 @@
+-- Writeup at https://work.njae.me.uk/2022/12/21/advent-of-code-2022-day-19/
+
+import Debug.Trace
+
+import AoC
+import Data.Text (Text)
+import qualified Data.Text.IO as TIO
+import Data.Attoparsec.Text hiding (take, D)
+import Control.Applicative
+import qualified Data.PQueue.Prio.Max as P
+import qualified Data.Set as S
+import qualified Data.Sequence as Q
+import qualified Data.Map.Strict as M
+import Data.Map.Strict ((!))
+import Data.MultiSet as MS
+import Data.Sequence ((|>)) 
+import Data.List
+import Data.Maybe
+import Data.Ord
+import Control.Monad.Reader
+import Control.Lens hiding ((<|), (|>), (:>), (:<), indices)
+import Control.Parallel.Strategies
+import Control.DeepSeq
+
+-- pattern Empty   <- (Q.viewl -> Q.EmptyL)  where Empty = Q.empty
+-- pattern x :< xs <- (Q.viewl -> x Q.:< xs) where (:<)  = (Q.<|) 
+-- pattern xs :> x <- (Q.viewr -> xs Q.:> x) where (:>)  = (Q.|>) 
+
+data Resource = Ore | Clay | Obsidian | Geode
+    deriving (Show, Eq, Ord)
+
+type Collection = MS.MultiSet Resource
+
+type Blueprint = M.Map Resource Collection
+
+data TimedBlueprint = TimedBlueprint { getBlueprint :: Blueprint, getTimeLimit :: Int, getMaxRobots :: Collection}
+    deriving (Show, Eq, Ord)
+
+type BlueprintContext = Reader TimedBlueprint
+
+data SingleSearchState = SingleSearchState
+    { _resources :: Collection
+    , _robots :: Collection
+    } deriving (Eq, Show, Ord)
+makeLenses ''SingleSearchState
+
+instance NFData SingleSearchState where
+  rnf a = a `seq` ()
+
+data Agendum s = 
+    Agendum { _current :: s
+            , _trail :: Q.Seq s
+            , _trailBenefit :: Int
+            , _benefit :: Int
+            } deriving (Show, Eq, Ord)
+makeLenses ''Agendum   
+
+type Agenda s = P.MaxPQueue Int (Agendum s)
+
+type ExploredStates s = S.Set (s, Int, Int)
+
+
+class (Eq s, Ord s, Show s) => SearchState s where
+  emptySearchState :: s
+  successors :: s -> BlueprintContext (Q.Seq s)
+  estimateBenefit :: s -> Int -> BlueprintContext Int
+
+instance SearchState SingleSearchState where
+  emptySearchState = SingleSearchState { _resources = MS.empty, _robots = MS.singleton Ore }
+
+  successors state = 
+    do blueprint <- asks getBlueprint
+       maxRobots <- asks getMaxRobots
+       let buildableRobots = M.keys $ M.filter (\required -> required `MS.isSubsetOf` (state ^. resources)) blueprint
+       --- if more bots than needed for making any single bot, don't make more of that bot
+       let usefulRobots = MS.foldOccur (\res maxNeeded rs -> 
+                                          if (MS.occur res (state ^. robots)) >= maxNeeded 
+                                          then Data.List.delete res rs
+                                          else rs
+                                        ) buildableRobots maxRobots
+       let madeRobots = [ state & robots %~ MS.insert robot 
+                                & resources %~ ( `MS.difference` (blueprint ! robot) )
+                        | robot <- usefulRobots
+                        ]
+       let afterBuild = [state] ++ madeRobots
+       let afterGather = fmap (\s -> s & resources %~ (MS.union (state ^. robots))) afterBuild
+       return $ Q.fromList afterGather
+
+
+  estimateBenefit currentState timeElapsed = 
+    do timeLimit <- asks getTimeLimit
+       let timeRemaining = timeLimit - (timeElapsed + 1)
+       let currentGeodes = MS.occur Geode (currentState ^. resources)
+       let currentRobotsGather = (MS.occur Geode (currentState ^. robots)) * timeRemaining
+       let newRobotsGather = (timeRemaining * (timeRemaining + 1)) `div` 2 
+       return $ currentGeodes + currentRobotsGather + newRobotsGather
+
+
+main :: IO ()
+main = 
+  do  dataFileName <- getDataFileName
+      text <- TIO.readFile dataFileName
+      let blueprints = successfulParse text
+      print $ part1 blueprints
+      print $ part2 blueprints
+
+part1 :: [(Int, Blueprint)] -> Int
+part1 blueprints = sum [n * (MS.occur Geode (r ^. resources)) | (n, r) <- results]
+    where results = [ (n, _current $ fromJust $ runReader searchSpace (TimedBlueprint blueprint 24 (robotLimits blueprint)) )
+                    | (n, blueprint) <- blueprints ] :: [(Int, SingleSearchState)]
+          robotLimits bp = M.foldl' MS.maxUnion MS.empty bp
+
+
+part2 :: [(Int, Blueprint)] -> Int
+part2 blueprints = product [MS.occur Geode (r ^. resources) | r <- pResults]
+    where results = [ _current $ fromJust $ runReader searchSpace (TimedBlueprint blueprint 32 (robotLimits blueprint))
+                    | (_, blueprint) <- (take 3 blueprints) ] :: [SingleSearchState]
+          pResults = parMap rdeepseq id results
+          robotLimits bp = M.foldl' MS.maxUnion MS.empty bp
+
+searchSpace :: SearchState s => BlueprintContext (Maybe (Agendum s))
+searchSpace = 
+    do agenda <- initAgenda 
+       -- aStar agenda S.empty
+       res <- aStar agenda S.empty
+       return (res `seq` res)
+
+initAgenda :: SearchState s => BlueprintContext (Agenda s)
+initAgenda = 
+    do let startState = emptySearchState 
+       b <- estimateBenefit startState 0
+       return $ P.singleton b Agendum { _current = startState, _trail = Q.empty, _trailBenefit = 0, _benefit = b}
+
+aStar ::  SearchState s => Agenda s -> ExploredStates s -> BlueprintContext (Maybe (Agendum s))
+aStar agenda closed 
+    -- | trace ("Peeping " ++ (show $ fst $ P.findMin agenda) ++ ": " ++ (show reached) ++ " <- " ++ (show $ toList $ Q.take 1 $ _trail $ currentAgendum) ++ " :: " ++ (show newAgenda)) False = undefined
+    -- | trace ("Peeping " ++ (show $ _current $ snd $ P.findMax agenda) ++ " benefit " ++ (show $ fst $ P.findMax agenda) ++ " : elapsed " ++ (show $ Q.length $ _trail $ snd $ P.findMax agenda)) False = undefined
+    | P.null agenda = return Nothing
+    | otherwise = 
+        do  let (_, currentAgendum) = P.findMax agenda
+            let reached = currentAgendum ^. current
+            nexts <- candidates currentAgendum closed
+            let newAgenda = foldl' (\q a -> P.insert (_benefit a) a q) (P.deleteMax agenda) nexts
+            -- let beamAgenda = P.fromDescList $ P.take 10000 newAgenda -- agenda beam width
+            -- let beamAgenda = P.fromDescList $ P.take 5000 newAgenda -- agenda beam width
+            reachedGoal <- isGoal currentAgendum
+            let cl = (reached, currentAgendum ^. trailBenefit, Q.length $ currentAgendum ^. trail)
+            if reachedGoal
+            then return (Just currentAgendum)
+            else if (cl `S.member` closed)
+                 then aStar (P.deleteMax agenda) closed
+                 -- else aStar newAgenda (S.insert cl closed)
+                 else aStar newAgenda (S.insert cl closed)
+
+candidates :: SearchState s => Agendum s -> ExploredStates s -> BlueprintContext (Q.Seq (Agendum s))
+candidates agendum closed = 
+    do  let candidate = agendum ^. current
+        let previous = agendum ^. trail
+        let prevBenefit = agendum ^. trailBenefit
+        succs <- successors candidate
+        succAgs <- mapM (makeAgendum previous prevBenefit) succs
+        let nonloops = Q.filter (\s -> (s ^. current, s ^. trailBenefit, Q.length $ s ^. trail) `S.notMember` closed) succAgs
+        return nonloops
+
+makeAgendum :: SearchState s => Q.Seq s -> Int -> s -> BlueprintContext (Agendum s)
+makeAgendum previous prevBenefit newState = 
+    do predicted <- estimateBenefit newState (Q.length previous)
+       let newTrail = previous |> newState
+       -- let incurred = geodesFound newState 
+       let incurred = 0
+       return Agendum { _current = newState
+                      , _trail = newTrail
+                      , _trailBenefit = incurred
+                      , _benefit = incurred + predicted
+                      }
+
+isGoal :: SearchState s => Agendum s -> BlueprintContext Bool
+isGoal agendum = 
+  do timeLimit <- asks getTimeLimit
+     return $ Q.length (agendum ^. trail) == timeLimit
+
+-- Parse the input file
+
+blueprintsP :: Parser [(Int, Blueprint)]
+blueprintP :: Parser (Int, Blueprint)
+robotP :: Parser (Resource, Collection)
+requirementsP :: Parser Collection
+requirementP :: Parser (Resource, Int)
+resourceP, oreP, clayP, obsidianP, geodeP :: Parser Resource
+
+blueprintsP = blueprintP `sepBy` endOfLine
+blueprintP = blueprintify <$> (("Blueprint " *> decimal) <* ": ") <*> (robotP `sepBy` ". ") <* "."
+  where blueprintify n robots = 
+          (n, M.fromList robots)
+robotP = (,) <$> ("Each " *> resourceP) <*> (" robot costs " *> requirementsP)
+
+requirementsP = MS.fromOccurList <$> (requirementP `sepBy` " and ")
+
+requirementP = (flip (,)) <$> (decimal <* " ") <*> resourceP
+
+resourceP = oreP <|> clayP <|> obsidianP <|> geodeP
+oreP = Ore <$ "ore"
+clayP = Clay <$ "clay"
+obsidianP = Obsidian <$ "obsidian"
+geodeP = Geode <$ "geode"
+
+successfulParse :: Text -> [(Int, Blueprint)]
+successfulParse input = 
+  case parseOnly blueprintsP input of
+    Left  _err -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err
+    Right blueprints -> blueprints
\ No newline at end of file
diff --git a/data/advent19.txt b/data/advent19.txt
new file mode 100644 (file)
index 0000000..125d399
--- /dev/null
@@ -0,0 +1,30 @@
+Blueprint 1: Each ore robot costs 4 ore. Each clay robot costs 4 ore. Each obsidian robot costs 4 ore and 7 clay. Each geode robot costs 2 ore and 19 obsidian.
+Blueprint 2: Each ore robot costs 2 ore. Each clay robot costs 4 ore. Each obsidian robot costs 4 ore and 20 clay. Each geode robot costs 4 ore and 18 obsidian.
+Blueprint 3: Each ore robot costs 4 ore. Each clay robot costs 4 ore. Each obsidian robot costs 3 ore and 20 clay. Each geode robot costs 2 ore and 10 obsidian.
+Blueprint 4: Each ore robot costs 3 ore. Each clay robot costs 4 ore. Each obsidian robot costs 2 ore and 19 clay. Each geode robot costs 2 ore and 12 obsidian.
+Blueprint 5: Each ore robot costs 3 ore. Each clay robot costs 4 ore. Each obsidian robot costs 3 ore and 20 clay. Each geode robot costs 3 ore and 14 obsidian.
+Blueprint 6: Each ore robot costs 3 ore. Each clay robot costs 4 ore. Each obsidian robot costs 2 ore and 15 clay. Each geode robot costs 3 ore and 7 obsidian.
+Blueprint 7: Each ore robot costs 3 ore. Each clay robot costs 3 ore. Each obsidian robot costs 2 ore and 19 clay. Each geode robot costs 2 ore and 20 obsidian.
+Blueprint 8: Each ore robot costs 2 ore. Each clay robot costs 3 ore. Each obsidian robot costs 3 ore and 13 clay. Each geode robot costs 2 ore and 20 obsidian.
+Blueprint 9: Each ore robot costs 2 ore. Each clay robot costs 2 ore. Each obsidian robot costs 2 ore and 8 clay. Each geode robot costs 2 ore and 14 obsidian.
+Blueprint 10: Each ore robot costs 4 ore. Each clay robot costs 4 ore. Each obsidian robot costs 2 ore and 11 clay. Each geode robot costs 3 ore and 14 obsidian.
+Blueprint 11: Each ore robot costs 3 ore. Each clay robot costs 4 ore. Each obsidian robot costs 4 ore and 5 clay. Each geode robot costs 4 ore and 8 obsidian.
+Blueprint 12: Each ore robot costs 3 ore. Each clay robot costs 3 ore. Each obsidian robot costs 2 ore and 16 clay. Each geode robot costs 2 ore and 18 obsidian.
+Blueprint 13: Each ore robot costs 3 ore. Each clay robot costs 4 ore. Each obsidian robot costs 2 ore and 11 clay. Each geode robot costs 2 ore and 10 obsidian.
+Blueprint 14: Each ore robot costs 4 ore. Each clay robot costs 4 ore. Each obsidian robot costs 2 ore and 14 clay. Each geode robot costs 3 ore and 17 obsidian.
+Blueprint 15: Each ore robot costs 3 ore. Each clay robot costs 3 ore. Each obsidian robot costs 3 ore and 19 clay. Each geode robot costs 3 ore and 17 obsidian.
+Blueprint 16: Each ore robot costs 2 ore. Each clay robot costs 4 ore. Each obsidian robot costs 3 ore and 20 clay. Each geode robot costs 2 ore and 17 obsidian.
+Blueprint 17: Each ore robot costs 4 ore. Each clay robot costs 4 ore. Each obsidian robot costs 3 ore and 14 clay. Each geode robot costs 4 ore and 8 obsidian.
+Blueprint 18: Each ore robot costs 2 ore. Each clay robot costs 3 ore. Each obsidian robot costs 3 ore and 9 clay. Each geode robot costs 3 ore and 9 obsidian.
+Blueprint 19: Each ore robot costs 4 ore. Each clay robot costs 4 ore. Each obsidian robot costs 2 ore and 10 clay. Each geode robot costs 3 ore and 14 obsidian.
+Blueprint 20: Each ore robot costs 3 ore. Each clay robot costs 3 ore. Each obsidian robot costs 2 ore and 13 clay. Each geode robot costs 3 ore and 12 obsidian.
+Blueprint 21: Each ore robot costs 4 ore. Each clay robot costs 3 ore. Each obsidian robot costs 4 ore and 15 clay. Each geode robot costs 4 ore and 9 obsidian.
+Blueprint 22: Each ore robot costs 3 ore. Each clay robot costs 3 ore. Each obsidian robot costs 3 ore and 20 clay. Each geode robot costs 2 ore and 12 obsidian.
+Blueprint 23: Each ore robot costs 4 ore. Each clay robot costs 3 ore. Each obsidian robot costs 4 ore and 19 clay. Each geode robot costs 4 ore and 12 obsidian.
+Blueprint 24: Each ore robot costs 4 ore. Each clay robot costs 4 ore. Each obsidian robot costs 4 ore and 15 clay. Each geode robot costs 3 ore and 8 obsidian.
+Blueprint 25: Each ore robot costs 2 ore. Each clay robot costs 3 ore. Each obsidian robot costs 3 ore and 11 clay. Each geode robot costs 2 ore and 16 obsidian.
+Blueprint 26: Each ore robot costs 3 ore. Each clay robot costs 4 ore. Each obsidian robot costs 3 ore and 17 clay. Each geode robot costs 3 ore and 7 obsidian.
+Blueprint 27: Each ore robot costs 4 ore. Each clay robot costs 4 ore. Each obsidian robot costs 3 ore and 7 clay. Each geode robot costs 3 ore and 20 obsidian.
+Blueprint 28: Each ore robot costs 4 ore. Each clay robot costs 3 ore. Each obsidian robot costs 3 ore and 10 clay. Each geode robot costs 2 ore and 10 obsidian.
+Blueprint 29: Each ore robot costs 4 ore. Each clay robot costs 4 ore. Each obsidian robot costs 4 ore and 17 clay. Each geode robot costs 2 ore and 13 obsidian.
+Blueprint 30: Each ore robot costs 4 ore. Each clay robot costs 3 ore. Each obsidian robot costs 4 ore and 20 clay. Each geode robot costs 4 ore and 8 obsidian.
\ No newline at end of file
diff --git a/data/advent19a.txt b/data/advent19a.txt
new file mode 100644 (file)
index 0000000..5212cde
--- /dev/null
@@ -0,0 +1,2 @@
+Blueprint 1: Each ore robot costs 4 ore. Each clay robot costs 2 ore. Each obsidian robot costs 3 ore and 14 clay. Each geode robot costs 2 ore and 7 obsidian.
+Blueprint 2: Each ore robot costs 2 ore. Each clay robot costs 3 ore. Each obsidian robot costs 3 ore and 8 clay. Each geode robot costs 3 ore and 12 obsidian.
\ No newline at end of file
diff --git a/problems/day19.html b/problems/day19.html
new file mode 100644 (file)
index 0000000..aa0ceb2
--- /dev/null
@@ -0,0 +1,476 @@
+<!DOCTYPE html>
+<html lang="en-us">
+<head>
+<meta charset="utf-8"/>
+<title>Day 19 - Advent of Code 2022</title>
+<!--[if lt IE 9]><script src="/static/html5.js"></script><![endif]-->
+<link href='//fonts.googleapis.com/css?family=Source+Code+Pro:300&subset=latin,latin-ext' rel='stylesheet' type='text/css'/>
+<link rel="stylesheet" type="text/css" href="/static/style.css?30"/>
+<link rel="stylesheet alternate" type="text/css" href="/static/highcontrast.css?0" title="High Contrast"/>
+<link rel="shortcut icon" href="/favicon.png"/>
+<script>window.addEventListener('click', function(e,s,r){if(e.target.nodeName==='CODE'&&e.detail===3){s=window.getSelection();s.removeAllRanges();r=document.createRange();r.selectNodeContents(e.target);s.addRange(r);}});</script>
+</head><!--
+
+
+
+
+Oh, hello!  Funny seeing you here.
+
+I appreciate your enthusiasm, but you aren't going to find much down here.
+There certainly aren't clues to any of the puzzles.  The best surprises don't
+even appear in the source until you unlock them for real.
+
+Please be careful with automated requests; I'm not a massive company, and I can
+only take so much traffic.  Please be considerate so that everyone gets to play.
+
+If you're curious about how Advent of Code works, it's running on some custom
+Perl code. Other than a few integrations (auth, analytics, social media), I
+built the whole thing myself, including the design, animations, prose, and all
+of the puzzles.
+
+The puzzles are most of the work; preparing a new calendar and a new set of
+puzzles each year takes all of my free time for 4-5 months. A lot of effort
+went into building this thing - I hope you're enjoying playing it as much as I
+enjoyed making it for you!
+
+If you'd like to hang out, I'm @ericwastl on Twitter.
+
+- Eric Wastl
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+-->
+<body>
+<header><div><h1 class="title-global"><a href="/">Advent of Code</a></h1><nav><ul><li><a href="/2022/about">[About]</a></li><li><a href="/2022/events">[Events]</a></li><li><a href="https://teespring.com/stores/advent-of-code" target="_blank">[Shop]</a></li><li><a href="/2022/settings">[Settings]</a></li><li><a href="/2022/auth/logout">[Log Out]</a></li></ul></nav><div class="user">Neil Smith <a href="/2022/support" class="supporter-badge" title="Advent of Code Supporter">(AoC++)</a> <span class="star-count">38*</span></div></div><div><h1 class="title-event">&nbsp;&nbsp;&nbsp;<span class="title-event-wrap">int y=</span><a href="/2022">2022</a><span class="title-event-wrap">;</span></h1><nav><ul><li><a href="/2022">[Calendar]</a></li><li><a href="/2022/support">[AoC++]</a></li><li><a href="/2022/sponsors">[Sponsors]</a></li><li><a href="/2022/leaderboard">[Leaderboard]</a></li><li><a href="/2022/stats">[Stats]</a></li></ul></nav></div></header>
+
+<div id="sidebar">
+<div id="sponsor"><div class="quiet">Our <a href="/2022/sponsors">sponsors</a> help make Advent of Code possible:</div><div class="sponsor"><a href="https://www.axis.com/" target="_blank" onclick="if(ga)ga('send','event','sponsor','sidebar',this.href);" rel="noopener">Axis</a> - All we want for Christmas is your application, pls! ----------------- &lt;embedded, cloud, Machine learning, fullstack&gt; our cameras require it all</div></div>
+</div><!--/sidebar-->
+
+<main>
+<article class="day-desc"><h2>--- Day 19: Not Enough Minerals ---</h2><p>Your scans show that the lava did indeed form obsidian!</p>
+<p>The wind has changed direction enough to stop sending lava droplets toward you, so you and the elephants exit the cave. As you do, you notice a collection of <a href="https://en.wikipedia.org/wiki/Geode" target="_blank">geodes</a> around the pond. Perhaps you could use the obsidian to create some <em>geode-cracking robots</em> and break them open?</p>
+<p>To collect the obsidian from the bottom of the pond, you'll need waterproof <em>obsidian-collecting robots</em>. Fortunately, there is an abundant amount of clay nearby that you can use to make them waterproof.</p>
+<p>In order to harvest the clay, you'll need special-purpose <em>clay-collecting robots</em>. To make any type of robot, you'll need <em>ore</em>, which is also plentiful but in the opposite direction from the clay.</p>
+<p>Collecting ore requires <em>ore-collecting robots</em> with big drills. Fortunately, <em>you have exactly one ore-collecting robot</em> in your pack that you can use to <span title="If You Give A Mouse An Ore-Collecting Robot">kickstart</span> the whole operation.</p>
+<p>Each robot can collect 1 of its resource type per minute. It also takes one minute for the robot factory (also conveniently from your pack) to construct any type of robot, although it consumes the necessary resources available when construction begins.</p>
+<p>The robot factory has many <em>blueprints</em> (your puzzle input) you can choose from, but once you've configured it with a blueprint, you can't change it. You'll need to work out which blueprint is best.</p>
+<p>For example:</p>
+<pre><code>Blueprint 1:
+  Each ore robot costs 4 ore.
+  Each clay robot costs 2 ore.
+  Each obsidian robot costs 3 ore and 14 clay.
+  Each geode robot costs 2 ore and 7 obsidian.
+
+Blueprint 2:
+  Each ore robot costs 2 ore.
+  Each clay robot costs 3 ore.
+  Each obsidian robot costs 3 ore and 8 clay.
+  Each geode robot costs 3 ore and 12 obsidian.
+</code></pre>
+<p>(Blueprints have been line-wrapped here for legibility. The robot factory's actual assortment of blueprints are provided one blueprint per line.)</p>
+<p>The elephants are starting to look hungry, so you shouldn't take too long; you need to figure out which blueprint would maximize the number of opened geodes after <em>24 minutes</em> by figuring out which robots to build and when to build them.</p>
+<p>Using blueprint 1 in the example above, the largest number of geodes you could open in 24 minutes is <code><em>9</em></code>. One way to achieve that is:</p>
+<pre><code>== Minute 1 ==
+1 ore-collecting robot collects 1 ore; you now have 1 ore.
+
+== Minute 2 ==
+1 ore-collecting robot collects 1 ore; you now have 2 ore.
+
+== Minute 3 ==
+Spend 2 ore to start building a clay-collecting robot.
+1 ore-collecting robot collects 1 ore; you now have 1 ore.
+The new clay-collecting robot is ready; you now have 1 of them.
+
+== Minute 4 ==
+1 ore-collecting robot collects 1 ore; you now have 2 ore.
+1 clay-collecting robot collects 1 clay; you now have 1 clay.
+
+== Minute 5 ==
+Spend 2 ore to start building a clay-collecting robot.
+1 ore-collecting robot collects 1 ore; you now have 1 ore.
+1 clay-collecting robot collects 1 clay; you now have 2 clay.
+The new clay-collecting robot is ready; you now have 2 of them.
+
+== Minute 6 ==
+1 ore-collecting robot collects 1 ore; you now have 2 ore.
+2 clay-collecting robots collect 2 clay; you now have 4 clay.
+
+== Minute 7 ==
+Spend 2 ore to start building a clay-collecting robot.
+1 ore-collecting robot collects 1 ore; you now have 1 ore.
+2 clay-collecting robots collect 2 clay; you now have 6 clay.
+The new clay-collecting robot is ready; you now have 3 of them.
+
+== Minute 8 ==
+1 ore-collecting robot collects 1 ore; you now have 2 ore.
+3 clay-collecting robots collect 3 clay; you now have 9 clay.
+
+== Minute 9 ==
+1 ore-collecting robot collects 1 ore; you now have 3 ore.
+3 clay-collecting robots collect 3 clay; you now have 12 clay.
+
+== Minute 10 ==
+1 ore-collecting robot collects 1 ore; you now have 4 ore.
+3 clay-collecting robots collect 3 clay; you now have 15 clay.
+
+== Minute 11 ==
+Spend 3 ore and 14 clay to start building an obsidian-collecting robot.
+1 ore-collecting robot collects 1 ore; you now have 2 ore.
+3 clay-collecting robots collect 3 clay; you now have 4 clay.
+The new obsidian-collecting robot is ready; you now have 1 of them.
+
+== Minute 12 ==
+Spend 2 ore to start building a clay-collecting robot.
+1 ore-collecting robot collects 1 ore; you now have 1 ore.
+3 clay-collecting robots collect 3 clay; you now have 7 clay.
+1 obsidian-collecting robot collects 1 obsidian; you now have 1 obsidian.
+The new clay-collecting robot is ready; you now have 4 of them.
+
+== Minute 13 ==
+1 ore-collecting robot collects 1 ore; you now have 2 ore.
+4 clay-collecting robots collect 4 clay; you now have 11 clay.
+1 obsidian-collecting robot collects 1 obsidian; you now have 2 obsidian.
+
+== Minute 14 ==
+1 ore-collecting robot collects 1 ore; you now have 3 ore.
+4 clay-collecting robots collect 4 clay; you now have 15 clay.
+1 obsidian-collecting robot collects 1 obsidian; you now have 3 obsidian.
+
+== Minute 15 ==
+Spend 3 ore and 14 clay to start building an obsidian-collecting robot.
+1 ore-collecting robot collects 1 ore; you now have 1 ore.
+4 clay-collecting robots collect 4 clay; you now have 5 clay.
+1 obsidian-collecting robot collects 1 obsidian; you now have 4 obsidian.
+The new obsidian-collecting robot is ready; you now have 2 of them.
+
+== Minute 16 ==
+1 ore-collecting robot collects 1 ore; you now have 2 ore.
+4 clay-collecting robots collect 4 clay; you now have 9 clay.
+2 obsidian-collecting robots collect 2 obsidian; you now have 6 obsidian.
+
+== Minute 17 ==
+1 ore-collecting robot collects 1 ore; you now have 3 ore.
+4 clay-collecting robots collect 4 clay; you now have 13 clay.
+2 obsidian-collecting robots collect 2 obsidian; you now have 8 obsidian.
+
+== Minute 18 ==
+Spend 2 ore and 7 obsidian to start building a geode-cracking robot.
+1 ore-collecting robot collects 1 ore; you now have 2 ore.
+4 clay-collecting robots collect 4 clay; you now have 17 clay.
+2 obsidian-collecting robots collect 2 obsidian; you now have 3 obsidian.
+The new geode-cracking robot is ready; you now have 1 of them.
+
+== Minute 19 ==
+1 ore-collecting robot collects 1 ore; you now have 3 ore.
+4 clay-collecting robots collect 4 clay; you now have 21 clay.
+2 obsidian-collecting robots collect 2 obsidian; you now have 5 obsidian.
+1 geode-cracking robot cracks 1 geode; you now have 1 open geode.
+
+== Minute 20 ==
+1 ore-collecting robot collects 1 ore; you now have 4 ore.
+4 clay-collecting robots collect 4 clay; you now have 25 clay.
+2 obsidian-collecting robots collect 2 obsidian; you now have 7 obsidian.
+1 geode-cracking robot cracks 1 geode; you now have 2 open geodes.
+
+== Minute 21 ==
+Spend 2 ore and 7 obsidian to start building a geode-cracking robot.
+1 ore-collecting robot collects 1 ore; you now have 3 ore.
+4 clay-collecting robots collect 4 clay; you now have 29 clay.
+2 obsidian-collecting robots collect 2 obsidian; you now have 2 obsidian.
+1 geode-cracking robot cracks 1 geode; you now have 3 open geodes.
+The new geode-cracking robot is ready; you now have 2 of them.
+
+== Minute 22 ==
+1 ore-collecting robot collects 1 ore; you now have 4 ore.
+4 clay-collecting robots collect 4 clay; you now have 33 clay.
+2 obsidian-collecting robots collect 2 obsidian; you now have 4 obsidian.
+2 geode-cracking robots crack 2 geodes; you now have 5 open geodes.
+
+== Minute 23 ==
+1 ore-collecting robot collects 1 ore; you now have 5 ore.
+4 clay-collecting robots collect 4 clay; you now have 37 clay.
+2 obsidian-collecting robots collect 2 obsidian; you now have 6 obsidian.
+2 geode-cracking robots crack 2 geodes; you now have 7 open geodes.
+
+== Minute 24 ==
+1 ore-collecting robot collects 1 ore; you now have 6 ore.
+4 clay-collecting robots collect 4 clay; you now have 41 clay.
+2 obsidian-collecting robots collect 2 obsidian; you now have 8 obsidian.
+2 geode-cracking robots crack 2 geodes; you now have 9 open geodes.
+</code></pre>
+<p>However, by using blueprint 2 in the example above, you could do even better: the largest number of geodes you could open in 24 minutes is <code><em>12</em></code>.</p>
+<p>Determine the <em>quality level</em> of each blueprint by <em>multiplying that blueprint's ID number</em> with the largest number of geodes that can be opened in 24 minutes using that blueprint. In this example, the first blueprint has ID 1 and can open 9 geodes, so its quality level is <code><em>9</em></code>. The second blueprint has ID 2 and can open 12 geodes, so its quality level is <code><em>24</em></code>. Finally, if you <em>add up the quality levels</em> of all of the blueprints in the list, you get <code><em>33</em></code>.</p>
+<p>Determine the quality level of each blueprint using the largest number of geodes it could produce in 24 minutes. <em>What do you get if you add up the quality level of all of the blueprints in your list?</em></p>
+</article>
+<p>Your puzzle answer was <code>1199</code>.</p><article class="day-desc"><h2 id="part2">--- Part Two ---</h2><p>While you were choosing the best blueprint, the elephants found some food on their own, so you're not in as much of a hurry; you figure you probably have <em>32 minutes</em> before the wind changes direction again and you'll need to get out of range of the erupting volcano.</p>
+<p>Unfortunately, one of the elephants <em>ate most of your blueprint list</em>! Now, only the first three blueprints in your list are intact.</p>
+<p>In 32 minutes, the largest number of geodes blueprint 1 (from the example above) can open is <code><em>56</em></code>. One way to achieve that is:</p>
+<pre><code>== Minute 1 ==
+1 ore-collecting robot collects 1 ore; you now have 1 ore.
+
+== Minute 2 ==
+1 ore-collecting robot collects 1 ore; you now have 2 ore.
+
+== Minute 3 ==
+1 ore-collecting robot collects 1 ore; you now have 3 ore.
+
+== Minute 4 ==
+1 ore-collecting robot collects 1 ore; you now have 4 ore.
+
+== Minute 5 ==
+Spend 4 ore to start building an ore-collecting robot.
+1 ore-collecting robot collects 1 ore; you now have 1 ore.
+The new ore-collecting robot is ready; you now have 2 of them.
+
+== Minute 6 ==
+2 ore-collecting robots collect 2 ore; you now have 3 ore.
+
+== Minute 7 ==
+Spend 2 ore to start building a clay-collecting robot.
+2 ore-collecting robots collect 2 ore; you now have 3 ore.
+The new clay-collecting robot is ready; you now have 1 of them.
+
+== Minute 8 ==
+Spend 2 ore to start building a clay-collecting robot.
+2 ore-collecting robots collect 2 ore; you now have 3 ore.
+1 clay-collecting robot collects 1 clay; you now have 1 clay.
+The new clay-collecting robot is ready; you now have 2 of them.
+
+== Minute 9 ==
+Spend 2 ore to start building a clay-collecting robot.
+2 ore-collecting robots collect 2 ore; you now have 3 ore.
+2 clay-collecting robots collect 2 clay; you now have 3 clay.
+The new clay-collecting robot is ready; you now have 3 of them.
+
+== Minute 10 ==
+Spend 2 ore to start building a clay-collecting robot.
+2 ore-collecting robots collect 2 ore; you now have 3 ore.
+3 clay-collecting robots collect 3 clay; you now have 6 clay.
+The new clay-collecting robot is ready; you now have 4 of them.
+
+== Minute 11 ==
+Spend 2 ore to start building a clay-collecting robot.
+2 ore-collecting robots collect 2 ore; you now have 3 ore.
+4 clay-collecting robots collect 4 clay; you now have 10 clay.
+The new clay-collecting robot is ready; you now have 5 of them.
+
+== Minute 12 ==
+Spend 2 ore to start building a clay-collecting robot.
+2 ore-collecting robots collect 2 ore; you now have 3 ore.
+5 clay-collecting robots collect 5 clay; you now have 15 clay.
+The new clay-collecting robot is ready; you now have 6 of them.
+
+== Minute 13 ==
+Spend 2 ore to start building a clay-collecting robot.
+2 ore-collecting robots collect 2 ore; you now have 3 ore.
+6 clay-collecting robots collect 6 clay; you now have 21 clay.
+The new clay-collecting robot is ready; you now have 7 of them.
+
+== Minute 14 ==
+Spend 3 ore and 14 clay to start building an obsidian-collecting robot.
+2 ore-collecting robots collect 2 ore; you now have 2 ore.
+7 clay-collecting robots collect 7 clay; you now have 14 clay.
+The new obsidian-collecting robot is ready; you now have 1 of them.
+
+== Minute 15 ==
+2 ore-collecting robots collect 2 ore; you now have 4 ore.
+7 clay-collecting robots collect 7 clay; you now have 21 clay.
+1 obsidian-collecting robot collects 1 obsidian; you now have 1 obsidian.
+
+== Minute 16 ==
+Spend 3 ore and 14 clay to start building an obsidian-collecting robot.
+2 ore-collecting robots collect 2 ore; you now have 3 ore.
+7 clay-collecting robots collect 7 clay; you now have 14 clay.
+1 obsidian-collecting robot collects 1 obsidian; you now have 2 obsidian.
+The new obsidian-collecting robot is ready; you now have 2 of them.
+
+== Minute 17 ==
+Spend 3 ore and 14 clay to start building an obsidian-collecting robot.
+2 ore-collecting robots collect 2 ore; you now have 2 ore.
+7 clay-collecting robots collect 7 clay; you now have 7 clay.
+2 obsidian-collecting robots collect 2 obsidian; you now have 4 obsidian.
+The new obsidian-collecting robot is ready; you now have 3 of them.
+
+== Minute 18 ==
+2 ore-collecting robots collect 2 ore; you now have 4 ore.
+7 clay-collecting robots collect 7 clay; you now have 14 clay.
+3 obsidian-collecting robots collect 3 obsidian; you now have 7 obsidian.
+
+== Minute 19 ==
+Spend 3 ore and 14 clay to start building an obsidian-collecting robot.
+2 ore-collecting robots collect 2 ore; you now have 3 ore.
+7 clay-collecting robots collect 7 clay; you now have 7 clay.
+3 obsidian-collecting robots collect 3 obsidian; you now have 10 obsidian.
+The new obsidian-collecting robot is ready; you now have 4 of them.
+
+== Minute 20 ==
+Spend 2 ore and 7 obsidian to start building a geode-cracking robot.
+2 ore-collecting robots collect 2 ore; you now have 3 ore.
+7 clay-collecting robots collect 7 clay; you now have 14 clay.
+4 obsidian-collecting robots collect 4 obsidian; you now have 7 obsidian.
+The new geode-cracking robot is ready; you now have 1 of them.
+
+== Minute 21 ==
+Spend 3 ore and 14 clay to start building an obsidian-collecting robot.
+2 ore-collecting robots collect 2 ore; you now have 2 ore.
+7 clay-collecting robots collect 7 clay; you now have 7 clay.
+4 obsidian-collecting robots collect 4 obsidian; you now have 11 obsidian.
+1 geode-cracking robot cracks 1 geode; you now have 1 open geode.
+The new obsidian-collecting robot is ready; you now have 5 of them.
+
+== Minute 22 ==
+Spend 2 ore and 7 obsidian to start building a geode-cracking robot.
+2 ore-collecting robots collect 2 ore; you now have 2 ore.
+7 clay-collecting robots collect 7 clay; you now have 14 clay.
+5 obsidian-collecting robots collect 5 obsidian; you now have 9 obsidian.
+1 geode-cracking robot cracks 1 geode; you now have 2 open geodes.
+The new geode-cracking robot is ready; you now have 2 of them.
+
+== Minute 23 ==
+Spend 2 ore and 7 obsidian to start building a geode-cracking robot.
+2 ore-collecting robots collect 2 ore; you now have 2 ore.
+7 clay-collecting robots collect 7 clay; you now have 21 clay.
+5 obsidian-collecting robots collect 5 obsidian; you now have 7 obsidian.
+2 geode-cracking robots crack 2 geodes; you now have 4 open geodes.
+The new geode-cracking robot is ready; you now have 3 of them.
+
+== Minute 24 ==
+Spend 2 ore and 7 obsidian to start building a geode-cracking robot.
+2 ore-collecting robots collect 2 ore; you now have 2 ore.
+7 clay-collecting robots collect 7 clay; you now have 28 clay.
+5 obsidian-collecting robots collect 5 obsidian; you now have 5 obsidian.
+3 geode-cracking robots crack 3 geodes; you now have 7 open geodes.
+The new geode-cracking robot is ready; you now have 4 of them.
+
+== Minute 25 ==
+2 ore-collecting robots collect 2 ore; you now have 4 ore.
+7 clay-collecting robots collect 7 clay; you now have 35 clay.
+5 obsidian-collecting robots collect 5 obsidian; you now have 10 obsidian.
+4 geode-cracking robots crack 4 geodes; you now have 11 open geodes.
+
+== Minute 26 ==
+Spend 2 ore and 7 obsidian to start building a geode-cracking robot.
+2 ore-collecting robots collect 2 ore; you now have 4 ore.
+7 clay-collecting robots collect 7 clay; you now have 42 clay.
+5 obsidian-collecting robots collect 5 obsidian; you now have 8 obsidian.
+4 geode-cracking robots crack 4 geodes; you now have 15 open geodes.
+The new geode-cracking robot is ready; you now have 5 of them.
+
+== Minute 27 ==
+Spend 2 ore and 7 obsidian to start building a geode-cracking robot.
+2 ore-collecting robots collect 2 ore; you now have 4 ore.
+7 clay-collecting robots collect 7 clay; you now have 49 clay.
+5 obsidian-collecting robots collect 5 obsidian; you now have 6 obsidian.
+5 geode-cracking robots crack 5 geodes; you now have 20 open geodes.
+The new geode-cracking robot is ready; you now have 6 of them.
+
+== Minute 28 ==
+2 ore-collecting robots collect 2 ore; you now have 6 ore.
+7 clay-collecting robots collect 7 clay; you now have 56 clay.
+5 obsidian-collecting robots collect 5 obsidian; you now have 11 obsidian.
+6 geode-cracking robots crack 6 geodes; you now have 26 open geodes.
+
+== Minute 29 ==
+Spend 2 ore and 7 obsidian to start building a geode-cracking robot.
+2 ore-collecting robots collect 2 ore; you now have 6 ore.
+7 clay-collecting robots collect 7 clay; you now have 63 clay.
+5 obsidian-collecting robots collect 5 obsidian; you now have 9 obsidian.
+6 geode-cracking robots crack 6 geodes; you now have 32 open geodes.
+The new geode-cracking robot is ready; you now have 7 of them.
+
+== Minute 30 ==
+Spend 2 ore and 7 obsidian to start building a geode-cracking robot.
+2 ore-collecting robots collect 2 ore; you now have 6 ore.
+7 clay-collecting robots collect 7 clay; you now have 70 clay.
+5 obsidian-collecting robots collect 5 obsidian; you now have 7 obsidian.
+7 geode-cracking robots crack 7 geodes; you now have 39 open geodes.
+The new geode-cracking robot is ready; you now have 8 of them.
+
+== Minute 31 ==
+Spend 2 ore and 7 obsidian to start building a geode-cracking robot.
+2 ore-collecting robots collect 2 ore; you now have 6 ore.
+7 clay-collecting robots collect 7 clay; you now have 77 clay.
+5 obsidian-collecting robots collect 5 obsidian; you now have 5 obsidian.
+8 geode-cracking robots crack 8 geodes; you now have 47 open geodes.
+The new geode-cracking robot is ready; you now have 9 of them.
+
+== Minute 32 ==
+2 ore-collecting robots collect 2 ore; you now have 8 ore.
+7 clay-collecting robots collect 7 clay; you now have 84 clay.
+5 obsidian-collecting robots collect 5 obsidian; you now have 10 obsidian.
+9 geode-cracking robots crack 9 geodes; you now have 56 open geodes.
+</code></pre>
+<p>However, blueprint 2 from the example above is still better; using it, the largest number of geodes you could open in 32 minutes is <code><em>62</em></code>.</p>
+<p>You <em>no longer have enough blueprints to worry about quality levels</em>. Instead, for each of the first three blueprints, determine the largest number of geodes you could open; then, multiply these three values together.</p>
+<p>Don't worry about quality levels; instead, just determine the largest number of geodes you could open using each of the first three blueprints. <em>What do you get if you multiply these numbers together?</em></p>
+</article>
+<p>Your puzzle answer was <code>3510</code>.</p><p class="day-success">Both parts of this puzzle are complete! They provide two gold stars: **</p>
+<p>At this point, you should <a href="/2022">return to your Advent calendar</a> and try another puzzle.</p>
+<p>If you still want to see it, you can <a href="19/input" target="_blank">get your puzzle input</a>.</p>
+<p>You can also <span class="share">[Share<span class="share-content">on
+  <a href="https://twitter.com/intent/tweet?text=I%27ve+completed+%22Not+Enough+Minerals%22+%2D+Day+19+%2D+Advent+of+Code+2022&amp;url=https%3A%2F%2Fadventofcode%2Ecom%2F2022%2Fday%2F19&amp;related=ericwastl&amp;hashtags=AdventOfCode" target="_blank">Twitter</a>
+  <a href="javascript:void(0);" onclick="var mastodon_instance=prompt('Mastodon Instance / Server Name?'); if(typeof mastodon_instance==='string' && mastodon_instance.length){this.href='https://'+mastodon_instance+'/share?text=I%27ve+completed+%22Not+Enough+Minerals%22+%2D+Day+19+%2D+Advent+of+Code+2022+%23AdventOfCode+https%3A%2F%2Fadventofcode%2Ecom%2F2022%2Fday%2F19'}else{return false;}" target="_blank">Mastodon</a
+></span>]</span> this puzzle.</p>
+</main>
+
+<!-- ga -->
+<script>
+(function(i,s,o,g,r,a,m){i['GoogleAnalyticsObject']=r;i[r]=i[r]||function(){
+(i[r].q=i[r].q||[]).push(arguments)},i[r].l=1*new Date();a=s.createElement(o),
+m=s.getElementsByTagName(o)[0];a.async=1;a.src=g;m.parentNode.insertBefore(a,m)
+})(window,document,'script','//www.google-analytics.com/analytics.js','ga');
+ga('create', 'UA-69522494-1', 'auto');
+ga('set', 'anonymizeIp', true);
+ga('send', 'pageview');
+</script>
+<!-- /ga -->
+</body>
+</html>
\ No newline at end of file