From: Neil Smith Date: Mon, 6 Jan 2020 14:21:41 +0000 (+0000) Subject: Part 2 done X-Git-Url: https://git.njae.me.uk/?p=advent-of-code-19.git;a=commitdiff_plain;h=8ed00a3a4af87fd211d5ae5a627e760adafa03da Part 2 done --- diff --git a/advent20/advent20.dot b/advent20/advent20.dot new file mode 100644 index 0000000..e541d7c --- /dev/null +++ b/advent20/advent20.dot @@ -0,0 +1,65 @@ +graph Maze { +# AA_O -- XI_O [ label = "6" style = "solid"]; +AA_O -- YA_I [ label = "60" style = "solid"]; +AM_I -- AM_O [ label = "" style = "dashed"]; +AM_I -- YO_O [ label = "44" style = "solid"]; +AM_O -- DM_I [ label = "74" style = "solid"]; +AW_O -- AW_I [ label = "" style = "dashed"]; +AW_O -- XI_I [ label = "50" style = "solid"]; +AW_I -- GY_O [ label = "44" style = "solid"]; +CQ_O -- CQ_I [ label = "" style = "dashed"]; +CQ_O -- CV_I [ label = "64" style = "solid"]; +CQ_I -- WH_O [ label = "60" style = "solid"]; +CV_O -- CV_I [ label = "" style = "dashed"]; +CV_O -- YO_I [ label = "78" style = "solid"]; +CY_O -- CY_I [ label = "" style = "dashed"]; +CY_O -- GY_I [ label = "48" style = "solid"]; +CY_I -- JV_O [ label = "52" style = "solid"]; +DM_O -- DM_I [ label = "" style = "dashed"]; +DM_O -- GC_I [ label = "58" style = "solid"]; +GC_I -- GC_O [ label = "" style = "dashed"]; +GC_O -- PP_I [ label = "54" style = "solid"]; +GL_O -- GL_I [ label = "" style = "dashed"]; +GL_O -- HB_I [ label = "60" style = "solid"]; +GL_I -- UC_O [ label = "40" style = "solid"]; +GY_I -- GY_O [ label = "" style = "dashed"]; +HB_I -- HB_O [ label = "" style = "dashed"]; +HB_O -- KK_I [ label = "50" style = "solid"]; +JV_I -- JV_O [ label = "" style = "dashed"]; +JV_I -- PP_O [ label = "44" style = "solid"]; +JV_I -- PY_I [ label = "4" style = "solid"]; +JV_I -- XZ_O [ label = "46" style = "solid"]; +KK_O -- KK_I [ label = "" style = "dashed"]; +KK_O -- WH_I [ label = "56" style = "solid"]; +KY_I -- KY_O [ label = "" style = "dashed"]; +KY_I -- YA_O [ label = "52" style = "solid"]; +KY_O -- XZ_I [ label = "52" style = "solid"]; +LM_I -- LM_O [ label = "" style = "dashed"]; +LM_I -- UM_O [ label = "44" style = "solid"]; +LM_O -- YF_I [ label = "44" style = "solid"]; +NZ_O -- NZ_I [ label = "" style = "dashed"]; +NZ_O -- UC_I [ label = "72" style = "solid"]; +# NZ_O -- ZZ_O [ label = "8" style = "solid"]; +NZ_I -- PN_O [ label = "80" style = "solid"]; +PN_O -- PN_I [ label = "" style = "dashed"]; +PN_I -- YF_O [ label = "66" style = "solid"]; +PP_O -- PP_I [ label = "" style = "dashed"]; +PP_O -- PY_I [ label = "42" style = "solid"]; +PP_O -- XZ_O [ label = "4" style = "solid"]; +PY_I -- PY_O [ label = "" style = "dashed"]; +PY_I -- XZ_O [ label = "44" style = "solid"]; +PY_O -- TL_I [ label = "56" style = "solid"]; +TL_O -- TL_I [ label = "" style = "dashed"]; +TL_O -- UM_I [ label = "42" style = "solid"]; +UC_I -- UC_O [ label = "" style = "dashed"]; +UC_I -- ZZ_O [ label = "66" style = "solid"]; +UM_I -- UM_O [ label = "" style = "dashed"]; +WH_I -- WH_O [ label = "" style = "dashed"]; +XI_I -- XI_O [ label = "" style = "dashed"]; +XI_O -- YA_I [ label = "64" style = "solid"]; +XZ_O -- XZ_I [ label = "" style = "dashed"]; +YA_O -- YA_I [ label = "" style = "dashed"]; +YF_O -- YF_I [ label = "" style = "dashed"]; +YO_I -- YO_O [ label = "" style = "dashed"]; + +} diff --git a/advent20/advent20.dot.png b/advent20/advent20.dot.png new file mode 100644 index 0000000..c4e1eb6 Binary files /dev/null and b/advent20/advent20.dot.png differ diff --git a/advent20/src/advent20.hs b/advent20/src/advent20.hs index 0e2516a..4132d9e 100644 --- a/advent20/src/advent20.hs +++ b/advent20/src/advent20.hs @@ -8,7 +8,7 @@ import qualified Data.PQueue.Prio.Min as P import qualified Data.Set as S import qualified Data.Sequence as Q import Data.Sequence ((<|)) -- , (|>), (><)) -import Data.Foldable (foldl', any, sum) -- (toList, foldr', foldl', all) +import Data.Foldable (foldl', sum) -- (toList, foldr', foldl', all) import Data.Char import Control.Monad.Reader import Control.Lens hiding ((<|), (|>)) @@ -18,8 +18,11 @@ import Data.Maybe (fromMaybe) type Position = (Int, Int) -- r, c + +data Location = Inner | Outer deriving (Eq, Ord, Show) data Portal = Portal { _label :: String , _position :: Position + , _location :: Location } deriving (Eq, Ord, Show) makeLenses ''Portal @@ -43,71 +46,90 @@ data Edge = Edge { _connects :: EdgeConnects } deriving (Eq, Ord, Show) makeLenses ''Edge -type Maze = S.Set Edge +type Edges = S.Set Edge + +-- type Maze = S.Set Edge +data Maze = Maze { _maze :: Edges + , _costPerLevel :: Int + , _costToFinish :: Int + } deriving (Eq, Ord, Show) +-- makeLenses ''Maze type MazeContext = Reader Maze -type ExploredStates = S.Set Portal +class (Eq s, Ord s, Show s) => SearchState s where + successors :: s -> MazeContext (Q.Seq (s, Edge)) + estimateCost :: s -> MazeContext Int + emptySearchState :: Portal -> s + isGoal :: s -> MazeContext Bool + +data LevelledSearchState = LevelledSearchState + { _portalS :: Portal + , _levelS :: Int + } deriving (Eq, Ord, Show) +makeLenses ''LevelledSearchState + -data Agendum = Agendum { _current :: Portal - , _trail :: Q.Seq Edge - , _cost :: Int} deriving (Show, Eq) +type ExploredStates s = S.Set s + +data Agendum s = + Agendum { _current :: s + , _trail :: Q.Seq Edge + , _cost :: Int + } deriving (Show, Eq) makeLenses ''Agendum -type Agenda = P.MinPQueue Int (Agendum) +type Agenda s = P.MinPQueue Int (Agendum s) main :: IO () main = do - -- text <- readFile "data/advent20a.txt" - -- let mc = buildComplex text - -- print mc - -- let maze = contractMaze mc - -- print maze maze <- setup + -- print maze putStrLn $ showContracted maze print $ part1 maze - -- print $ S.size $ edgeC $ _caveE ccE - -- print $ S.size $ _cave $ contractCave ccE [startPosition] - -- putStrLn $ showContracted $ contractCave ccE [startPosition] - -- let (re, ce) = startPosition - -- let startPositions = [(re - 1, ce - 1), (re - 1, ce + 1), (re + 1 , ce - 1), (re + 1, ce + 1)] - -- let cavern0 = ccE ^. caveE - -- let cavern = cavern0 `S.difference` [(re, ce), (re + 1, ce), (re - 1, ce), (re, ce + 1), (re, ce - 1)] - -- let caveComplex = ccE & caveE .~ cavern - -- let cc = contractCave caveComplex startPositions - -- putStrLn $ showContracted cc - -- print $ part1 ccE startPosition - -- print $ part2 ccE startPosition - --- edgeC ec = S.foldl' ecAdd S.empty ec --- where ecAdd es n = S.union (eds n) es --- eds n = S.map (\m -> S.fromList [n, m]) $ nbrs n --- nbrs n = S.intersection ec $ possibleNeighbours n - + print $ part2 maze setup = do text <- readFile "data/advent20.txt" let mc = buildComplex text -- print mc - return $ contractMaze mc -- print maze + return $ contractMaze mc --- part1 :: Maze -> Int -part1 maze = result -- maybe 0 _cost result - where result = runReader searchMaze maze +part1 :: Maze -> Int +-- part1 :: Maze -> Maybe (Agendum Portal) +part1 maze = maybe 0 _cost result + where result = runReader searchMaze maze :: Maybe (Agendum Portal) +part2 :: Maze -> Int +-- part2 :: Maze -> Maybe (Agendum LevelledSearchState) +part2 maze = maybe 0 _cost result + where result = runReader searchMaze maze :: Maybe (Agendum LevelledSearchState) buildComplex :: String -> MazeComplex -buildComplex text = mc & portalLocs .~ pLocs +buildComplex text = mc & portalLocs .~ pLocs & portalsE .~ portals' where mc = foldl' (buildMazeRow rows) mc0 [0..l] mc0 = MazeComplex {_mazeE = S.empty, _portalsE = S.empty, _portalLocs = S.empty} rows = lines text l = length rows - 1 + minR = 2 + maxR = l - 2 + minC = 2 + maxC = length (rows!!2) - 3 pLocs = S.map _position (mc ^. portalsE) + portals = mc ^. portalsE + portals' = S.map (classifiyPortal minR maxR minC maxC) portals + +classifiyPortal :: Int -> Int -> Int -> Int -> Portal -> Portal +classifiyPortal minR maxR minC maxC portal = portal & location .~ loc + where (r, c) = portal ^. position + loc = if (r == minR) || (r == maxR) || (c == minC) || (c == maxC) + then Outer + else Inner buildMazeRow :: [String] -> MazeComplex -> Int -> MazeComplex buildMazeRow rows mc r = foldl' (buildMazeCell rows r) mc [0..l] @@ -127,11 +149,11 @@ buildMazeCell rows r mc c makePortal portals rows hc r c | isUpper rc = if pr == '.' - then S.insert (Portal [hc, rc] (r, c + 2)) portals - else S.insert (Portal [hc, rc] (r, c - 1)) portals + then S.insert (Portal { _label = [hc, rc], _position = (r, c + 2), _location = Outer } ) portals + else S.insert (Portal { _label = [hc, rc], _position = (r, c - 1), _location = Outer } ) portals | isUpper dc = if pd == '.' - then S.insert (Portal [hc, dc] (r + 2, c)) portals - else S.insert (Portal [hc, dc] (r - 1, c)) portals + then S.insert (Portal { _label = [hc, dc], _position = (r + 2, c), _location = Outer } ) portals + else S.insert (Portal { _label = [hc, dc], _position = (r - 1, c), _location = Outer } ) portals | otherwise = portals where -- lc = charAt rows r (c - 1) rc = charAt rows r (c + 1) @@ -142,6 +164,7 @@ makePortal portals rows hc r c -- pl = charAt rows r (c - 1) pr = charAt rows r (c + 2) + charAt :: [String] -> Int -> Int -> Char charAt rows r c = atDef ' ' (atDef "" rows r) c @@ -157,13 +180,19 @@ atMaybe xs i contractMaze :: MazeComplex -> Maze -contractMaze expanded = S.union mazeW mazeP +contractMaze expanded = Maze + { _maze = S.union mazeW mazeP + , _costPerLevel = cpl + , _costToFinish = ctf + } where starts = expanded ^. portalsE - mazeW = S.foldr (contractFrom expanded) S.empty starts - mazeP = S.foldr (addWarp starts) S.empty starts - + mazeP = S.foldr (contractFrom expanded) S.empty starts + mazeW = S.foldr (addWarp starts) S.empty starts + cpl = minimum $ map (^. distance) $ S.toList $ S.filter (\e -> e ^. edgeType == Walk) mazeP + ctf = minimum $ map (^. distance) $ S.toList $ S.filter (edgeTouches term) mazeP + term = S.findMin $ S.filter (\p -> p ^. label == "ZZ") starts -contractFrom :: MazeComplex -> Portal -> Maze -> Maze +contractFrom :: MazeComplex -> Portal -> Edges -> Edges contractFrom expanded start maze0 = S.union maze0 reachables where startPos = start ^. position reachables = reachableFrom [(startPos, 0)] S.empty expanded' start @@ -171,9 +200,9 @@ contractFrom expanded start maze0 = S.union maze0 reachables & portalLocs %~ (S.delete startPos) -- & mazeE %~ (S.delete startPos) -reachableFrom :: [(Position, Int)] -> (S.Set Position) -> MazeComplex -> Portal -> Maze +reachableFrom :: [(Position, Int)] -> (S.Set Position) -> MazeComplex -> Portal -> Edges reachableFrom [] _closed _expanded _start = S.empty -reachableFrom ((here, distance):boundary) closed expanded start +reachableFrom ((here, dist):boundary) closed expanded start | here `S.member` closed = reachableFrom boundary closed expanded start | here `S.member` ps = S.insert edge $ reachableFrom boundary closed' expanded start | otherwise = reachableFrom boundary' closed' expanded start @@ -182,12 +211,12 @@ reachableFrom ((here, distance):boundary) closed expanded start closed' = S.insert here closed ps = expanded ^. portalLocs other = S.findMin $ S.filter (\p -> p ^. position == here) $ expanded ^. portalsE - edge = Edge { _connects = mkConnection start other, _edgeType = Walk, _distance = distance } - neighbours = S.map (\n -> (n, distance + 1)) nbrs + edge = Edge { _connects = mkConnection start other, _edgeType = Walk, _distance = dist } + neighbours = S.map (\n -> (n, dist + 1)) nbrs boundary' = boundary ++ (S.toAscList neighbours) -addWarp :: Portals -> Portal -> Maze -> Maze +addWarp :: Portals -> Portal -> Edges -> Edges addWarp portals portal warps | S.null others = warps | otherwise = S.insert warp warps @@ -197,9 +226,8 @@ addWarp portals portal warps other = S.findMin others warp = Edge {_connects = mkConnection portal other, _edgeType = Teleport, _distance = 1} - portalsConnect :: String -> Position -> Portal -> Bool -portalsConnect lab pos portal = (pLabel == lab) && (not (pPos == pos)) +portalsConnect lab pos portal = (pLabel == lab) && (pPos /= pos) where pLabel = portal ^. label pPos = portal ^. position @@ -207,6 +235,7 @@ portalsConnect lab pos portal = (pLabel == lab) && (not (pPos == pos)) mkConnection :: Portal -> Portal -> EdgeConnects mkConnection a b = if a < b then (a, b) else (b, a) + edgeTouches :: Portal -> Edge -> Bool edgeTouches p e | p == a = True @@ -214,10 +243,6 @@ edgeTouches p e | otherwise = False where (a, b) = e ^. connects --- anyEdgeTouch :: S.Set Portal -> Edge -> Bool --- -- anyEdgeTouch xs e = S.foldl' (\t x -> t || (edgeTouches e x)) False xs --- anyEdgeTouch xs e = any (edgeTouches e) xs - edgeOther :: Portal -> Edge -> Portal edgeOther x e | x == a = b @@ -233,22 +258,22 @@ mazePortals edges = S.foldr' mps S.empty edges in S.insert p1 $ S.insert p2 ps - -searchMaze :: MazeContext (Maybe (Agendum)) +searchMaze :: SearchState s => MazeContext (Maybe (Agendum s)) searchMaze = do agenda <- initAgenda aStar agenda S.empty -initAgenda :: MazeContext (Agenda) +initAgenda :: SearchState s => MazeContext (Agenda s) initAgenda = - do edges <- ask + do edges <- asks _maze let portals = mazePortals edges let portal = S.findMin $ S.filter (\p -> p ^. label == "AA") portals - cost <- estimateCost portal - return $ P.singleton cost Agendum { _current = portal, _trail = Q.empty, _cost = cost} + let ss = emptySearchState portal + c <- estimateCost ss + return $ P.singleton c Agendum { _current = ss, _trail = Q.empty, _cost = c} -aStar :: Agenda -> ExploredStates -> MazeContext (Maybe (Agendum)) +aStar :: SearchState s => Agenda s -> ExploredStates s -> MazeContext (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.findMin agenda) ) False = undefined @@ -266,57 +291,105 @@ aStar agenda closed else aStar newAgenda (S.insert reached closed) -isGoal :: Portal -> MazeContext Bool -isGoal portal = return $ portal ^. label == "ZZ" - -candidates :: Agendum -> ExploredStates -> MazeContext (Q.Seq (Agendum)) +candidates :: SearchState s => Agendum s -> ExploredStates s -> MazeContext (Q.Seq (Agendum s)) candidates agendum closed = do let candidate = agendum ^. current let previous = agendum ^. trail + -- let prevCost = agendum ^. cost succs <- successors candidate let nonloops = Q.filter (\s -> not $ (fst s) `S.member` closed) succs mapM (makeAgendum previous) nonloops -makeAgendum :: (Q.Seq Edge) -> (Portal, Edge) -> MazeContext (Agendum) +makeAgendum :: SearchState s => (Q.Seq Edge) -> (s, Edge) -> MazeContext (Agendum s) makeAgendum previous (newP, newE) = do predicted <- estimateCost newP - let incurred = (newE ^. distance) + (sum $ fmap (^. distance) previous) + let newTrail = newE <| previous + let incurred = sum $ fmap (^. distance) newTrail return Agendum { _current = newP - , _trail = newE <| previous + , _trail = newTrail , _cost = incurred + predicted } -successors :: Portal -> MazeContext (Q.Seq (Portal, Edge)) -successors portal = - do maze <- ask - let edges = S.filter (edgeTouches portal) maze - let locations = S.map (\e -> (edgeOther portal e, e)) edges - let succs = S.foldr' (<|) Q.empty locations - return succs - -estimateCost :: Portal -> MazeContext Int -estimateCost portal = return 0 - -- do let heres = explorer ^. position - -- ks <- asks _keys - -- cavern <- asks _cave - -- let kH = explorer ^. keysHeld - -- let unfound = ks `S.difference` kH - -- let unfoundEdges0 = S.filter (\e -> edgeTouch heres e) cavern - -- let unfoundEdges = S.filter (\e -> not $ anyEdgeTouch kH e) unfoundEdges0 - -- let furthest = S.findMax $ S.insert 0 $ S.map _distance unfoundEdges - -- return $ max 0 $ furthest + (S.size unfound) - 1 - - - +instance SearchState Portal where + + emptySearchState portal = portal + + -- successors :: Portal -> MazeContext (Q.Seq (Portal, Edge)) + successors portal = + do maze <- asks _maze + let edges = S.filter (edgeTouches portal) maze + let locations = S.map (\e -> (edgeOther portal e, e)) edges + let succs = S.foldr' (<|) Q.empty locations + return succs + + -- estimateCost :: Portal -> MazeContext Int + estimateCost _portal = return 0 + + -- isGoal :: Portal -> MazeContext Bool + isGoal portal = return $ portal ^. label == "ZZ" + +instance SearchState LevelledSearchState where + emptySearchState portal = LevelledSearchState {_portalS = portal, _levelS = 0} + + -- successors :: LevelledSearchState -> MazeContext (Q.Seq (LevelledSearchState, Edge)) + successors ss = + do maze <- asks _maze + let lvl = ss ^. levelS + let portal = ss ^. portalS + let edges = S.filter (edgeTouches portal) maze + let lvlEdges = S.filter (edgeAtLevel portal lvl) edges + let locations = S.map (\e -> (newLSS portal lvl e, e)) lvlEdges + let locations' = S.filter (\(s, _) -> (s ^. levelS) >= 0) locations + let succs = S.foldr' (<|) Q.empty locations' + return succs + + -- estimateCost :: Portal -> MazeContext Int + estimateCost ss = -- return 0 + do let lvl = ss ^. levelS + cpl <- asks _costPerLevel + ctf <- asks _costToFinish + let cplT = if ss ^. portalS . location == Outer + then cpl * (lvl - 1) + 1 + else cpl * lvl + if isTerminal (ss ^. portalS) + then return 0 + else return (cplT + ctf) + + -- isGoal :: LevelledSearchState -> MazeContext Bool + isGoal ss = return $ ss ^. portalS . label == "ZZ" + +edgeAtLevel portal lvl edge + -- | (lvl == 0) && (isTerminal other) && (et == Walk) = True + | (lvl /= 0) && (isTerminal other) && (et == Walk) = False + | (lvl == 0) && (not $ isTerminal other) && (et == Walk) && ((other ^. location) == Outer) = False + | otherwise = True + where other = edgeOther portal edge + et = edge ^. edgeType + +isTerminal p = (p ^. label == "AA") || (p ^. label == "ZZ") + +newLSS :: Portal -> Int -> Edge -> LevelledSearchState +newLSS portal lvl edge + | et == Teleport && pl == Outer = LevelledSearchState { _portalS = otherPortal, _levelS = lvl - 1 } + | et == Teleport && pl == Inner = LevelledSearchState { _portalS = otherPortal, _levelS = lvl + 1 } + | otherwise = LevelledSearchState { _portalS = otherPortal, _levelS = lvl } -- et == Walk + where pl = portal ^. location + et = edge ^. edgeType + otherPortal = edgeOther portal edge showContracted :: Maze -> String -showContracted maze = "graph Maze {\n" ++ bulk ++ "\n}" - where bulk = S.foldr (\e s -> (showEdge e) ++ s) "" maze +showContracted m = "graph Maze {\n" ++ bulk ++ "\n}" + where bulk = S.foldr (\e s -> (showEdge e) ++ s) "" (_maze m) showEdge :: Edge -> String -showEdge e = (showPortal h) ++ " -- " ++ (showPortal t) ++ " [ label = \"" ++ (edgeLabel e) ++ "\"];\n" - where edgeLabel e = (show (e ^. edgeType)) ++ ", " ++ (show (e ^. distance)) +showEdge e = (showPortal h) ++ " -- " ++ (showPortal t) ++ " [ label = \"" ++ edgeLabel ++ "\" style = \"" ++ style ++ "\"];\n" + where -- edgeLabel e = (show (e ^. edgeType)) ++ ", " ++ (show (e ^. distance)) + (edgeLabel, style) = + if (e ^. edgeType) == Walk + then (show (e ^. distance), "solid") + else ("", "dashed") (h, t) = e ^. connects - showPortal p = p ^. label ++ (show (fst (p ^. position))) ++ "c" ++ (show (snd (p ^. position))) + -- showPortal p = p ^. label ++ (show (fst (p ^. position))) ++ "c" ++ (show (snd (p ^. position))) ++ (take 1 $ show (p ^. location)) + showPortal p = p ^. label ++ "_" ++ (take 1 $ show (p ^. location)) diff --git a/data/advent20c.txt b/data/advent20c.txt new file mode 100644 index 0000000..754d23b --- /dev/null +++ b/data/advent20c.txt @@ -0,0 +1,37 @@ + Z L X W C + Z P Q B K + ###########.#.#.#.#######.############### + #...#.......#.#.......#.#.......#.#.#...# + ###.#.#.#.#.#.#.#.###.#.#.#######.#.#.### + #.#...#.#.#...#.#.#...#...#...#.#.......# + #.###.#######.###.###.#.###.###.#.####### + #...#.......#.#...#...#.............#...# + #.#########.#######.#.#######.#######.### + #...#.# F R I Z #.#.#.# + #.###.# D E C H #.#.#.# + #.#...# #...#.# + #.###.# #.###.# + #.#....OA WB..#.#..ZH + #.###.# #.#.#.# +CJ......# #.....# + ####### ####### + #.#....CK #......IC + #.###.# #.###.# + #.....# #...#.# + ###.### #.#.#.# +XF....#.# RF..#.#.# + #####.# ####### + #......CJ NM..#...# + ###.#.# #.###.# +RE....#.# #......RF + ###.### X X L #.#.#.# + #.....# F Q P #.#.#.# + ###.###########.###.#######.#########.### + #.....#...#.....#.......#...#.....#.#...# + #####.#.###.#######.#######.###.###.#.#.# + #.......#.......#.#.#.#.#...#...#...#.#.# + #####.###.#####.#.#.#.#.###.###.#.###.### + #.......#.....#.#...#...............#...# + #############.#.#.###.################### + A O F N + A A D M \ No newline at end of file diff --git a/problems/day20.html b/problems/day20.html new file mode 100644 index 0000000..befc650 --- /dev/null +++ b/problems/day20.html @@ -0,0 +1,303 @@ + + + + +Day 20 - Advent of Code 2019 + + + + + + + +

Advent of Code

Neil Smith (AoC++) 40*

        //2019

+ + + +
+ +

--- Day 20: Donut Maze ---

You notice a strange pattern on the surface of Pluto and land nearby to get a closer look. Upon closer inspection, you realize you've come across one of the famous space-warping mazes of the long-lost Pluto civilization!

+

Because there isn't much space on Pluto, the civilization that used to live here thrived by inventing a method for folding spacetime. Although the technology is no longer understood, mazes like this one provide a small glimpse into the daily life of an ancient Pluto citizen.

+

This maze is shaped like a donut. Portals along the inner and outer edge of the donut can instantly teleport you from one side to the other. For example:

+
         A           
+         A           
+  #######.#########  
+  #######.........#  
+  #######.#######.#  
+  #######.#######.#  
+  #######.#######.#  
+  #####  B    ###.#  
+BC...##  C    ###.#  
+  ##.##       ###.#  
+  ##...DE  F  ###.#  
+  #####    G  ###.#  
+  #########.#####.#  
+DE..#######...###.#  
+  #.#########.###.#  
+FG..#########.....#  
+  ###########.#####  
+             Z       
+             Z       
+
+

This map of the maze shows solid walls (#) and open passages (.). Every maze on Pluto has a start (the open tile next to AA) and an end (the open tile next to ZZ). Mazes on Pluto also have portals; this maze has three pairs of portals: BC, DE, and FG. When on an open tile next to one of these labels, a single step can take you to the other tile with the same label. (You can only walk on . tiles; labels and empty space are not traversable.)

+

One path through the maze doesn't require any portals. Starting at AA, you could go down 1, right 8, down 12, left 4, and down 1 to reach ZZ, a total of 26 steps.

+

However, there is a shorter path: You could walk from AA to the inner BC portal (4 steps), warp to the outer BC portal (1 step), walk to the inner DE (6 steps), warp to the outer DE (1 step), walk to the outer FG (4 steps), warp to the inner FG (1 step), and finally walk to ZZ (6 steps). In total, this is only 23 steps.

+

Here is a larger example:

+
                   A               
+                   A               
+  #################.#############  
+  #.#...#...................#.#.#  
+  #.#.#.###.###.###.#########.#.#  
+  #.#.#.......#...#.....#.#.#...#  
+  #.#########.###.#####.#.#.###.#  
+  #.............#.#.....#.......#  
+  ###.###########.###.#####.#.#.#  
+  #.....#        A   C    #.#.#.#  
+  #######        S   P    #####.#  
+  #.#...#                 #......VT
+  #.#.#.#                 #.#####  
+  #...#.#               YN....#.#  
+  #.###.#                 #####.#  
+DI....#.#                 #.....#  
+  #####.#                 #.###.#  
+ZZ......#               QG....#..AS
+  ###.###                 #######  
+JO..#.#.#                 #.....#  
+  #.#.#.#                 ###.#.#  
+  #...#..DI             BU....#..LF
+  #####.#                 #.#####  
+YN......#               VT..#....QG
+  #.###.#                 #.###.#  
+  #.#...#                 #.....#  
+  ###.###    J L     J    #.#.###  
+  #.....#    O F     P    #.#...#  
+  #.###.#####.#.#####.#####.###.#  
+  #...#.#.#...#.....#.....#.#...#  
+  #.#####.###.###.#.#.#########.#  
+  #...#.#.....#...#.#.#.#.....#.#  
+  #.###.#####.###.###.#.#.#######  
+  #.#.........#...#.............#  
+  #########.###.###.#############  
+           B   J   C               
+           U   P   P               
+
+

Here, AA has no direct path to ZZ, but it does connect to AS and CP. By passing through AS, QG, BU, and JO, you can reach ZZ in 58 steps.

+

In your maze, how many steps does it take to get from the open tile marked AA to the open tile marked ZZ?

+
+

Your puzzle answer was 556.

--- Part Two ---

Strangely, the exit isn't open when you reach it. Then, you remember: the ancient Plutonians were famous for building recursive spaces.

+

The marked connections in the maze aren't portals: they physically connect to a larger or smaller copy of the maze. Specifically, the labeled tiles around the inside edge actually connect to a smaller copy of the same maze, and the smaller copy's inner labeled tiles connect to yet a smaller copy, and so on.

+

When you enter the maze, you are at the outermost level; when at the outermost level, only the outer labels AA and ZZ function (as the start and end, respectively); all other outer labeled tiles are effectively walls. At any other level, AA and ZZ count as walls, but the other outer labeled tiles bring you one level outward.

+

Your goal is to find a path through the maze that brings you back to ZZ at the outermost level of the maze.

+

In the first example above, the shortest path is now the loop around the right side. If the starting level is 0, then taking the previously-shortest path would pass through BC (to level 1), DE (to level 2), and FG (back to level 1). Because this is not the outermost level, ZZ is a wall, and the only option is to go back around to BC, which would only send you even deeper into the recursive maze.

+

In the second example above, there is no path that brings you to ZZ at the outermost level.

+

Here is a more interesting example:

+
             Z L X W       C                 
+             Z P Q B       K                 
+  ###########.#.#.#.#######.###############  
+  #...#.......#.#.......#.#.......#.#.#...#  
+  ###.#.#.#.#.#.#.#.###.#.#.#######.#.#.###  
+  #.#...#.#.#...#.#.#...#...#...#.#.......#  
+  #.###.#######.###.###.#.###.###.#.#######  
+  #...#.......#.#...#...#.............#...#  
+  #.#########.#######.#.#######.#######.###  
+  #...#.#    F       R I       Z    #.#.#.#  
+  #.###.#    D       E C       H    #.#.#.#  
+  #.#...#                           #...#.#  
+  #.###.#                           #.###.#  
+  #.#....OA                       WB..#.#..ZH
+  #.###.#                           #.#.#.#  
+CJ......#                           #.....#  
+  #######                           #######  
+  #.#....CK                         #......IC
+  #.###.#                           #.###.#  
+  #.....#                           #...#.#  
+  ###.###                           #.#.#.#  
+XF....#.#                         RF..#.#.#  
+  #####.#                           #######  
+  #......CJ                       NM..#...#  
+  ###.#.#                           #.###.#  
+RE....#.#                           #......RF
+  ###.###        X   X       L      #.#.#.#  
+  #.....#        F   Q       P      #.#.#.#  
+  ###.###########.###.#######.#########.###  
+  #.....#...#.....#.......#...#.....#.#...#  
+  #####.#.###.#######.#######.###.###.#.#.#  
+  #.......#.......#.#.#.#.#...#...#...#.#.#  
+  #####.###.#####.#.#.#.#.###.###.#.###.###  
+  #.......#.....#.#...#...............#...#  
+  #############.#.#.###.###################  
+               A O F   N                     
+               A A D   M                     
+
+

One shortest path through the maze is the following:

+
    +
  • Walk from AA to XF (16 steps)
  • +
  • Recurse into level 1 through XF (1 step)
  • +
  • Walk from XF to CK (10 steps)
  • +
  • Recurse into level 2 through CK (1 step)
  • +
  • Walk from CK to ZH (14 steps)
  • +
  • Recurse into level 3 through ZH (1 step)
  • +
  • Walk from ZH to WB (10 steps)
  • +
  • Recurse into level 4 through WB (1 step)
  • +
  • Walk from WB to IC (10 steps)
  • +
  • Recurse into level 5 through IC (1 step)
  • +
  • Walk from IC to RF (10 steps)
  • +
  • Recurse into level 6 through RF (1 step)
  • +
  • Walk from RF to NM (8 steps)
  • +
  • Recurse into level 7 through NM (1 step)
  • +
  • Walk from NM to LP (12 steps)
  • +
  • Recurse into level 8 through LP (1 step)
  • +
  • Walk from LP to FD (24 steps)
  • +
  • Recurse into level 9 through FD (1 step)
  • +
  • Walk from FD to XQ (8 steps)
  • +
  • Recurse into level 10 through XQ (1 step)
  • +
  • Walk from XQ to WB (4 steps)
  • +
  • Return to level 9 through WB (1 step)
  • +
  • Walk from WB to ZH (10 steps)
  • +
  • Return to level 8 through ZH (1 step)
  • +
  • Walk from ZH to CK (14 steps)
  • +
  • Return to level 7 through CK (1 step)
  • +
  • Walk from CK to XF (10 steps)
  • +
  • Return to level 6 through XF (1 step)
  • +
  • Walk from XF to OA (14 steps)
  • +
  • Return to level 5 through OA (1 step)
  • +
  • Walk from OA to CJ (8 steps)
  • +
  • Return to level 4 through CJ (1 step)
  • +
  • Walk from CJ to RE (8 steps)
  • +
  • Return to level 3 through RE (1 step)
  • +
  • Walk from RE to IC (4 steps)
  • +
  • Recurse into level 4 through IC (1 step)
  • +
  • Walk from IC to RF (10 steps)
  • +
  • Recurse into level 5 through RF (1 step)
  • +
  • Walk from RF to NM (8 steps)
  • +
  • Recurse into level 6 through NM (1 step)
  • +
  • Walk from NM to LP (12 steps)
  • +
  • Recurse into level 7 through LP (1 step)
  • +
  • Walk from LP to FD (24 steps)
  • +
  • Recurse into level 8 through FD (1 step)
  • +
  • Walk from FD to XQ (8 steps)
  • +
  • Recurse into level 9 through XQ (1 step)
  • +
  • Walk from XQ to WB (4 steps)
  • +
  • Return to level 8 through WB (1 step)
  • +
  • Walk from WB to ZH (10 steps)
  • +
  • Return to level 7 through ZH (1 step)
  • +
  • Walk from ZH to CK (14 steps)
  • +
  • Return to level 6 through CK (1 step)
  • +
  • Walk from CK to XF (10 steps)
  • +
  • Return to level 5 through XF (1 step)
  • +
  • Walk from XF to OA (14 steps)
  • +
  • Return to level 4 through OA (1 step)
  • +
  • Walk from OA to CJ (8 steps)
  • +
  • Return to level 3 through CJ (1 step)
  • +
  • Walk from CJ to RE (8 steps)
  • +
  • Return to level 2 through RE (1 step)
  • +
  • Walk from RE to XQ (14 steps)
  • +
  • Return to level 1 through XQ (1 step)
  • +
  • Walk from XQ to FD (8 steps)
  • +
  • Return to level 0 through FD (1 step)
  • +
  • Walk from FD to ZZ (18 steps)
  • +
+

This path takes a total of 396 steps to move from AA at the outermost layer to ZZ at the outermost layer.

+

In your maze, when accounting for recursion, how many steps does it take to get from the open tile marked AA to the open tile marked ZZ, both at the outermost layer?

+
+

Your puzzle answer was 6532.

Both parts of this puzzle are complete! They provide two gold stars: **

+

At this point, you should return to your Advent calendar and try another puzzle.

+

If you still want to see it, you can get your puzzle input.

+

You can also this puzzle.

+
+ + + + + + \ No newline at end of file