Done day 16
authorNeil Smith <NeilNjae@users.noreply.github.com>
Sat, 17 Dec 2022 13:46:34 +0000 (13:46 +0000)
committerNeil Smith <NeilNjae@users.noreply.github.com>
Sat, 17 Dec 2022 13:46:34 +0000 (13:46 +0000)
advent-of-code22.cabal
advent16/Main.hs [new file with mode: 0644]
data/advent16.txt [new file with mode: 0644]
data/advent16a.txt [new file with mode: 0644]
problems/day16.html [new file with mode: 0644]

index 94190f578d9549a60299dd9733c9c58cafe504ec..32e063ad50f2ece7724a51bf01c190cc0c0ca9eb 100644 (file)
@@ -175,3 +175,14 @@ executable advent15
   import: common-extensions, build-directives
   main-is: advent15/Main.hs
   build-depends: text, attoparsec, containers, linear, lens
+
+executable advent16
+  import: common-extensions, build-directives
+  main-is: advent16/Main.hs
+  build-depends: text, attoparsec, containers, pqueue, mtl, lens, split
+
+executable advent17
+  import: common-extensions, build-directives
+  main-is: advent17/Main.hs
+  build-depends: containers, linear, lens
+  
\ No newline at end of file
diff --git a/advent16/Main.hs b/advent16/Main.hs
new file mode 100644 (file)
index 0000000..7db601d
--- /dev/null
@@ -0,0 +1,275 @@
+-- Writeup at https://work.njae.me.uk/2022/12/17/advent-of-code-2022-day-16/
+
+-- 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.Sequence ((|>)) 
+import Data.List
+import Data.List.Split (chunksOf)
+import Data.Ord
+import Control.Monad.Reader
+import Control.Lens hiding ((<|), (|>), (:>), (:<), indices)
+
+-- 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.|>) 
+
+type RoomID = String
+
+data Room = Room 
+    { _flowRate :: Int
+    , _tunnels :: [RoomID]
+    } deriving (Eq, Show, Ord)
+makeLenses ''Room
+
+type Cave = M.Map RoomID Room
+data TimedCave = TimedCave { getCave :: Cave, getTimeLimit :: Int}
+
+type CaveContext = Reader TimedCave
+
+data SingleSearchState = SingleSearchState
+    { _currentRoom :: RoomID
+    , _sOpenValves :: S.Set RoomID
+    } deriving (Eq, Show, Ord)
+makeLenses ''SingleSearchState
+
+data DoubleSearchState = DoubleSearchState
+    { _personRoom :: RoomID
+    , _elephantRoom :: RoomID
+    , _dOpenValves :: S.Set RoomID
+    } deriving (Eq, Show, Ord)
+makeLenses ''DoubleSearchState
+
+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 :: RoomID -> s
+  currentFlow :: s -> CaveContext Int
+  successors :: s -> CaveContext (Q.Seq s)
+  estimateBenefit :: s -> Int -> CaveContext Int
+
+instance SearchState SingleSearchState where
+  emptySearchState startID = SingleSearchState { _currentRoom = startID, _sOpenValves = S.empty }
+
+  currentFlow state =
+    do cave <- asks getCave
+       let valves = state ^. sOpenValves
+       let presentRooms = cave `M.restrictKeys` valves
+       return $ sumOf (folded . flowRate) presentRooms
+
+  successors state = 
+    do isFF <- isFullFlow state
+       let here = state ^. currentRoom
+       let opened = state ^. sOpenValves
+       succPairs <- personSuccessor here opened
+       let succStates = 
+              [ SingleSearchState 
+                  { _currentRoom = r
+                  , _sOpenValves = o
+                  }
+              | (r, o) <- succPairs
+              ]
+       if isFF
+       then return $ Q.singleton state
+       else return $ Q.fromList succStates
+
+  estimateBenefit here timeElapsed = 
+    do cave <- asks getCave
+       timeLimit <- asks getTimeLimit
+       let timeRemaining = timeLimit - (timeElapsed + 2)
+       cf <- currentFlow here
+       let closedValves = (cave `M.withoutKeys` (here ^. sOpenValves)) ^.. folded . flowRate
+       let sortedClosedValves = sortOn Down closedValves
+       let otherValveFlows = sum $ zipWith (*) [timeRemaining, (timeRemaining - 2) .. 0] sortedClosedValves
+       return $ (cf * timeRemaining) + otherValveFlows
+
+
+instance SearchState DoubleSearchState where
+  emptySearchState startID = DoubleSearchState 
+      { _personRoom = startID
+      , _elephantRoom = startID
+      , _dOpenValves = S.empty 
+      }
+
+  currentFlow state =
+    do cave <- asks getCave
+       let valves = state ^. dOpenValves
+       let presentRooms = cave `M.restrictKeys` valves
+       return $ sumOf (folded . flowRate) presentRooms
+
+  successors state = 
+    do isFF <- isFullFlow state
+       let pHere = state ^. personRoom
+       let eHere = state ^. elephantRoom
+       let opened = state ^. dOpenValves
+       pSuccPairs <- personSuccessor pHere opened
+       eSuccPairs <- personSuccessor eHere opened
+       let succStates = 
+              [ DoubleSearchState 
+                  { _personRoom = p
+                  , _elephantRoom = e
+                  , _dOpenValves = S.union po eo
+                  }
+              | (p, po) <- pSuccPairs
+              , (e, eo) <- eSuccPairs
+              ]
+       if isFF
+       then return $ Q.singleton state
+       else return $ Q.fromList succStates
+
+  estimateBenefit here timeElapsed = 
+    do cave <- asks getCave
+       timeLimit <- asks getTimeLimit
+       let timeRemaining = timeLimit - (timeElapsed + 2)
+       cf <- currentFlow here
+       let closedValves = (cave `M.withoutKeys` (here ^. dOpenValves)) ^.. folded . flowRate
+       let sortedClosedValves = fmap sum $ chunksOf 2 $ sortOn Down closedValves
+       let otherValveFlows = sum $ zipWith (*) [timeRemaining, (timeRemaining - 2) .. 0] sortedClosedValves
+       return $ (cf * timeRemaining) + otherValveFlows
+
+
+main :: IO ()
+main = 
+  do  dataFileName <- getDataFileName
+      text <- TIO.readFile dataFileName
+      let cave = successfulParse text
+      -- print cave
+      print $ part1 cave
+      print $ part2 cave
+
+-- part1 :: Cave -> Maybe (Agendum SingleSearchState)
+-- part1 cave = runReader (searchCave "AA") (TimedCave cave 30)
+
+-- part2 :: Cave -> Maybe (Agendum DoubleSearchState)
+-- part2 cave = runReader (searchCave "AA") (TimedCave cave 26)
+
+part1, part2 :: Cave -> Int
+part1 cave = maybe 0 _benefit result
+    where result = runReader (searchCave "AA") (TimedCave cave 30) :: Maybe (Agendum SingleSearchState)
+part2 cave = maybe 0 _benefit result
+    where result = runReader (searchCave "AA") (TimedCave cave 26) :: Maybe (Agendum DoubleSearchState)
+
+searchCave :: SearchState s => String -> CaveContext (Maybe (Agendum s))
+searchCave startRoom = 
+    do agenda <- initAgenda startRoom
+       aStar agenda S.empty
+
+initAgenda :: SearchState s => String -> CaveContext (Agenda s)
+initAgenda startID = 
+    do let startState = emptySearchState startID
+       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 -> CaveContext (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) ++ " : len " ++ (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 beamAgenda (S.insert cl closed)
+
+
+candidates :: SearchState s => Agendum s -> ExploredStates s -> CaveContext (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
+
+personSuccessor, openValveSuccessor, walkSuccessor ::  RoomID -> S.Set RoomID -> CaveContext [(RoomID, S.Set RoomID)]
+personSuccessor here opened =
+  do ovs <- openValveSuccessor here opened
+     ws <- walkSuccessor here opened
+     return (ovs ++ ws)
+
+openValveSuccessor here opened
+  | here `S.member` opened = return []
+  | otherwise = return [(here, S.insert here opened)]
+
+walkSuccessor here opened = 
+  do cave <- asks getCave
+     let neighbours = (cave ! here) ^. tunnels
+     return [(n, opened) | n <- neighbours]
+
+makeAgendum :: SearchState s => Q.Seq s -> Int -> s -> CaveContext (Agendum s)
+makeAgendum previous prevBenefit newState = 
+    do predicted <- estimateBenefit newState (Q.length previous)
+       cf <- currentFlow newState
+       let newTrail = previous |> newState
+       let incurred = prevBenefit + cf
+       return Agendum { _current = newState
+                      , _trail = newTrail
+                      , _trailBenefit = incurred
+                      , _benefit = incurred + predicted
+                      }
+
+
+isGoal :: SearchState s => Agendum s -> CaveContext Bool
+isGoal agendum = 
+  do timeLimit <- asks getTimeLimit
+     return $ Q.length (agendum ^. trail) == (timeLimit - 1)
+
+isFullFlow :: SearchState s => s -> CaveContext Bool
+isFullFlow state = 
+  do cave <- asks getCave
+     cf <- currentFlow state
+     let ff = sumOf (folded . flowRate) cave
+     return (cf == ff)
+
+
+-- Parse the input file
+
+caveP :: Parser Cave
+valveP :: Parser (RoomID, Room)
+roomP :: Parser Room
+tunnelsP :: Parser [RoomID]
+turnnelTextP :: Parser Text
+
+caveP = M.fromList <$> valveP `sepBy` endOfLine
+valveP = (,) <$> ("Valve " *> (many1 letter)) <*> roomP
+roomP = roomify <$> (" has flow rate=" *> decimal) <*> (turnnelTextP *> tunnelsP)
+    where roomify v ts = Room {_flowRate = v, _tunnels = ts }
+tunnelsP = (many1 letter) `sepBy` ", "
+turnnelTextP = "; tunnels lead to valves " <|> "; tunnel leads to valve "
+
+successfulParse :: Text -> Cave
+successfulParse input = 
+  case parseOnly caveP input of
+    Left  _err -> M.empty -- TIO.putStr $ T.pack $ parseErrorPretty err
+    Right cave -> cave
\ No newline at end of file
diff --git a/data/advent16.txt b/data/advent16.txt
new file mode 100644 (file)
index 0000000..aaddfeb
--- /dev/null
@@ -0,0 +1,62 @@
+Valve AV has flow rate=0; tunnels lead to valves AX, PI
+Valve JI has flow rate=0; tunnels lead to valves VD, HF
+Valve FF has flow rate=0; tunnels lead to valves ZL, CG
+Valve CG has flow rate=10; tunnels lead to valves TI, SU, RV, FF, QX
+Valve RC has flow rate=18; tunnels lead to valves EQ, WR, AD
+Valve ZJ has flow rate=0; tunnels lead to valves GJ, WI
+Valve GJ has flow rate=21; tunnels lead to valves TG, YJ, EU, AZ, ZJ
+Valve VJ has flow rate=0; tunnels lead to valves UJ, AA
+Valve ER has flow rate=0; tunnels lead to valves QO, ZK
+Valve QO has flow rate=24; tunnels lead to valves MF, ER
+Valve LN has flow rate=0; tunnels lead to valves ZR, TI
+Valve SU has flow rate=0; tunnels lead to valves CG, LM
+Valve AJ has flow rate=12; tunnels lead to valves QX, JW, TR, MK
+Valve YJ has flow rate=0; tunnels lead to valves GJ, EQ
+Valve JW has flow rate=0; tunnels lead to valves YI, AJ
+Valve WI has flow rate=13; tunnels lead to valves XO, ZJ, ZL
+Valve VS has flow rate=0; tunnels lead to valves XL, VD
+Valve TI has flow rate=0; tunnels lead to valves LN, CG
+Valve VD has flow rate=17; tunnels lead to valves TR, VS, JI, GQ, VO
+Valve TX has flow rate=0; tunnels lead to valves FV, WR
+Valve HP has flow rate=0; tunnels lead to valves AX, ET
+Valve BK has flow rate=0; tunnels lead to valves PI, AD
+Valve ET has flow rate=0; tunnels lead to valves ZR, HP
+Valve VY has flow rate=0; tunnels lead to valves KU, LM
+Valve DZ has flow rate=0; tunnels lead to valves VO, AA
+Valve ZK has flow rate=0; tunnels lead to valves FR, ER
+Valve TG has flow rate=0; tunnels lead to valves GJ, AX
+Valve YI has flow rate=0; tunnels lead to valves JW, LM
+Valve XO has flow rate=0; tunnels lead to valves ZR, WI
+Valve ZR has flow rate=11; tunnels lead to valves KX, AZ, ET, LN, XO
+Valve EQ has flow rate=0; tunnels lead to valves RC, YJ
+Valve PI has flow rate=4; tunnels lead to valves BK, KX, VQ, EU, AV
+Valve VO has flow rate=0; tunnels lead to valves VD, DZ
+Valve WR has flow rate=0; tunnels lead to valves TX, RC
+Valve TF has flow rate=0; tunnels lead to valves FR, KU
+Valve FR has flow rate=22; tunnels lead to valves ZK, TF
+Valve MK has flow rate=0; tunnels lead to valves AJ, YW
+Valve AZ has flow rate=0; tunnels lead to valves GJ, ZR
+Valve TC has flow rate=0; tunnels lead to valves KU, RO
+Valve GQ has flow rate=0; tunnels lead to valves MF, VD
+Valve YW has flow rate=0; tunnels lead to valves MK, KU
+Valve AA has flow rate=0; tunnels lead to valves RO, EI, VJ, VQ, DZ
+Valve MF has flow rate=0; tunnels lead to valves QO, GQ
+Valve ZL has flow rate=0; tunnels lead to valves WI, FF
+Valve LM has flow rate=3; tunnels lead to valves YI, SU, UJ, VY, HF
+Valve KU has flow rate=9; tunnels lead to valves XL, TC, TF, VY, YW
+Valve FV has flow rate=23; tunnels lead to valves KV, TX
+Valve EU has flow rate=0; tunnels lead to valves PI, GJ
+Valve KV has flow rate=0; tunnels lead to valves FV, OF
+Valve QX has flow rate=0; tunnels lead to valves AJ, CG
+Valve RO has flow rate=0; tunnels lead to valves AA, TC
+Valve TR has flow rate=0; tunnels lead to valves VD, AJ
+Valve VQ has flow rate=0; tunnels lead to valves AA, PI
+Valve HF has flow rate=0; tunnels lead to valves JI, LM
+Valve RV has flow rate=0; tunnels lead to valves EI, CG
+Valve KX has flow rate=0; tunnels lead to valves PI, ZR
+Valve UJ has flow rate=0; tunnels lead to valves LM, VJ
+Valve AX has flow rate=5; tunnels lead to valves TG, AV, HP
+Valve XL has flow rate=0; tunnels lead to valves KU, VS
+Valve AD has flow rate=0; tunnels lead to valves BK, RC
+Valve EI has flow rate=0; tunnels lead to valves RV, AA
+Valve OF has flow rate=19; tunnel leads to valve KV
\ No newline at end of file
diff --git a/data/advent16a.txt b/data/advent16a.txt
new file mode 100644 (file)
index 0000000..85fa5b0
--- /dev/null
@@ -0,0 +1,10 @@
+Valve AA has flow rate=0; tunnels lead to valves DD, II, BB
+Valve BB has flow rate=13; tunnels lead to valves CC, AA
+Valve CC has flow rate=2; tunnels lead to valves DD, BB
+Valve DD has flow rate=20; tunnels lead to valves CC, AA, EE
+Valve EE has flow rate=3; tunnels lead to valves FF, DD
+Valve FF has flow rate=0; tunnels lead to valves EE, GG
+Valve GG has flow rate=0; tunnels lead to valves FF, HH
+Valve HH has flow rate=22; tunnel leads to valve GG
+Valve II has flow rate=0; tunnels lead to valves AA, JJ
+Valve JJ has flow rate=21; tunnel leads to valve II
\ No newline at end of file
diff --git a/problems/day16.html b/problems/day16.html
new file mode 100644 (file)
index 0000000..d0c4564
--- /dev/null
@@ -0,0 +1,329 @@
+<!DOCTYPE html>
+<html lang="en-us">
+<head>
+<meta charset="utf-8"/>
+<title>Day 16 - 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">32*</span></div></div><div><h1 class="title-event">&nbsp;<span class="title-event-wrap">{&apos;year&apos;:</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://careers.bankofamerica.com/" target="_blank" onclick="if(ga)ga('send','event','sponsor','sidebar',this.href);" rel="noopener">Bank of America</a> - We use technology, models and data to make financial lives better for our clients and communities.</div></div>
+</div><!--/sidebar-->
+
+<main>
+<article class="day-desc"><h2>--- Day 16: Proboscidea Volcanium ---</h2><p>The sensors have led you to the origin of the distress signal: yet another handheld device, just like the one the Elves gave you. However, you don't see any Elves around; instead, the device is surrounded by elephants! They must have gotten lost in these tunnels, and one of the elephants apparently figured out how to turn on the distress signal.</p>
+<p>The ground rumbles again, much stronger this time. What kind of cave is this, exactly? You scan the cave with your handheld device; it reports mostly igneous rock, some ash, pockets of pressurized gas, magma... this isn't just a cave, it's a volcano!</p>
+<p>You need to get the elephants out of here, quickly. Your device estimates that you have <em>30 minutes</em> before the volcano erupts, so you don't have time to go back out the way you came in.</p>
+<p>You scan the cave for other options and discover a network of pipes and pressure-release <em>valves</em>. You aren't sure how such a system got into a volcano, but you don't have time to complain; your device produces a report (your puzzle input) of each valve's <em>flow rate</em> if it were opened (in pressure per minute) and the tunnels you could use to move between the valves.</p>
+<p>There's even a valve in the room you and the elephants are currently standing in labeled <code>AA</code>. You estimate it will take you one minute to open a single valve and one minute to follow any tunnel from one valve to another. What is the most pressure you could release?</p>
+<p>For example, suppose you had the following scan output:</p>
+<pre><code>Valve AA has flow rate=0; tunnels lead to valves DD, II, BB
+Valve BB has flow rate=13; tunnels lead to valves CC, AA
+Valve CC has flow rate=2; tunnels lead to valves DD, BB
+Valve DD has flow rate=20; tunnels lead to valves CC, AA, EE
+Valve EE has flow rate=3; tunnels lead to valves FF, DD
+Valve FF has flow rate=0; tunnels lead to valves EE, GG
+Valve GG has flow rate=0; tunnels lead to valves FF, HH
+Valve HH has flow rate=22; tunnel leads to valve GG
+Valve II has flow rate=0; tunnels lead to valves AA, JJ
+Valve JJ has flow rate=21; tunnel leads to valve II
+</code></pre>
+<p>All of the valves begin <em>closed</em>. You start at valve <code>AA</code>, but it must be damaged or <span title="Wait, sir! The valve, sir! it appears to be... jammed!">jammed</span> or something: its flow rate is <code>0</code>, so there's no point in opening it. However, you could spend one minute moving to valve <code>BB</code> and another minute opening it; doing so would release pressure during the remaining <em>28 minutes</em> at a flow rate of <code>13</code>, a total eventual pressure release of <code>28 * 13 = <em>364</em></code>. Then, you could spend your third minute moving to valve <code>CC</code> and your fourth minute opening it, providing an additional <em>26 minutes</em> of eventual pressure release at a flow rate of <code>2</code>, or <code><em>52</em></code> total pressure released by valve <code>CC</code>.</p>
+<p>Making your way through the tunnels like this, you could probably open many or all of the valves by the time 30 minutes have elapsed. However, you need to release as much pressure as possible, so you'll need to be methodical. Instead, consider this approach:</p>
+<pre><code>== Minute 1 ==
+No valves are open.
+You move to valve DD.
+
+== Minute 2 ==
+No valves are open.
+You open valve DD.
+
+== Minute 3 ==
+Valve DD is open, releasing <em>20</em> pressure.
+You move to valve CC.
+
+== Minute 4 ==
+Valve DD is open, releasing <em>20</em> pressure.
+You move to valve BB.
+
+== Minute 5 ==
+Valve DD is open, releasing <em>20</em> pressure.
+You open valve BB.
+
+== Minute 6 ==
+Valves BB and DD are open, releasing <em>33</em> pressure.
+You move to valve AA.
+
+== Minute 7 ==
+Valves BB and DD are open, releasing <em>33</em> pressure.
+You move to valve II.
+
+== Minute 8 ==
+Valves BB and DD are open, releasing <em>33</em> pressure.
+You move to valve JJ.
+
+== Minute 9 ==
+Valves BB and DD are open, releasing <em>33</em> pressure.
+You open valve JJ.
+
+== Minute 10 ==
+Valves BB, DD, and JJ are open, releasing <em>54</em> pressure.
+You move to valve II.
+
+== Minute 11 ==
+Valves BB, DD, and JJ are open, releasing <em>54</em> pressure.
+You move to valve AA.
+
+== Minute 12 ==
+Valves BB, DD, and JJ are open, releasing <em>54</em> pressure.
+You move to valve DD.
+
+== Minute 13 ==
+Valves BB, DD, and JJ are open, releasing <em>54</em> pressure.
+You move to valve EE.
+
+== Minute 14 ==
+Valves BB, DD, and JJ are open, releasing <em>54</em> pressure.
+You move to valve FF.
+
+== Minute 15 ==
+Valves BB, DD, and JJ are open, releasing <em>54</em> pressure.
+You move to valve GG.
+
+== Minute 16 ==
+Valves BB, DD, and JJ are open, releasing <em>54</em> pressure.
+You move to valve HH.
+
+== Minute 17 ==
+Valves BB, DD, and JJ are open, releasing <em>54</em> pressure.
+You open valve HH.
+
+== Minute 18 ==
+Valves BB, DD, HH, and JJ are open, releasing <em>76</em> pressure.
+You move to valve GG.
+
+== Minute 19 ==
+Valves BB, DD, HH, and JJ are open, releasing <em>76</em> pressure.
+You move to valve FF.
+
+== Minute 20 ==
+Valves BB, DD, HH, and JJ are open, releasing <em>76</em> pressure.
+You move to valve EE.
+
+== Minute 21 ==
+Valves BB, DD, HH, and JJ are open, releasing <em>76</em> pressure.
+You open valve EE.
+
+== Minute 22 ==
+Valves BB, DD, EE, HH, and JJ are open, releasing <em>79</em> pressure.
+You move to valve DD.
+
+== Minute 23 ==
+Valves BB, DD, EE, HH, and JJ are open, releasing <em>79</em> pressure.
+You move to valve CC.
+
+== Minute 24 ==
+Valves BB, DD, EE, HH, and JJ are open, releasing <em>79</em> pressure.
+You open valve CC.
+
+== Minute 25 ==
+Valves BB, CC, DD, EE, HH, and JJ are open, releasing <em>81</em> pressure.
+
+== Minute 26 ==
+Valves BB, CC, DD, EE, HH, and JJ are open, releasing <em>81</em> pressure.
+
+== Minute 27 ==
+Valves BB, CC, DD, EE, HH, and JJ are open, releasing <em>81</em> pressure.
+
+== Minute 28 ==
+Valves BB, CC, DD, EE, HH, and JJ are open, releasing <em>81</em> pressure.
+
+== Minute 29 ==
+Valves BB, CC, DD, EE, HH, and JJ are open, releasing <em>81</em> pressure.
+
+== Minute 30 ==
+Valves BB, CC, DD, EE, HH, and JJ are open, releasing <em>81</em> pressure.
+</code></pre>
+<p>This approach lets you release the most pressure possible in 30 minutes with this valve layout, <code><em>1651</em></code>.</p>
+<p>Work out the steps to release the most pressure in 30 minutes. <em>What is the most pressure you can release?</em></p>
+</article>
+<p>Your puzzle answer was <code>1792</code>.</p><article class="day-desc"><h2 id="part2">--- Part Two ---</h2><p>You're worried that even with an optimal approach, the pressure released won't be enough. What if you got one of the elephants to help you?</p>
+<p>It would take you 4 minutes to teach an elephant how to open the right valves in the right order, leaving you with only <em>26 minutes</em> to actually execute your plan. Would having two of you working together be better, even if it means having less time? (Assume that you teach the elephant before opening any valves yourself, giving you both the same full 26 minutes.)</p>
+<p>In the example above, you could teach the elephant to help you as follows:</p>
+<pre><code>== Minute 1 ==
+No valves are open.
+You move to valve II.
+The elephant moves to valve DD.
+
+== Minute 2 ==
+No valves are open.
+You move to valve JJ.
+The elephant opens valve DD.
+
+== Minute 3 ==
+Valve DD is open, releasing <em>20</em> pressure.
+You open valve JJ.
+The elephant moves to valve EE.
+
+== Minute 4 ==
+Valves DD and JJ are open, releasing <em>41</em> pressure.
+You move to valve II.
+The elephant moves to valve FF.
+
+== Minute 5 ==
+Valves DD and JJ are open, releasing <em>41</em> pressure.
+You move to valve AA.
+The elephant moves to valve GG.
+
+== Minute 6 ==
+Valves DD and JJ are open, releasing <em>41</em> pressure.
+You move to valve BB.
+The elephant moves to valve HH.
+
+== Minute 7 ==
+Valves DD and JJ are open, releasing <em>41</em> pressure.
+You open valve BB.
+The elephant opens valve HH.
+
+== Minute 8 ==
+Valves BB, DD, HH, and JJ are open, releasing <em>76</em> pressure.
+You move to valve CC.
+The elephant moves to valve GG.
+
+== Minute 9 ==
+Valves BB, DD, HH, and JJ are open, releasing <em>76</em> pressure.
+You open valve CC.
+The elephant moves to valve FF.
+
+== Minute 10 ==
+Valves BB, CC, DD, HH, and JJ are open, releasing <em>78</em> pressure.
+The elephant moves to valve EE.
+
+== Minute 11 ==
+Valves BB, CC, DD, HH, and JJ are open, releasing <em>78</em> pressure.
+The elephant opens valve EE.
+
+(At this point, all valves are open.)
+
+== Minute 12 ==
+Valves BB, CC, DD, EE, HH, and JJ are open, releasing <em>81</em> pressure.
+
+...
+
+== Minute 20 ==
+Valves BB, CC, DD, EE, HH, and JJ are open, releasing <em>81</em> pressure.
+
+...
+
+== Minute 26 ==
+Valves BB, CC, DD, EE, HH, and JJ are open, releasing <em>81</em> pressure.
+</code></pre>
+<p>With the elephant helping, after 26 minutes, the best you could do would release a total of <code><em>1707</em></code> pressure.</p>
+<p><em>With you and an elephant working together for 26 minutes, what is the most pressure you could release?</em></p>
+</article>
+<p>Your puzzle answer was <code>2587</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="16/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+%22Proboscidea+Volcanium%22+%2D+Day+16+%2D+Advent+of+Code+2022&amp;url=https%3A%2F%2Fadventofcode%2Ecom%2F2022%2Fday%2F16&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+%22Proboscidea+Volcanium%22+%2D+Day+16+%2D+Advent+of+Code+2022+%23AdventOfCode+https%3A%2F%2Fadventofcode%2Ecom%2F2022%2Fday%2F16'}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