From: Neil Smith Date: Sun, 25 Dec 2016 16:01:27 +0000 (+0000) Subject: Day 24 at last X-Git-Url: https://git.njae.me.uk/?p=advent-of-code-16.git;a=commitdiff_plain;h=14719080465b4b525aeb9cfddcb6e5ec1c0ff544 Day 24 at last --- diff --git a/adventofcode1624/adventofcode1624.cabal b/adventofcode1624/adventofcode1624.cabal new file mode 100644 index 0000000..f016db1 --- /dev/null +++ b/adventofcode1624/adventofcode1624.cabal @@ -0,0 +1,50 @@ +name: adventofcode1624 +version: 0.1.0.0 +synopsis: Initial project template from stack +description: Please see README.md +homepage: https://github.com/neilnjae/adventofcode16#readme +license: BSD3 +license-file: LICENSE +author: Neil Smith +maintainer: noone@njae.me.uk +copyright: 2016 Neil Smith +category: None +build-type: Simple +extra-source-files: README.md +cabal-version: >=1.10 + +library + hs-source-dirs: src + build-depends: base >= 4.7 && < 5 + default-language: Haskell2010 + +executable advent24 + hs-source-dirs: app + main-is: advent24.hs + ghc-options: -O2 -threaded -rtsopts -with-rtsopts=-N + build-depends: base + , adventofcode1624 + , adventofcode16 + , containers + , astar + , hashable + , unordered-containers + default-language: Haskell2010 + +test-suite adventofcode1624-test + type: exitcode-stdio-1.0 + hs-source-dirs: test + main-is: Spec.hs + build-depends: base + , adventofcode1601 + , adventofcode16 + , containers + , astar + , hashable + , unordered-containers + ghc-options: -threaded -rtsopts -with-rtsopts=-N + default-language: Haskell2010 + +source-repository head + type: git + location: https://github.com/neilnjae/adventofcode16 diff --git a/adventofcode1624/app/advent24.hs b/adventofcode1624/app/advent24.hs new file mode 100644 index 0000000..fc97d16 --- /dev/null +++ b/adventofcode1624/app/advent24.hs @@ -0,0 +1,175 @@ +{-# LANGUAGE DeriveGeneric #-} + +module Main(main) where + +import GHC.Generics (Generic) +import Data.Maybe (catMaybes, fromJust) +import Data.List +import Data.Char (isDigit) +import qualified Data.Map.Strict as M +import Data.Map.Strict ((!)) +import qualified Data.HashSet as S +import Data.Graph.AStar +import Data.Hashable +import qualified Data.HashSet +import Debug.Trace + +type Point = (Int, Int) -- row, column, both zero based. +type Grid = M.Map Point Char + +data Path = Path { from :: Point + , to :: Point + , path :: Int + } deriving (Eq, Generic) +instance Hashable Path +-- instance Eq Path where +-- p1 == p2 = (joins p1) == (joins p2) +instance Show Path where + show p = "Path { " ++ show (from p) ++ " -> " ++ show (to p) ++ ", " ++ show (path p) ++ " }" + +type PathSet = S.HashSet Path + +-- Grid search state +data Gss = Gss { origin :: Point + , current :: Point + , goal :: Point + , gssPath :: [Point] + } deriving (Eq, Generic) +instance Hashable Gss +instance Ord Gss where + s1 `compare` s2 = ((heuristicG s1) + (length (gssPath s1))) `compare` ((heuristicG s2) + (length (gssPath s2))) +instance Show Gss where + show gss = "Gss { " ++ show (origin gss) ++ " -> " ++ show (current gss) ++ " -> " ++ show (goal gss) ++ " }" + +data Tour = Tour {at :: Point, tour :: [Path]} deriving (Show, Eq) + + +littleGrid = "\ +\###########\n\ +\#0.1.....2#\n\ +\#.#######.#\n\ +\#4.......3#\n\ +\###########" + +main :: IO () +main = do + text <- readFile "data/advent24.txt" + -- let text = littleGrid + let tl = lines text + let mp = M.fromList $ [((r, c), (tl!!r)!!c)| r <- [0..(length tl - 1)], c <- [0..(length (tl!!0) - 1)]] + let goals = M.filter (isDigit) mp + let start = head $ M.keys $ M.filter (=='0') mp + let aStarSearch s g = asG [startGss s g] mp [] + let paths = map (fromGss) $ catMaybes $ [aStarSearch st gl | st <- (M.keys goals), gl <- (M.keys goals), st /= gl] + + -- part0 mp + part1 start (M.keys goals) paths + part2 start (M.keys goals) paths + +part0 mp = print (length allPaths, allPaths) + where goals = M.filter (isDigit) mp + start = head $ M.keys $ M.filter (=='0') mp + -- goal = head $ M.keys goals + goal = head $ M.keys $ M.filter (=='2') mp + -- aStarSearch s g = aStar (successorsG mp) costG heuristicG isGoalG (startGss s g) + aStarSearch s g = asG [startGss s g] mp [] + traceSearch s g = trace ("Trace " ++ (show s) ++ " -> " ++ (show g)) (aStarSearch s g) + paths = S.fromList $ map (fromGss) $ catMaybes $ map (\gl -> aStarSearch start gl) $ M.keys goals + path = aStarSearch start goal + allPaths = map (fromGss) $ catMaybes $ [traceSearch st gl | st <- (M.keys goals), gl <- (M.keys goals), st /= gl] + +fromGss :: Gss -> Path +fromGss g = Path {from = origin g, to = goal g, path = (length (gssPath g)) - 1} + +part1 :: Point -> [Point] -> [Path] -> IO () +part1 start points paths = print $ shortestTour start points paths + + -- where goals = M.filter (isDigit) mp + -- start = head $ M.keys $ M.filter (=='0') mp + -- aStarSearch s g = asG [startGss s g] mp [] + -- paths = nub $ map (fromGss) $ catMaybes $ [aStarSearch st gl | st <- (M.keys goals), gl <- (M.keys goals), st /= gl] + +part2 :: Point -> [Point] -> [Path] -> IO () +part2 start points paths = print $ shortestReturningTour start points paths + +-- bfsG :: [Gss] -> Grid -> [Path] -> [Point] -> [Path] +-- -- bfsG ps _ paths closed | trace ((show ps) ++ " :: " ++ (show paths) ++ " X " ++ (show closed)) False = undefined +-- bfsG [] _ paths _ = paths +-- bfsG (p:ps) g paths closed = +-- if current p /= origin p && isDigit currentCell +-- then bfsG ps g (newPath:paths) ((current p):closed) +-- else bfsG (ps ++ extraAgenda) g paths ((current p):closed) +-- where currentCell = (g!(current p)) +-- newPath = Path {joins = S.fromList [current p, origin p], path = gssPath p} +-- nextPoints = filter (\np -> np `notElem` ((gssPath p) ++ closed)) $ gridNeighbours g $ current p +-- extraAgenda = map (\n -> Gss {origin = origin p, goal = goal p, current = n, gssPath = (n:(gssPath p))}) nextPoints + +asG :: [Gss] -> Grid -> [Point] -> Maybe Gss +-- asG ps _ closed | trace ((show ps) ++ " :: " ++ (show paths) ++ " X " ++ (show closed)) False = undefined +asG [] _ _ = Nothing +asG (p:ps) g closed = + if current p == goal p + then Just p + else if (head $ gssPath p) `elem` closed + then asG ps g closed + else asG newAgenda g ((current p):closed) + where -- currentCell = (g!(current p)) + -- newPath = Path {joins = S.fromList [current p, origin p], path = gssPath p} + nextPoints = filter (\np -> np `notElem` ((gssPath p) ++ closed)) $ gridNeighbours g $ current p + extraAgenda = map (\n -> Gss {origin = origin p, goal = goal p, current = n, gssPath = (n:(gssPath p))}) nextPoints + newAgenda = sort (ps ++ extraAgenda) + + +startGss :: Point -> Point -> Gss +startGss p g = Gss {origin = p, goal = g, current = p, gssPath = [p]} + + +gridNeighbours :: Grid -> Point -> [Point] +gridNeighbours g p@(r, c) = filter (\n -> (g!n) /= '#') ns + where ns = [(r-1, c), (r+1, c), (r, c-1), (r, c+1)] + +heuristicG :: Gss -> Int +heuristicG gss = abs (rg - rc) + abs (cg - cc) + where (rg, cg) = goal gss + (rc, cc) = current gss + +-- isGoalG :: Gss -> Bool +-- isGoalG st = current st == goal st + +-- successorsG :: Grid -> Gss -> Data.HashSet.HashSet Gss +-- successorsG grid st = Data.HashSet.fromList extraAgenda +-- where nextPoints = gridNeighbours grid $ current st +-- -- nextPoints = filter (\np -> np `notElem` (gssPath st)) $ gridNeighbours grid $ current st +-- extraAgenda = map (\n -> Gss {origin = origin st, goal = goal st, current = n, gssPath = (n:(gssPath st))}) nextPoints + +-- costG :: a -> b -> Int +-- costG = const $ const 1 + + + +shortestTour :: Point -> [Point] -> [Path] -> Int +shortestTour p0 points paths = minimum $ map (\p -> pathLength p paths) startRight + where pointPerms = permutations points + startRight = filter (\p -> (head p) == p0) pointPerms + +shortestReturningTour :: Point -> [Point] -> [Path] -> Int +shortestReturningTour p0 points paths = minimum $ map (\p -> pathLength p paths) startRight + where pointPerms = map (\p -> p ++ [p0]) $ permutations points + startRight = filter (\p -> (head p) == p0) pointPerms + +pathBetween :: [Path] -> Point -> Point -> Path +pathBetween paths a b = head $ filter (\p -> from p == a && to p == b) paths + +adjacents :: [a] -> [[a]] +adjacents ts = filter (\t -> (length t) == 2) $ map (\t -> take 2 t) $ tails ts + +pathLength :: [Point] -> [Path] -> Int +pathLength points paths = sum $ map (path) builtPath + where pairs = adjacents points + builtPath = foldl (addPath paths) [] pairs + +addPath :: [Path] -> [Path] -> [Point] -> [Path] +addPath paths built posPair = built ++ [toAdd] + where toAdd = pathBetween paths (posPair!!0) (posPair!!1) + + diff --git a/data/advent24.txt b/data/advent24.txt new file mode 100644 index 0000000..771b64d --- /dev/null +++ b/data/advent24.txt @@ -0,0 +1,45 @@ +####################################################################################################################################################################################### +#.......#.....#.....#.#.....#.#...#.#.......#.....#.#...#.......#...........#...#.............#.....#.......#.........#.....#.....#...........#.#...................#.....#...........# +#.#######.#.#.#.###.#.#####.#.#.#.#.#####.#.#.###.#.#######.#.###.#.#.#.#.#####.#.#########.#.###.#.#.#.#.#.#.#.#.###.#.#####.#.#.#.#.#.#.#.#.#.#.#.###.#####.#.#.#.#.#.#.#.#.#.#.#.#.# +#....0#.#.....#.#...#.......#.......#...#...#.#......1#.....#.....#.........#...#...#.....#.........#.#...#.#.#.#.#...#.#...#.....#...#...#...#.#...#.#.#.#...........#.#.......#.#..3# +#.#####.#.#.#.#.#.###.###.#.###.#.#.#.###.#.#.#.#.#.#.###.#.#.#######.#.#.#.###.#.#.#.#.#######.#.###.###.#.#.###.#####.#.#.#.#####.###.#.#.#########.#.#.#.###.#####.#.#.#####.#.#.### +#...#...#.#.#.....#...#.............#.#.......#.......#.#...#.#.........#.......#.#.....#.......#.......................#.#...#.#.#...#...#.#.#...#...#.......#.........#...#.#.....#.# +#.#.###.#.#.#.#.#.#.#.#.#.###.#.#.#.#.#.###.###.###.#.#.#.#.###.###.###.#.#.#####.#.#.#.#.#.#.#.#.###.#.###########.#.#.#.#.#.#.#.###.###.#.#.#.#.#.#.#.#.#.#.#####.###.#.###.#.#####.# +#...#...#...#...#.#.#.#...#...#...#...#.....#...................#...#.#.....#...........#.....#.#.#...#.#...#.........#.#.......#...........#...#.....#...#.#...............#.#.......# +#.#.#.#.###.#.#.###.#######.#.#.#.#.#.#.###.#.###.#.#.#.###.#.#.#.#.#.#.#####.#.#.###.#.#.###.#.#.#.#.#.###.###.#.#.#.#####.#.###########.#.#.#.#########.#.#.###.###.###.#.#.###.#.#.# +#.#.........#...#.....#.....#.#...#...#.....#...............#...#.......#.#.#.......#.#...#.....#.#.#.........#.#.........#...#...#.........#.#...#.#.#...........#.....#.......#.....# +#.#.#.#.#.###.#.#.#.#.#.#.###.#########.#.#.###.#.#.#####.#####.#.#####.#.#.###.#.#.#.#.#.#.#.#.#.#.#.#.#.###.###.###.#.#.###.###.#.#.#.#.#.###.#.#.#.#.#.#####.###.#.#.#######.#.###.# +#...#.........#...#.#...#.#.#...........#.#.#...........#.......#.#.#.....#...#.#.#.#...#.......#.........#...#.....#...#.....#.#.....#.#...#.....#.#...#.....#.#.#.#.............#...# +#.#.###########.###.#.###.#.#####.#.#.#.###.#.###.#.#.#.#########.#.#.#####.#.#.#.#.#.#.#####.#.#.#.###.#.#.#.#.###############.#.###.#.#.#.#.#.###.###.#.#.#.#.#.#.#####.#.#.###.#.### +#.....#.#...........#.#.............#.#...........#.....#.#.....#...#.#.#.#...........#.#.....#...#.....#...#.....#...........#.#.#...#.........#.#.....#...#.......#.....#...#.......# +#####.#.#.#.#.#.#####.#.#####.#.#.#.#.###.#.#.###.#######.#.#.#####.#.#.#.#.#.#####.###.#.###.#.#.#.#####.#.#.###.#.###.#.###.#.#.###.#.###.###.#.#.#.#.###.#.#####.#.#.#.#####.#.###.# +#.....#.#.....#.#.......#.......#.....#...#...#...............#.....#...........#.........#.....#.#.#.............#.#...#.#.....#.#...#...#...#.........#.....#...#...#...........#...# +#.#.#.###.#.###.#.#.#.###.#.###.#.#.#.###.###.#.###.#.#.#.#####.#.#.#.###.#####.#####.#.#.#.###.#.###.###.#####.#.#.#.#.#.###.###.#.###.#.#.#.#.#.#####.#####.#.#.#.###.#.#.#.#####.### +#...#.....#.#.......#.....#.#.....#...#...#.#.#.....#...#.#...#.#.....................#.....#.....#.....#.......#.........#...#...#...#.#.#.#...#.#.#...#...#.....#.#.......#...#.....# +#####.###.###.#.#.#.#.#.#.###.#.#.#.#####.#.#.#.#.#.#######.#.#.#.#.#.#######.###.#.###.#.#.###.#.#.#.#.#.#####.#.#.#.###.#.###.###.#.###.#.###.#.#.#.#.###.#.###.###.#####.###.#.##### +#.....#.....#...#.....#.#...#...#.........#...................#.....#...#.........#.....#...........#...#.#.......#.#...#...#...............#.......#...#.........#.............#.....# +#.#.#.#.#######.#.#.#########.#######.###.#####.###.#.###.#.#######.#.###.#.###.###.###.#####.#####.###.#.#.#.#.#.#.#.###.#.#.#######.#.#.#.#.#.#.#.#.#####.#.#.#.#.#.#.###.#.#.###.#.# +#2#.#.......#...#.#...#.......#.................#.....#...#.......#.#.....#.....#.#...#.#.....#...#.#.......#...#.....#.....#.....#.......#.....#...#.#...#.....#...#.#.#7..#...#.....# +###.#.#####.#.###.###.#.#.###.#.###.#####.#.#.#######.#.#########.#####.#.#.#.###.#.#.#.###.#######.#.#########.#.#.#.#.#.#.#####.###.###.###.#.#.#.#.#.#.#.###.#.#.#.#.#####.#.#.###.# +#.#...#.....#.....#.#.....#...#...#.#...#...#.#.#.#.....#.....#.#.#.#.....#.................#.#.#...#...#...#.#.#.#.#.#...#...#.#.............#.#...#...#.#.#.......#.........#.#.....# +#.###.#.###.#.#.#.#.###.#.#.###.#####.#.###.#.#.#.#.#.###.#.#.#.#.#.#.#.#.#.#.#####.###.#.###.#.#.###.#.#.#.#.#.#.#.#.#.###.#.#.###.#.#.#.#######.#.###.#.#.#.###.#.#.#.###.###.#.#.#.# +#.#...#.....#.....#.#...#...#.......#...#.....#.#.#.....#.#...#...#...#.#.........#.....#...#.#...#...#...#.#.#.......#...#.#...#...#.#...#.....#.......#.......#.#.....#.#...#.#.....# +#.#.#.#.#.#.#.###.#.###.#.#.#.###.###.#.#.###.###.#.#.#.#.###.#.#.#.#.#.#.#########.#.#.#.#.#.#######.#.###.#.#.#.#.#.#.###.#.###.#######.#.#.#.#.###.#.#.#.#.#.#.#.#####.###.#.#.###.# +#.....#.....#.#...#.#.#...#.....#.....#.#...#.....#.....#.....#.#.#...#...#.#.....#.#.#...#...#.......#.....#...........#...#.#...#.......#.......#.#.#...#.#...#.#.#...........#.....# +#.#####.#####.#####.#.###.#########.#.#.#.#.###.#.#.#.#.#.#.#.#####.###.#.#.#.###.#.###.#.#####.###.#####.#####.#.###.###.#.#.#.#.#.###.#.#.#####.#.#.###.###.###.#.#.#.#.#.###.###.#.# +#.....#...#...#.#...#.........#.................#.#.....#.#.....#.........#...#.....#...#.#.....#.......#.......#.....#.#.#.......#.#...#.#...#.#.........#.........#...#.....#.....#.# +#.###.#####.#.#.#.#.#.#######.#.#####.#########.#.#.###.#.#####.#.#####.###.#.#.#.#.###.#.#.#.#.###.#.#####.#.###.###.#.#.#.###.#.#.#.#.#.#.#.#.#.#####.#.#.###.#.#.#.#.#.#.#.###.###.# +#.#...#.#.....#...#.#.#.......#.#.................#...#.....#...............#.........#...#.#.#...#.#...#...#.........#.....#...........#.#...........#.....#.#.#.#...#...#...#.#.#...# +#.#.#.#.#.###.#######.#.#.#.###.#.#.#.###.#.#.###.###.#.###.#.#####.#.#.#.#.#.###.#########.#.#.#.#.#.#.#######.###.#.#.###.#.#.###.#.###.#.#.###.#.#.#.#.#.#.#.#.#.###.#####.#.###.#.# +#.#.....#.....#.#.......#...#...#...#.#...#.....#.......#...#...#...#.#.#...#...#.....#.#...#...........#.........#...#.#...#...#...#...#...........#5#.#...#...........#.....#.#.....# +###.#.###.#####.#.#.#.#.#.###.#.#.#####.#.#.#.#.#.#.#.###.###.#.#.###.#.###.###.#####.#.#.###.#.#.###.#.#.#.###.#####.###.#####.#.#.###.#.#####.#.#.#.#####.###.###.###.#.#.#.#.#.#.### +#.........#.....#.....#...#...............#.#...#.#.#.....#.#...#...#.#...............#.......#.......#.#...#.#...........#.#.#...............#...#.........#...............#...#...#.# +#.#.#.###.#.#####.#.#.#.#.#.#.###.###.###.#####.#.#####.###.#.#.###.#.###.###.#####.#####.#####.#########.###.#.#.#.#.#.#.#.#.#.#.#.#.###.#.#.###.#####.###.#####.###.#.###.###.#.#.#.# +#.....#.#.............#...#.......#.#.............#.#...#.#...#...#.#.....#.#.#...#.#.....#...#...........#.....#.#.#...#...................#.....#.....#...............#.....#.#.....# +#.#####.#.###.#.#######.###.###.#.#.#.###.###.#.###.#.#.#.###.#.#.#.#####.#.###.###.#########.#.#####.#.#.#.#.#.#.#.#####.#########.#.#.#.#.###.###.#.#####.#.#.###.#####.#.#.###.###.# +#...#.....#4#.#.#...............#.........#.....#.......#.........#...........#...#.......#.#...#.......#.....#...#.#...#.#...#.#.....#...........#.................#...#.#.#.#...#.#.# +#.#.#.#####.#.###.###.#.#.#####.#.#####.###.#.###.#.#######.#.#.###.###.###.#.#.#.#.#.#.#.#.#.#.#.#.#######.#######.#.#.###.###.#.###.#.###.#.#.#.#.#.#######.#.#.###.#.###.#####.#.#.# +#.....#.#.....#...#...#.#.......#...#.............#...#.....#...#.#.......#.....#...#...#.#.....#.#...........#.......#.#...#...#.#...#.#.#.....#...............#...#.#.#...#...#.....# +#####.#.#.#.###.#.###.#.#####.#######.#############.#.#.#.#.#.###.#.#.###.#.#####.#.#.#.#####.#.#.###.###.#.#.#.###.#.#.###.#.#.#.#.#.#.#.#.#.###.###.#.#######.###.#.#####.#######.### +#.....#...........#.....#.....#.......#...#...#.......#.....#.#...#.#.#...#.#...#.....#.......#...#...#...#.#.#.#.....#.....#...#.#...#......6#...#...#.....#...#...#.........#.#.....# +####################################################################################################################################################################################### diff --git a/day24.html b/day24.html new file mode 100644 index 0000000..54becd2 --- /dev/null +++ b/day24.html @@ -0,0 +1,152 @@ + + + + +Day 24 - Advent of Code 2016 + + + + + + +

Advent of Code

Neil Smith (AoC++) 48*

   int y=2016;

+ + + +
+

--- Day 24: Air Duct Spelunking ---

You've finally met your match; the doors that provide access to the roof are locked tight, and all of the controls and related electronics are inaccessible. You simply can't reach them.

+

The robot that cleans the air ducts, however, can.

+

It's not a very fast little robot, but you reconfigure it to be able to interface with some of the exposed wires that have been routed through the HVAC system. If you can direct it to each of those locations, you should be able to bypass the security controls.

+

You extract the duct layout for this area from some blueprints you acquired and create a map with the relevant locations marked (your puzzle input). 0 is your current location, from which the cleaning robot embarks; the other numbers are (in no particular order) the locations the robot needs to visit at least once each. Walls are marked as #, and open passages are marked as .. Numbers behave like open passages.

+

For example, suppose you have a map like the following:

+
###########
+#0.1.....2#
+#.#######.#
+#4.......3#
+###########
+
+

To reach all of the points of interest as quickly as possible, you would have the robot take the following path:

+
    +
  • 0 to 4 (2 steps)
  • +
  • 4 to 1 (4 steps; it can't move diagonally)
  • +
  • 1 to 2 (6 steps)
  • +
  • 2 to 3 (2 steps)
  • +
+

Since the robot isn't very fast, you need to find it the shortest route. This path is the fewest steps (in the above example, a total of 14) required to start at 0 and then visit every other location at least once.

+

Given your actual map, and starting from location 0, what is the fewest number of steps required to visit every non-0 number marked on the map at least once?

+
+

Your puzzle answer was 412.

--- Part Two ---

Of course, if you leave the cleaning robot somewhere weird, someone is bound to notice.

+

What is the fewest number of steps required to start at 0, visit every non-0 number marked on the map at least once, and then return to 0?

+
+

Your puzzle answer was 664.

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 diff --git a/stack.yaml b/stack.yaml index 48e2e2e..b51ba57 100644 --- a/stack.yaml +++ b/stack.yaml @@ -4,6 +4,7 @@ packages: - adventofcode16 - adventofcode1601 - adventofcode1602 +- adventofcode1624 system-ghc: true extra-deps: - astar-0.3.0.0