From: Neil Smith Date: Sun, 2 Jan 2022 18:37:04 +0000 (+0000) Subject: Done day 23 X-Git-Url: https://git.njae.me.uk/?a=commitdiff_plain;h=de1fcea0ec1190169209dc5be726b66f1be14afe;p=advent-of-code-21.git Done day 23 --- diff --git a/advent-of-code21.cabal b/advent-of-code21.cabal index 8ba8f78..6fd1c09 100644 --- a/advent-of-code21.cabal +++ b/advent-of-code21.cabal @@ -43,7 +43,7 @@ common common-extensions , NamedFieldPuns , NegativeLiterals , NumDecimals - , OverloadedLists + -- , OverloadedLists , OverloadedStrings , PartialTypeSignatures , PatternGuards @@ -216,3 +216,8 @@ executable advent22 import: common-extensions, build-directives main-is: advent22/Main.hs build-depends: linear, text, attoparsec, containers, lens + +executable advent23 + import: common-extensions, build-directives + main-is: advent23/Main.hs + build-depends: containers, linear, pqueue, mtl, lens diff --git a/advent23/Main.hs b/advent23/Main.hs new file mode 100644 index 0000000..2666769 --- /dev/null +++ b/advent23/Main.hs @@ -0,0 +1,343 @@ +-- Writeup at https://work.njae.me.uk/2021/12/16/advent-of-code-2021-day-15/ + +import Debug.Trace + + +import qualified Data.PQueue.Prio.Min as P +import qualified Data.Set as S +import qualified Data.Sequence as Q +import Data.Sequence ((<|), (|>), (><)) --, ViewR( (:>) ), ViewL( (:<) )) +import qualified Data.Map.Strict as M +import Data.Map.Strict ((!)) +import Data.Foldable (foldl', sum) -- (toList, foldr', foldl', all) +-- import Data.Char +import Control.Monad.Reader +import Control.Lens hiding ((<|), (|>), (:>), (:<)) +import Data.Maybe -- (fromMaybe) +-- import Linear (V2(..), (^+^)) --, (^-^), (*^), (^*)) +import Linear hiding (trace) + + + +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 Amphipod = A | B | C | D deriving (Show, Read, Eq, Ord, Enum) + +type Coord = V2 Int -- r, c +_r :: Lens' (V2 Int) Int +_r = _x +_c :: Lens' (V2 Int) Int +_c = _y + +data Step = Step + { _destination :: Coord + , _distance :: Int + , _transits :: S.Set Coord + , _entryRequirement :: Maybe Amphipod + } deriving (Show, Eq, Ord) +makeLenses ''Step + +type Steps = M.Map Coord (S.Set Step) + +data Burrow = Burrow + { _possibleSteps :: Steps + , _roomColumns :: M.Map Amphipod Int + , _hallRow :: Int + } deriving (Show, Eq) +makeLenses ''Burrow + +type BurrowContext = Reader Burrow + +type MoveState = M.Map Coord Amphipod + +data AppliedMove = AppliedMove + { _afterMove :: MoveState + , _appliedStep :: Step + } + deriving (Show, Eq, Ord) +makeLenses ''AppliedMove + +data Agendum = + Agendum { _current :: MoveState + , _trail :: Q.Seq MoveState + , _trailCost :: Int + , _cost :: Int + } deriving (Show, Eq) +makeLenses ''Agendum + +type Agenda = P.MinPQueue Int Agendum + +type ExploredStates = S.Set MoveState + + + +main :: IO () +main = + do text <- readFile "data/advent23.txt" + -- let (burrow, initState) = mkBurrow text + -- print burrow + -- print initState + print $ part1 text + print $ part2 text + + +-- part1 :: Burrow -> MoveState -> Int +part1 text = maybe 0 _cost result + where + (burrow, initState) = mkBurrow text + result = runReader (searchBurrow initState) burrow + +part2 text = maybe 0 _cost result + where + rows = lines text + extraRows = [(" #D#C#B#A# " :: String), (" #D#B#A#C# " :: String)] + modifiedRows = (take 3 rows) ++ extraRows ++ (drop 3 rows) + modifiedText = unlines modifiedRows + (burrow, initState) = mkBurrow modifiedText + result = runReader (searchBurrow initState) burrow + + +searchBurrow :: MoveState -> BurrowContext (Maybe Agendum) +searchBurrow initState = + do agenda <- initAgenda initState + aStar agenda S.empty + +initAgenda :: MoveState -> BurrowContext Agenda +initAgenda initState = + do c <- estimateCost initState + return $ P.singleton c Agendum { _current = initState + , _trail = Q.empty, _trailCost = 0, _cost = c} + + +aStar :: Agenda -> ExploredStates -> BurrowContext (Maybe Agendum) +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 + | P.null agenda = return Nothing + | otherwise = + do let (_, currentAgendum) = P.findMin agenda + let reached = currentAgendum ^. current + nexts <- candidates currentAgendum closed + let newAgenda = foldl' (\q a -> P.insert (_cost a) a q) (P.deleteMin agenda) nexts + reachedGoal <- isGoal reached + if reachedGoal + then return (Just currentAgendum) + else if reached `S.member` closed + then aStar (P.deleteMin agenda) closed + else aStar newAgenda (S.insert reached closed) + + +candidates :: Agendum -> ExploredStates -> BurrowContext (Q.Seq Agendum) +candidates agendum closed = + do let candidate = agendum ^. current + let previous = agendum ^. trail + let prevCost = agendum ^. trailCost + succs <- successors candidate + let nonloops = S.filter (\s -> (s ^. afterMove) `S.notMember` closed) succs + let nonloopsQ = Q.fromList $ S.toList nonloops + mapM (makeAgendum previous prevCost) nonloopsQ + + +makeAgendum :: Q.Seq MoveState -> Int -> AppliedMove -> BurrowContext Agendum +makeAgendum previous prevCost newPosition = + do predicted <- estimateCost (newPosition ^. afterMove) + -- grid <- asks _grid + let newTrail = previous |> (newPosition ^. afterMove) + let newPositionCost = stepCost newPosition + let incurred = prevCost + newPositionCost + return Agendum { _current = newPosition ^. afterMove + , _trail = newTrail + , _trailCost = incurred + , _cost = incurred + predicted + } + +-- class (Eq s, Ord s, Show s) => SearchState s where +-- emptySearchState :: MoveState +-- successors :: MoveState -> BurrowContext (Q.Seq MoveState) +-- estimateCost :: MoveState -> BurrowContext Int +-- isGoal :: MoveState -> BurrowContext Bool +-- entryCost :: MoveState -> BurrowContext Int + + +-- instance SearchState Position where + +-- emptySearchState = Position (V2 0 0) + +successors :: MoveState -> BurrowContext (S.Set AppliedMove) +successors moveState = + do steps <- asks _possibleSteps + let succs = M.foldrWithKey' (legalSteps steps moveState) S.empty moveState + return succs + +legalSteps :: Steps -> MoveState -> Coord -> Amphipod -> S.Set AppliedMove -> S.Set AppliedMove +legalSteps steps state here amphipod acc = S.union appliedSteps acc + where allSteps = steps ! here + freeSteps = S.filter freeSpaces allSteps + freeSpaces st = S.null $ S.intersection (M.keysSet state) (st ^. transits) + validTargetSteps = S.filter (\st -> fromMaybe amphipod (st ^. entryRequirement) == amphipod) freeSteps + openRoomSteps = S.filter (openRoom state) validTargetSteps + appliedSteps = S.map (\s -> AppliedMove + { _afterMove = (applyStep state here s) + , _appliedStep = s + } + ) openRoomSteps + +openRoom :: MoveState -> Step -> Bool +openRoom state step + | isNothing e = True + | otherwise = M.null roomBlockers + where e = step ^. entryRequirement + je = fromJust e + tc = step ^. destination . _c + roomBlockers = M.filterWithKey (\(V2 _ ac) a -> a /= je && ac == tc) state + +applyStep :: MoveState -> Coord -> Step -> MoveState +applyStep moveState here step = moveState'' + where moveState' = M.delete here moveState + moveState'' = M.insert (step ^. destination) (moveState ! here) moveState' + +singleStepCost :: Amphipod -> Int +singleStepCost A = 1 +singleStepCost B = 10 +singleStepCost C = 100 +singleStepCost D = 1000 + +estimateCost :: MoveState -> BurrowContext Int +estimateCost state = + do rCols <- asks _roomColumns + hRow <- asks _hallRow + let amphipodCosts = M.mapWithKey (estimateACost rCols hRow) state + return $ sum $ M.elems amphipodCosts + +estimateACost :: M.Map Amphipod Int -> Int -> Coord -> Amphipod -> Int +estimateACost rCols hRow (V2 r c) amphipod = (singleStepCost amphipod) * dist + where targetCol = rCols ! amphipod + dist = if c == targetCol + then 0 + else (r - hRow) + (abs (c - targetCol)) + 1 + +stepCost :: AppliedMove -> Int +stepCost aStep = (singleStepCost amphipod) * (S.size $ aStep ^. appliedStep . transits) + where dest = aStep ^. appliedStep . destination + amphipod = (aStep ^. afterMove) ! dest + +isGoal :: MoveState -> BurrowContext Bool +isGoal state = + do rCols <- asks _roomColumns + let misplaced = M.filterWithKey (inWrongRoom rCols) state + return $ M.null misplaced + +inWrongRoom rCols (V2 _ c) amphipod = c /= rightCol + where rightCol = rCols ! amphipod + + +------------------------------ + + +mkBurrow :: String -> (Burrow, MoveState) +-- mkBurrow :: String -> ((S.Set Coord, M.Map Coord Amphipod), MoveState) +mkBurrow text = (burrow, initState) -- (burrow, initState) + where rows = lines text + hall = mkHall (rows!!1) + rooms = mkRooms $ drop 2 rows + roomCols = S.map (^. _c) $ M.keysSet rooms + hall' = S.filter ((`S.notMember` roomCols) . (^. _c)) hall + routes = mkRoutes hall' rooms + roomColMap = M.fromList $ zip [A .. D] $ S.toAscList roomCols + burrow = Burrow { _possibleSteps = routes, _roomColumns = roomColMap, _hallRow = 1} + initState = mkInitialState rows + + +mkHall :: String -> S.Set Coord +mkHall text = S.fromList hallCoords + where hallCols = filter ((/= '#') . snd) $ zip [0..] text + hallCoords = map ((V2 1) . fst) hallCols + +mkRooms :: [String] -> M.Map Coord Amphipod +mkRooms text = M.unions rooms + where rooms = map mkRoom $ zip [2..] text + +mkRoom :: (Int, String) -> M.Map Coord Amphipod +mkRoom (r, text) = M.fromList roomCoords + where roomCols = filter ((`elem` ("ABCD." :: String)) . snd) $ zip [0..] text + roomCoords = zip (map ((V2 r) . fst) roomCols) [A .. D] + +-- invertRooms rooms = M.fromList [(a, M.keysSet $ M.filter (== a) rooms) | a <- [A .. D]] + +mkRoutes :: S.Set Coord -> M.Map Coord Amphipod -> Steps +mkRoutes halls rooms = M.unionsWith (S.union) [hallRoutes, roomHallRoutes, roomRoomRoutes] + where hallRoutes = S.foldr' (mkHallRoute rooms) M.empty halls + roomHallRoutes = S.foldr' (mkRoomHallRoute halls) M.empty (M.keysSet rooms) + roomRoomRoutes = S.foldr' (mkRoomRoomRoute hallRow rooms) M.empty (M.keysSet rooms) + hallRow = (S.findMin halls) ^. _r + +mkHallRoute :: M.Map Coord Amphipod -> Coord -> Steps -> Steps +-- mkHallRoute rooms here routes | trace ("mkHR " ++ (show here) ++ " " ++ (show routes)) False = undefined +mkHallRoute rooms here routes = M.foldrWithKey' (mkHallRoute1 here) routes rooms + +mkHallRoute1 :: Coord -> Coord -> Amphipod -> Steps -> Steps +-- mkHallRoute1 here there entry routes | trace ("mkHR1 " ++ (show here) ++ " " ++ (show there) ++ (show routes)) False = undefined +mkHallRoute1 here@(V2 hr hc) there@(V2 tr tc) entry routes = M.insert here (S.insert step existingRoutes) routes + -- | trace ("mkHR1 " ++ (show here) ++ " " ++ (show there) ++ (show routes) ++ " > " ++ show res) False = undefined + -- | otherwise = res + where step = Step { _destination = there + , _distance = (S.size transits) + , _transits = transits + , _entryRequirement = Just entry + } + cMin = min hc tc + cMax = max hc tc + transits = S.delete here $ S.fromList $ [V2 hr c | c <- [cMin..cMax]] ++ [V2 r tc | r <- [hr..tr]] + existingRoutes = M.findWithDefault S.empty here routes + -- res = M.insert here (S.insert step existingRoutes) routes + +mkRoomHallRoute :: S.Set Coord -> Coord -> Steps -> Steps +mkRoomHallRoute halls here routes = S.foldr' (mkRoomHallRoute1 here) routes halls + +mkRoomHallRoute1 :: Coord -> Coord -> Steps -> Steps +mkRoomHallRoute1 here@(V2 hr hc) there@(V2 tr tc) routes = M.insert here (S.insert step existingRoutes) routes + where step = Step { _destination = there + , _distance = (S.size transits) + , _transits = transits + , _entryRequirement = Nothing + } + cMin = min hc tc + cMax = max hc tc + transits = S.delete here $ S.fromList $ [V2 r hc | r <- [tr..hr]] ++ [V2 tr c | c <- [cMin..cMax]] + existingRoutes = M.findWithDefault S.empty here routes + +mkRoomRoomRoute :: Int -> M.Map Coord Amphipod -> Coord -> Steps -> Steps +mkRoomRoomRoute hallRow rooms here routes = M.foldrWithKey' (mkRoomRoomRoute1 hallRow here) routes rooms + +mkRoomRoomRoute1 :: Int -> Coord -> Coord -> Amphipod -> Steps -> Steps +-- mkRoomRoomRoute1 _hallRow here there entry routes | trace ("mkRR1 " ++ (show here) ++ " " ++ (show there) ++ (show routes)) False = undefined +mkRoomRoomRoute1 hallRow here@(V2 hr hc) there@(V2 tr tc) entry routes + | here == there = routes + | otherwise = M.insert here (S.insert step existingRoutes) routes + where step = Step { _destination = there + , _distance = (S.size transits) + , _transits = transits + , _entryRequirement = Just entry + } + cMin = min hc tc + cMax = max hc tc + transitUp = S.fromList [V2 r hc | r <- [hallRow..hr]] + transitAcross = S.fromList [V2 hallRow c | c <- [cMin..cMax]] + transitDown = S.fromList [V2 r tc | r <- [hallRow..tr]] + transits = S.delete here $ S.unions [transitUp, transitAcross, transitDown] + existingRoutes = M.findWithDefault S.empty here routes + + +mkInitialState :: [String] -> MoveState +mkInitialState rows = + M.fromList [ (V2 r c, read [(rows!!r)!!c]) + | r <- [0..maxR], c <- [0..maxC] + , isAmphipod ((rows!!r)!!c) + ] + where maxR = length rows - 1 + maxC = (length $ head rows) - 1 + isAmphipod c = c `elem` ("ABCD" :: String) + diff --git a/data/advent23.txt b/data/advent23.txt new file mode 100644 index 0000000..0b327f0 --- /dev/null +++ b/data/advent23.txt @@ -0,0 +1,5 @@ +############# +#...........# +###D#B#D#A### + #C#C#A#B# + ######### \ No newline at end of file diff --git a/data/advent23a.txt b/data/advent23a.txt new file mode 100644 index 0000000..e59b374 --- /dev/null +++ b/data/advent23a.txt @@ -0,0 +1,5 @@ +############# +#...........# +###B#C#B#D### + #A#D#C#A# + ######### \ No newline at end of file diff --git a/problems/day23.html b/problems/day23.html new file mode 100644 index 0000000..b663d78 --- /dev/null +++ b/problems/day23.html @@ -0,0 +1,420 @@ + + + + +Day 23 - Advent of Code 2021 + + + + + + + +

Advent of Code

Neil Smith (AoC++) 46*

        //2021

+ + + +
+ +

--- Day 23: Amphipod ---

A group of amphipods notice your fancy submarine and flag you down. "With such an impressive shell," one amphipod says, "surely you can help us with a question that has stumped our best scientists."

+

They go on to explain that a group of timid, stubborn amphipods live in a nearby burrow. Four types of amphipods live there: Amber (A), Bronze (B), Copper (C), and Desert (D). They live in a burrow that consists of a hallway and four side rooms. The side rooms are initially full of amphipods, and the hallway is initially empty.

+

They give you a diagram of the situation (your puzzle input), including locations of each amphipod (A, B, C, or D, each of which is occupying an otherwise open space), walls (#), and open space (.).

+

For example:

+
#############
+#...........#
+###B#C#B#D###
+  #A#D#C#A#
+  #########
+
+

The amphipods would like a method to organize every amphipod into side rooms so that each side room contains one type of amphipod and the types are sorted A-D going left to right, like this:

+
#############
+#...........#
+###A#B#C#D###
+  #A#B#C#D#
+  #########
+
+

Amphipods can move up, down, left, or right so long as they are moving into an unoccupied open space. Each type of amphipod requires a different amount of energy to move one step: Amber amphipods require 1 energy per step, Bronze amphipods require 10 energy, Copper amphipods require 100, and Desert ones require 1000. The amphipods would like you to find a way to organize the amphipods that requires the least total energy.

+

However, because they are timid and stubborn, the amphipods have some extra rules:

+
    +
  • Amphipods will never stop on the space immediately outside any room. They can move into that space so long as they immediately continue moving. (Specifically, this refers to the four open spaces in the hallway that are directly above an amphipod starting position.)
  • +
  • Amphipods will never move from the hallway into a room unless that room is their destination room and that room contains no amphipods which do not also have that room as their own destination. If an amphipod's starting room is not its destination room, it can stay in that room until it leaves the room. (For example, an Amber amphipod will not move from the hallway into the right three rooms, and will only move into the leftmost room if that room is empty or if it only contains other Amber amphipods.)
  • +
  • Once an amphipod stops moving in the hallway, it will stay in that spot until it can move into a room. (That is, once any amphipod starts moving, any other amphipods currently in the hallway are locked in place and will not move again until they can move fully into a room.)
  • +
+

In the above example, the amphipods can be organized using a minimum of 12521 energy. One way to do this is shown below.

+

Starting configuration:

+
#############
+#...........#
+###B#C#B#D###
+  #A#D#C#A#
+  #########
+
+

One Bronze amphipod moves into the hallway, taking 4 steps and using 40 energy:

+
#############
+#...B.......#
+###B#C#.#D###
+  #A#D#C#A#
+  #########
+
+

The only Copper amphipod not in its side room moves there, taking 4 steps and using 400 energy:

+
#############
+#...B.......#
+###B#.#C#D###
+  #A#D#C#A#
+  #########
+
+

A Desert amphipod moves out of the way, taking 3 steps and using 3000 energy, and then the Bronze amphipod takes its place, taking 3 steps and using 30 energy:

+
#############
+#.....D.....#
+###B#.#C#D###
+  #A#B#C#A#
+  #########
+
+

The leftmost Bronze amphipod moves to its room using 40 energy:

+
#############
+#.....D.....#
+###.#B#C#D###
+  #A#B#C#A#
+  #########
+
+

Both amphipods in the rightmost room move into the hallway, using 2003 energy in total:

+
#############
+#.....D.D.A.#
+###.#B#C#.###
+  #A#B#C#.#
+  #########
+
+

Both Desert amphipods move into the rightmost room using 7000 energy:

+
#############
+#.........A.#
+###.#B#C#D###
+  #A#B#C#D#
+  #########
+
+

Finally, the last Amber amphipod moves into its room, using 8 energy:

+
#############
+#...........#
+###A#B#C#D###
+  #A#B#C#D#
+  #########
+
+

What is the least energy required to organize the amphipods?

+
+

Your puzzle answer was 14460.

--- Part Two ---

As you prepare to give the amphipods your solution, you notice that the diagram they handed you was actually folded up. As you unfold it, you discover an extra part of the diagram.

+

Between the first and second lines of text that contain amphipod starting positions, insert the following lines:

+
  #D#C#B#A#
+  #D#B#A#C#
+
+

So, the above example now becomes:

+
#############
+#...........#
+###B#C#B#D###
+  #D#C#B#A#
+  #D#B#A#C#
+  #A#D#C#A#
+  #########
+
+

The amphipods still want to be organized into rooms similar to before:

+
#############
+#...........#
+###A#B#C#D###
+  #A#B#C#D#
+  #A#B#C#D#
+  #A#B#C#D#
+  #########
+
+

In this updated example, the least energy required to organize these amphipods is 44169:

+
#############
+#...........#
+###B#C#B#D###
+  #D#C#B#A#
+  #D#B#A#C#
+  #A#D#C#A#
+  #########
+
+#############
+#..........D#
+###B#C#B#.###
+  #D#C#B#A#
+  #D#B#A#C#
+  #A#D#C#A#
+  #########
+
+#############
+#A.........D#
+###B#C#B#.###
+  #D#C#B#.#
+  #D#B#A#C#
+  #A#D#C#A#
+  #########
+
+#############
+#A........BD#
+###B#C#.#.###
+  #D#C#B#.#
+  #D#B#A#C#
+  #A#D#C#A#
+  #########
+
+#############
+#A......B.BD#
+###B#C#.#.###
+  #D#C#.#.#
+  #D#B#A#C#
+  #A#D#C#A#
+  #########
+
+#############
+#AA.....B.BD#
+###B#C#.#.###
+  #D#C#.#.#
+  #D#B#.#C#
+  #A#D#C#A#
+  #########
+
+#############
+#AA.....B.BD#
+###B#.#.#.###
+  #D#C#.#.#
+  #D#B#C#C#
+  #A#D#C#A#
+  #########
+
+#############
+#AA.....B.BD#
+###B#.#.#.###
+  #D#.#C#.#
+  #D#B#C#C#
+  #A#D#C#A#
+  #########
+
+#############
+#AA...B.B.BD#
+###B#.#.#.###
+  #D#.#C#.#
+  #D#.#C#C#
+  #A#D#C#A#
+  #########
+
+#############
+#AA.D.B.B.BD#
+###B#.#.#.###
+  #D#.#C#.#
+  #D#.#C#C#
+  #A#.#C#A#
+  #########
+
+#############
+#AA.D...B.BD#
+###B#.#.#.###
+  #D#.#C#.#
+  #D#.#C#C#
+  #A#B#C#A#
+  #########
+
+#############
+#AA.D.....BD#
+###B#.#.#.###
+  #D#.#C#.#
+  #D#B#C#C#
+  #A#B#C#A#
+  #########
+
+#############
+#AA.D......D#
+###B#.#.#.###
+  #D#B#C#.#
+  #D#B#C#C#
+  #A#B#C#A#
+  #########
+
+#############
+#AA.D......D#
+###B#.#C#.###
+  #D#B#C#.#
+  #D#B#C#.#
+  #A#B#C#A#
+  #########
+
+#############
+#AA.D.....AD#
+###B#.#C#.###
+  #D#B#C#.#
+  #D#B#C#.#
+  #A#B#C#.#
+  #########
+
+#############
+#AA.......AD#
+###B#.#C#.###
+  #D#B#C#.#
+  #D#B#C#.#
+  #A#B#C#D#
+  #########
+
+#############
+#AA.......AD#
+###.#B#C#.###
+  #D#B#C#.#
+  #D#B#C#.#
+  #A#B#C#D#
+  #########
+
+#############
+#AA.......AD#
+###.#B#C#.###
+  #.#B#C#.#
+  #D#B#C#D#
+  #A#B#C#D#
+  #########
+
+#############
+#AA.D.....AD#
+###.#B#C#.###
+  #.#B#C#.#
+  #.#B#C#D#
+  #A#B#C#D#
+  #########
+
+#############
+#A..D.....AD#
+###.#B#C#.###
+  #.#B#C#.#
+  #A#B#C#D#
+  #A#B#C#D#
+  #########
+
+#############
+#...D.....AD#
+###.#B#C#.###
+  #A#B#C#.#
+  #A#B#C#D#
+  #A#B#C#D#
+  #########
+
+#############
+#.........AD#
+###.#B#C#.###
+  #A#B#C#D#
+  #A#B#C#D#
+  #A#B#C#D#
+  #########
+
+#############
+#..........D#
+###A#B#C#.###
+  #A#B#C#D#
+  #A#B#C#D#
+  #A#B#C#D#
+  #########
+
+#############
+#...........#
+###A#B#C#D###
+  #A#B#C#D#
+  #A#B#C#D#
+  #A#B#C#D#
+  #########
+
+

Using the initial configuration from the full diagram, what is the least energy required to organize the amphipods?

+
+

Your puzzle answer was 41366.

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