Compare commits

...

10 commits

Author SHA1 Message Date
thornAvery f401e0a681 15 2021-12-15 21:28:46 +00:00
thornAvery 3b4c9c0962 alt 05 2021-12-15 01:11:24 +00:00
thornAvery 8b5adfcd3b cleanup 2021-12-14 21:43:35 +00:00
thornAvery cb5da3cd96 timings 2021-12-14 07:07:01 +00:00
thornAvery ab98e50cea 14 2021-12-14 07:01:50 +00:00
thornAvery de4c80d259 07 speedup 2021-12-14 04:29:43 +00:00
thornAvery 9bbd9d8088 cleanup 2021-12-14 03:19:18 +00:00
thornAvery cec5485fda improved 12 2021-12-14 03:17:58 +00:00
thornAvery 46a6c20cde cleanup 2021-12-13 10:08:26 +00:00
thornAvery 149ba84b98 cleanup 2021-12-13 07:48:26 +00:00
25 changed files with 878 additions and 103 deletions

View file

@ -101,3 +101,17 @@ executable aoc2021-13
hs-source-dirs: src/13
build-depends: base
default-language: Haskell2010
executable aoc2021-14
main-is: Main.hs
ghc-options: -O2 -Wall
hs-source-dirs: src/14
build-depends: base, containers
default-language: Haskell2010
executable aoc2021-15
main-is: Main.hs
ghc-options: -O2 -Wall
hs-source-dirs: src/15
build-depends: base, containers, PSQueue
default-language: Haskell2010

View file

@ -43,8 +43,6 @@ How many measurements are larger than the previous measurement?
Your puzzle answer was 1832.
The first half of this puzzle is complete! It provides one gold star: *
--- Part Two ---
Considering every single measurement isn't as useful as you expected: there's just too much noise in the data.
@ -77,3 +75,8 @@ H: 792 (increased)
In this example, there are 5 sums that are larger than the previous sum.
Consider sums of a three-measurement sliding window. How many sums are larger than the previous sum?
Your puzzle answer was 1858.
Both parts of this puzzle are complete! They provide two gold stars: **

View file

@ -30,8 +30,6 @@ Calculate the horizontal position and depth you would have after following the p
Your puzzle answer was 1698735.
The first half of this puzzle is complete! It provides one gold star: *
--- Part Two ---
Based on your calculations, the planned course doesn't seem to make any sense. You find the submarine manual and discover that the process is actually slightly more complicated.
@ -56,4 +54,7 @@ After following these new instructions, you would have a horizontal position of
Using this new interpretation of the commands, calculate the horizontal position and depth you would have after following the planned course. What do you get if you multiply your final horizontal position by your final depth?
Your puzzle answer was 1594785890.
Both parts of this puzzle are complete! They provide two gold stars: **

View file

@ -33,8 +33,6 @@ Use the binary numbers in your diagnostic report to calculate the gamma rate and
Your puzzle answer was 4160394.
The first half of this puzzle is complete! It provides one gold star: *
--- Part Two ---
Next, you should verify the life support rating, which can be determined by multiplying the oxygen generator rating by the CO2 scrubber rating.
@ -64,3 +62,8 @@ As there is only one number left, stop; the CO2 scrubber rating is 01010, or 10
Finally, to find the life support rating, multiply the oxygen generator rating (23) by the CO2 scrubber rating (10) to get 230.
Use the binary numbers in your diagnostic report to calculate the oxygen generator rating and CO2 scrubber rating, then multiply them together. What is the life support rating of the submarine? (Be sure to represent your answer in decimal, not binary.)
Your puzzle answer was 4125600.
Both parts of this puzzle are complete! They provide two gold stars: **

View file

@ -55,8 +55,6 @@ To guarantee victory against the giant squid, figure out which board will win fi
Your puzzle answer was 45031.
The first half of this puzzle is complete! It provides one gold star: *
--- Part Two ---
On the other hand, it might be wise to try a different strategy: let the giant squid win.
@ -65,3 +63,8 @@ You aren't sure how many bingo boards a giant squid could play at once, so rathe
In the above example, the second board is the last to win, which happens after 13 is eventually called and its middle column is completely marked. If you were to keep playing until this point, the second board would have a sum of unmarked numbers equal to 148 for a final score of 148 * 13 = 1924.
Figure out which board will win last. Once it wins, what would its final score be?
Your puzzle answer was 2568.
Both parts of this puzzle are complete! They provide two gold stars: **

View file

@ -66,6 +66,3 @@ Your puzzle answer was 17741.
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.

90
code/src/05/Main2.hs Normal file
View file

@ -0,0 +1,90 @@
-- why is this slower than the other one? i dont get it
module Main where
import Data.Tuple
import Data.List
import qualified Text.Parsec as P
import qualified Data.Map as M
import Data.Map.Strict (insertWith)
type Point = (Int,Int)
type Segment = (Point,Point)
type Op = Db -> Db
type Db = M.Map Point Int
data Line =
Straight Segment
| Diag Segment
main :: IO ()
main = do
raw <- getContents
let input = parseInput raw
(straight, diag) = splitLines input
partAdb = toOps straight $ M.empty
partBdb = toOps diag $ partAdb
putStrLn $ "day5a: " ++ show (solve $ partAdb)
putStrLn $ "day5b: " ++ show (solve $ partBdb)
solve :: Db -> Int
solve db = M.size $ M.filter (>= 2) db
toOps :: [Line] -> Op
toOps ls = foldl (.) id $ map toOp ls
toOp :: Line -> Op
toOp l = foldl (.) id $ map f (createSpots l)
where
f p = insertWith (+) p 1
splitLines :: [Line] -> ([Line], [Line])
splitLines = go ([],[])
where
go acc [] = acc
go (al,ar) (l@(Straight s):ls) = go ((l:al),ar) ls
go (al,ar) (l@(Diag s):ls) = go (al,(l:ar)) ls
parseInput :: String -> [Line]
parseInput raw = [ toLine l | Right l <- segs ]
where
segs = map (P.parse lineP []) $ lines raw
toLine :: Segment -> Line
toLine s@((x1,y1),(x2,y2))
| x1 == x2 || y1 == y2 = Straight s
| otherwise = Diag s
lineP :: P.Parsec String () Segment
lineP = do
x1 <- P.many1 P.digit
_ <- P.char ','
y1 <- P.many1 P.digit
_ <- P.string " -> "
x2 <- P.many1 P.digit
_ <- P.char ','
y2 <- P.many1 P.digit
return ((read x1, read y1), (read x2, read y2))
range :: Int -> Int -> [Int]
range x y = [ i .. j ]
where
(i,j) = if x > y then (y,x) else (x,y)
createSpots :: Line -> [Point]
createSpots (Straight ps) = runStraight ps
createSpots (Diag ps) = runDiag ps
runStraight :: Segment -> [Point]
runStraight ((x1,y1),(x2,y2))
| x1 == x2 = [ (x1,j) | j <- range y1 y2 ]
| otherwise = [ (i,y1) | i <- range x1 x2 ]
runDiag :: Segment -> [Point]
runDiag ((x1,y1),(x2,y2)) = take n $ iterate f start
where
dl (x,y) = (x+1,y+1)
dr (x,y) = (x-1,y+1)
n = (abs (x1-x2)) + 1
f = if (fst start) < (fst end) then dl else dr
(start,end) = (if y1 < y2 then id else swap) ((x1,y1),(x2,y2))

View file

@ -5,7 +5,7 @@ A massive school of glowing lanternfish swims past. They must spawn quickly to r
Although you know nothing about this specific species of lanternfish, you make some guesses about their attributes. Surely, each lanternfish creates a new lanternfish once every 7 days.
However, this process isn't necessarily synchronized between every lanternfish - one lanternfish might have 2 days left until it creates another lanternfish, while another might have 4. So, you can model each fish as a single number that represents the number of days until it creates a new lanternfish.
However, this process isn't necessarily synchronized between every lanternfish - one lanternfish might have 2 days left until it creates another lanternfish, while another might have 4. So, you can model each fish as a single number that represents the number of days until it creates a nw lanternfish.
Furthermore, you reason, a new lanternfish would surely need slightly longer before it's capable of producing more lanternfish: two more days for its first cycle.
@ -50,11 +50,14 @@ Find a way to simulate lanternfish. How many lanternfish would there be after 80
Your puzzle answer was 395627.
The first half of this puzzle is complete! It provides one gold star: *
--- Part Two ---
Suppose the lanternfish live forever and have unlimited food and space. Would they take over the entire ocean?
After 256 days in the example above, there would be a total of 26984457539 lanternfish!
How many lanternfish would there be after 256 days?
Your puzzle answer was 1767323539209.
Both parts of this puzzle are complete! They provide two gold stars: **

View file

@ -57,8 +57,3 @@ Your puzzle answer was 96798233.
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 [Share] this puzzle.

View file

@ -5,30 +5,27 @@ import Data.List
main :: IO ()
main = do
raw <- getLine
let input = map read $ words $ repCom raw
let input = sort $ map read $ words $ repCom raw
putStrLn $ "day7a: " ++ (show $ solveA input)
putStrLn $ "day7b: " ++ (show $ solveB input)
repCom :: String -> String
repCom = map f
where f c = if c == ',' then ' ' else c
solveA :: [Int] -> Int
solveA is = minimum $ map f us
solveA is = sum $ map (absdiff mid) is
where
f x = sum $ map (absdiff x) is
us = nub is
mid = is !! (length is `div` 2)
solveB :: [Int] -> Int
solveB is = minimum $ map f [low .. high]
solveB is = sum $ map (expdiff mid) is
where
high = maximum us
low = minimum us
f x = sum $ map (expdiff x) is
us = nub is
mid = (sum is) `div` (length is)
absdiff :: Int -> Int -> Int
absdiff x y = abs (x - y)
expdiff :: Int -> Int -> Int
expdiff x y = sum $ take (absdiff x y) [1..]
repCom :: String -> String
repCom = map f
where f c = if c == ',' then ' ' else c

View file

@ -68,8 +68,6 @@ In the output values, how many times do digits 1, 4, 7, or 8 appear?
Your puzzle answer was 330.
The first half of this puzzle is complete! It provides one gold star: *
--- Part Two ---
Through a little deduction, you should now be able to determine the remaining digits. Consider again the first example above:
@ -120,4 +118,7 @@ Adding all of the output values in this larger example produces 61229.
For each entry, determine all of the wire/segment connections and decode the four-digit output values. What do you get if you add up all of the output values?
Your puzzle answer was 1010472.
Both parts of this puzzle are complete! They provide two gold stars: **

View file

@ -22,8 +22,6 @@ Find all of the low points on your heightmap. What is the sum of the risk levels
Your puzzle answer was 550.
The first half of this puzzle is complete! It provides one gold star: *
--- Part Two ---
Next, you need to find the largest basins so you know what areas are most important to avoid.
@ -62,3 +60,8 @@ The bottom-right basin, size 9:
Find the three largest basins and multiply their sizes together. In the above example, this is 9 * 14 * 9 = 1134.
What do you get if you multiply together the sizes of the three largest basins?
Your puzzle answer was 1100682.
Both parts of this puzzle are complete! They provide two gold stars: **

View file

@ -51,8 +51,6 @@ Find the first illegal character in each corrupted line of the navigation subsys
Your puzzle answer was 392043.
The first half of this puzzle is complete! It provides one gold star: *
--- Part Two ---
Now, discard the corrupted lines. The remaining lines are incomplete.
@ -90,3 +88,8 @@ The five lines' completion strings have total scores as follows:
Autocomplete tools are an odd bunch: the winner is found by sorting all of the scores and then taking the middle score. (There will always be an odd number of scores to consider.) In this example, the middle score is 288957 because there are the same number of scores smaller and larger than it.
Find the completion string for each incomplete line, score the completion strings, and sort the scores. What is the middle score?
Your puzzle answer was 1605968119.
Both parts of this puzzle are complete! They provide two gold stars: **

View file

@ -340,8 +340,3 @@ Your puzzle answer was 337.
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 [Share] this puzzle.

View file

@ -142,3 +142,4 @@ Given these new rules, how many paths through this cave system are there?
Your puzzle answer was 105453.
Both parts of this puzzle are complete! They provide two gold stars: **

View file

@ -3,25 +3,79 @@ module Main where
import Data.Char
import Data.List
import qualified Data.Map as M
import Debug.Trace
type Db = M.Map String Node
data Path =
Simple [String]
| Extra [String]
deriving Show
data Node = Node {
big :: Bool
, nbs :: [String]
} deriving Show
type Path = [String]
main :: IO ()
main = do
raw <- getContents
let input = mkDb $ map splitInp $ lines raw
let input = findPaths [ Simple ["start"] ] [] $ mkDb $ map splitInp $ lines raw
in do
putStrLn $ "day12a: " ++ (show $ solveA input)
putStrLn $ "day12b: " ++ (show $ solveB input)
solveA :: [Path] -> Int
solveA ps = length $ [ x | Simple x <- ps ]
solveB :: [Path] -> Int
solveB = length
findPaths :: [Path] -> [Path] -> Db -> [Path]
findPaths [] comp _ = comp
findPaths (k:ks) comp db =
if rec k == "end"
then findPaths ks (k:comp) db
else case k of
(Extra ps) -> go stepExtra ps
(Simple ps) -> go stepSimple ps
where
rec (Extra (k:_)) = k
rec (Simple (k:_)) = k
rec _ = error "empty path"
go f ps = findPaths ((f db ps) ++ ks) comp db
stepExtra :: Db -> [String] -> [Path]
stepExtra _ [] = error "empty list"
stepExtra db ps = map (Extra . (flip (:) ps)) (l (head ps) db)
where
isBig s = isUpper $ head s
l k db = filter (\n -> (n /= "start") && ((isBig n) || not (n `elem` ps))) $ nbs $ db M.! k
stepSimple :: Db -> [String] -> [Path]
stepSimple _ [] = error "empty list"
stepSimple db ps = map (\p -> (c (p:ps))) (l (head ps) db)
where
isBig s = isUpper $ head s
c ps = if isBig (head ps)
then Simple ps
else
let smalls = filter (not . isBig) ps
in if any (== (head smalls)) (tail smalls)
then Extra ps
else Simple ps
l k db = filter (/= "start") $ nbs $ db M.! k
-- io and parsing
splitInp :: String -> (String,String)
splitInp s = (\(a,b) -> (a, drop 1 b)) $ splitAt n s
where
n = findIn '-' s
findIn :: Char -> String -> Int
findIn c s = go 0 c s
where
go n c (s:ss) = if c == s then n else go (n+1) c ss
go n c [] = error "bad parse"
mkDb :: [(String,String)] -> Db
mkDb adjs = foldl f (M.fromList $ (map mkInitDb $ getUniques adjs)) adjs
where
@ -36,49 +90,3 @@ mkInitDb s = (,) s
getUniques :: [(String,String)] -> [String]
getUniques is = nub $ foldl (\t (a,b) -> (a:b:t)) [] is
findPaths :: (Db -> [String] -> [[String]]) -> [[String]] -> [[String]] -> Db -> [[String]]
findPaths f [] comp _ = comp
findPaths f (k:ks) comp db = findPaths f (ks ++ new) (nk comp) db
where
nk = if (head k) == "end"
then (k:)
else id
new = if (head k) /= "end"
then f db k
else []
nextSteps :: Db -> [String] -> [[String]]
nextSteps db me = filter f $ map (\n -> (n:me)) nobs
where
f ss = (isUpper $ (head . head) ss)
|| not (any (\n -> n == (head ss)) (tail ss))
nobs = (nbs $ db M.! (head me))
nextSteps' :: Db -> [String] -> [[String]]
nextSteps' db me = filter f $ map (\n -> (n:me)) nobs
where
f ss = (isUpper $ (head . head) ss)
|| length (g ss) == length (nub (g ss))+1
|| not (any (\n -> n == (head ss)) (tail ss))
nobs = filter (/= "start") (nbs $ db M.! (head me))
g ss = filter (\s -> not $ isUpper (head s)) ss
solveA :: Db -> Int
solveA db = length $ findPaths nextSteps [["start"]] [] db
solveB :: Db -> Int
solveB db = length $ findPaths nextSteps' [["start"]] [] db
-- io and parsing
splitInp :: String -> (String,String)
splitInp s = (\(a,b) -> (a, drop 1 b)) $ splitAt n s
where
n = findIn '-' s
findIn :: Char -> String -> Int
findIn c s = go 0 c s
where
go n c (s:ss) = if c == s then n else go (n+1) c ss
go n c [] = error "bad parse"

View file

@ -111,3 +111,4 @@ What code do you use to activate the infrared thermal imaging camera system?
Your puzzle answer was EPZGKCHU.
Both parts of this puzzle are complete! They provide two gold stars: **

View file

@ -1,6 +1,5 @@
module Main where
import Debug.Trace
import Data.List
import System.IO
@ -21,7 +20,7 @@ solveA :: [(Int,Int)] -> Fold -> Int
solveA dots f = length $ nub $ map (crease f) dots
solveB :: [(Int,Int)] -> [Fold] -> [String]
solveB dots fs = showPaper $ foldl (\d f -> map (crease f) d) dots fs
solveB dots folds = showPaper $ (foldl (\d f -> map (crease f) d)) dots folds
crease :: Fold -> (Int,Int) -> (Int,Int)
crease (Hori h) (x,y) =
@ -34,23 +33,21 @@ crease (Vert v) (x,y) =
else (x, (v-(y-v)))
parseFolds :: [String] -> [Fold]
parseFolds ss = map f ss
parseFolds = map f
where
g (d:'=':t) = (if d == 'y' then Vert else Hori) (read t)
f s = g (drop 11 s)
f = g . (drop 11)
parseDots :: [String] -> [(Int,Int)]
parseDots ss = map f ss
parseDots = map f
where
g (x:y:_) = ((read x), (read y))
f s = g $ words $ map (\c -> if c == ',' then ' ' else c) s
showPaper :: [(Int,Int)] -> [String]
showPaper db = mkPap
showPaper db = map (\y -> mkRow y) [0..mH]
where
mW = maximum $ map fst $ db
mH = maximum $ map snd $ db
f c = if c then '#' else ' '
f c = if c then '' else ' '
mkRow y = [ f $ (x,y) `elem` db | x <- [0..mW] ]
mkPap = map (\y -> mkRow y) [0..mH]

View file

@ -0,0 +1,62 @@
--- Day 14: Extended Polymerization ---
The incredible pressures at this depth are starting to put a strain on your submarine. The submarine has polymerization equipment that would produce suitable materials to reinforce the submarine, and the nearby volcanically-active caves should even have the necessary input elements in sufficient quantities.
The submarine manual contains instructions for finding the optimal polymer formula; specifically, it offers a polymer template and a list of pair insertion rules (your puzzle input). You just need to work out what polymer would result after repeating the pair insertion process a few times.
For example:
NNCB
CH -> B
HH -> N
CB -> H
NH -> C
HB -> C
HC -> B
HN -> C
NN -> C
BH -> H
NC -> B
NB -> B
BN -> B
BB -> N
BC -> B
CC -> N
CN -> C
The first line is the polymer template - this is the starting point of the process.
The following section defines the pair insertion rules. A rule like AB -> C means that when elements A and B are immediately adjacent, element C should be inserted between them. These insertions all happen simultaneously.
So, starting with the polymer template NNCB, the first step simultaneously considers all three pairs:
The first pair (NN) matches the rule NN -> C, so element C is inserted between the first N and the second N.
The second pair (NC) matches the rule NC -> B, so element B is inserted between the N and the C.
The third pair (CB) matches the rule CB -> H, so element H is inserted between the C and the B.
Note that these pairs overlap: the second element of one pair is the first element of the next pair. Also, because all pairs are considered simultaneously, inserted elements are not considered to be part of a pair until the next step.
After the first step of this process, the polymer becomes NCNBCHB.
Here are the results of a few steps using the above rules:
Template: NNCB
After step 1: NCNBCHB
After step 2: NBCCNBBBCBHCB
After step 3: NBBBCNCCNBBNBNBBCHBHHBCHB
After step 4: NBBNBNBBCCNBCNCCNBBNBBNBBBNBBNBBCBHCBHHNHCBBCBHCB
This polymer grows quickly. After step 5, it has length 97; After step 10, it has length 3073. After step 10, B occurs 1749 times, C occurs 298 times, H occurs 161 times, and N occurs 865 times; taking the quantity of the most common element (B, 1749) and subtracting the quantity of the least common element (H, 161) produces 1749 - 161 = 1588.
Apply 10 steps of pair insertion to the polymer template and find the most and least common elements in the result. What do you get if you take the quantity of the most common element and subtract the quantity of the least common element?
Your puzzle answer was 3143.
--- Part Two ---
The resulting polymer isn't nearly strong enough to reinforce the submarine. You'll need to run more steps of the pair insertion process; a total of 40 steps should do it.
In the above example, the most common element is B (occurring 2192039569602 times) and the least common element is H (occurring 3849876073 times); subtracting these produces 2188189693529.
Apply 40 steps of pair insertion to the polymer template and find the most and least common elements in the result. What do you get if you take the quantity of the most common element and subtract the quantity of the least common element?
Your puzzle answer was 4110215602456.
Both parts of this puzzle are complete! They provide two gold stars: **

102
code/src/14/14-input.txt Normal file
View file

@ -0,0 +1,102 @@
FSHBKOOPCFSFKONFNFBB
FO -> K
FF -> H
SN -> C
CC -> S
BB -> V
FK -> H
PC -> P
PH -> N
OB -> O
PV -> C
BH -> B
HO -> C
VF -> H
HB -> O
VO -> N
HK -> N
OF -> V
PF -> C
KS -> H
KV -> F
PO -> B
BF -> P
OO -> B
PS -> S
KC -> P
BV -> K
OC -> B
SH -> C
SF -> P
NH -> C
BS -> C
VH -> F
CH -> S
BC -> B
ON -> K
FH -> O
HN -> O
HS -> C
KK -> V
OK -> K
VC -> H
HV -> F
FS -> H
OV -> P
HF -> F
FB -> O
CK -> O
HP -> C
NN -> V
PP -> F
FC -> O
SK -> N
FN -> K
HH -> F
BP -> O
CP -> K
VV -> S
BO -> N
KN -> S
SB -> B
SC -> H
OS -> S
CF -> K
OP -> P
CO -> C
VK -> C
NB -> K
PB -> S
FV -> B
CS -> C
HC -> P
PK -> V
BK -> P
KF -> V
NS -> P
SO -> C
CV -> P
NP -> V
VB -> F
KO -> C
KP -> F
KH -> N
VN -> S
NO -> P
NF -> K
CB -> H
VS -> V
NK -> N
KB -> C
SV -> F
NC -> H
VP -> K
PN -> H
OH -> K
CN -> N
BN -> F
NV -> K
SP -> S
SS -> K
FP -> S

50
code/src/14/Main.hs Normal file
View file

@ -0,0 +1,50 @@
module Main where
import Data.List
import qualified Data.Map as M
import Data.Map.Strict (insertWith)
type Rules = M.Map (Char,Char) Char
type Polymer = M.Map (Char,Char) Integer
type Freqs = M.Map Char Integer
main :: IO ()
main = do
raw <- getContents
let input = parseMatches $ drop 2 $ lines raw
init = parsePolymer $ head $ lines raw
putStrLn $ "day14a: " ++ (show $ solveA input init)
putStrLn $ "day14b: " ++ (show $ solveB input init)
solveA :: Rules -> Polymer -> Integer
solveA = solve 10
solveB :: Rules -> Polymer -> Integer
solveB = solve 40
solve :: Int -> Rules -> Polymer -> Integer
solve n rs p = (maximum nums) - (minimum nums)
where
nums = M.elems $ getFreqs $ (iterate (step rs) p) !! n
step :: Rules -> Polymer -> Polymer
step rs p = foldr ($) M.empty $ map f $ M.toList p
where
f ((a,b),i) = let c = rs M.! (a,b)
in (insertWith (+) (a,c) i) . (insertWith (+) (c,b) i)
getFreqs :: Polymer -> Freqs
getFreqs p = M.map (\x -> (x+1) `div` 2) $ foldr ($) M.empty $ map f $ M.toList p
where
f ((a,b),i) = (insertWith (+) a i) . (insertWith (+) b i)
parsePolymer :: String -> Polymer
parsePolymer s = foldr f M.empty $ pairs s
where
pairs s = zip s (tail s)
f p = M.insertWith (+) p 1
parseMatches :: [String] -> Rules
parseMatches ss = M.fromList $ map f ss
where
f s = ((s !! 0, s !! 1), s !! 6)

View file

@ -0,0 +1,159 @@
--- Day 15: Chiton ---
You've almost reached the exit of the cave, but the walls are getting closer together. Your submarine can barely still fit, though; the main problem is that the walls of the cave are covered in chitons, and it would be best not to bump any of them.
The cavern is large, but has a very low ceiling, restricting your motion to two dimensions. The shape of the cavern resembles a square; a quick scan of chiton density produces a map of risk level throughout the cave (your puzzle input). For example:
1163751742
1381373672
2136511328
3694931569
7463417111
1319128137
1359912421
3125421639
1293138521
2311944581
You start in the top left position, your destination is the bottom right position, and you cannot move diagonally. The number at each position is its risk level; to determine the total risk of an entire path, add up the risk levels of each position you enter (that is, don't count the risk level of your starting position unless you enter it; leaving it adds no risk to your total).
Your goal is to find a path with the lowest total risk. In this example, a path with the lowest total risk is highlighted here:
1163751742
1381373672
2136511328
3694931569
7463417111
1319128137
1359912421
3125421639
1293138521
2311944581
The total risk of this path is 40 (the starting position is never entered, so its risk is not counted).
What is the lowest total risk of any path from the top left to the bottom right?
Your puzzle answer was 741.
--- Part Two ---
Now that you know how to find low-risk paths in the cave, you can try to find your way out.
The entire cave is actually five times larger in both dimensions than you thought; the area you originally scanned is just one tile in a 5x5 tile area that forms the full map. Your original map tile repeats to the right and downward; each time the tile repeats to the right or downward, all of its risk levels are 1 higher than the tile immediately up or left of it. However, risk levels above 9 wrap back around to 1. So, if your original map had some position with a risk level of 8, then that same position on each of the 25 total tiles would be as follows:
8 9 1 2 3
9 1 2 3 4
1 2 3 4 5
2 3 4 5 6
3 4 5 6 7
Each single digit above corresponds to the example position with a value of 8 on the top-left tile. Because the full map is actually five times larger in both dimensions, that position appears a total of 25 times, once in each duplicated tile, with the values shown above.
Here is the full five-times-as-large version of the first example above, with the original map in the top left corner highlighted:
11637517422274862853338597396444961841755517295286
13813736722492484783351359589446246169155735727126
21365113283247622439435873354154698446526571955763
36949315694715142671582625378269373648937148475914
74634171118574528222968563933317967414442817852555
13191281372421239248353234135946434524615754563572
13599124212461123532357223464346833457545794456865
31254216394236532741534764385264587549637569865174
12931385212314249632342535174345364628545647573965
23119445813422155692453326671356443778246755488935
22748628533385973964449618417555172952866628316397
24924847833513595894462461691557357271266846838237
32476224394358733541546984465265719557637682166874
47151426715826253782693736489371484759148259586125
85745282229685639333179674144428178525553928963666
24212392483532341359464345246157545635726865674683
24611235323572234643468334575457944568656815567976
42365327415347643852645875496375698651748671976285
23142496323425351743453646285456475739656758684176
34221556924533266713564437782467554889357866599146
33859739644496184175551729528666283163977739427418
35135958944624616915573572712668468382377957949348
43587335415469844652657195576376821668748793277985
58262537826937364893714847591482595861259361697236
96856393331796741444281785255539289636664139174777
35323413594643452461575456357268656746837976785794
35722346434683345754579445686568155679767926678187
53476438526458754963756986517486719762859782187396
34253517434536462854564757396567586841767869795287
45332667135644377824675548893578665991468977611257
44961841755517295286662831639777394274188841538529
46246169155735727126684683823779579493488168151459
54698446526571955763768216687487932779859814388196
69373648937148475914825958612593616972361472718347
17967414442817852555392896366641391747775241285888
46434524615754563572686567468379767857948187896815
46833457545794456865681556797679266781878137789298
64587549637569865174867197628597821873961893298417
45364628545647573965675868417678697952878971816398
56443778246755488935786659914689776112579188722368
55172952866628316397773942741888415385299952649631
57357271266846838237795794934881681514599279262561
65719557637682166874879327798598143881961925499217
71484759148259586125936169723614727183472583829458
28178525553928963666413917477752412858886352396999
57545635726865674683797678579481878968159298917926
57944568656815567976792667818781377892989248891319
75698651748671976285978218739618932984172914319528
56475739656758684176786979528789718163989182927419
67554889357866599146897761125791887223681299833479
Equipped with the full map, you can now find a path from the top left corner to the bottom right corner with the lowest total risk:
11637517422274862853338597396444961841755517295286
13813736722492484783351359589446246169155735727126
21365113283247622439435873354154698446526571955763
36949315694715142671582625378269373648937148475914
74634171118574528222968563933317967414442817852555
13191281372421239248353234135946434524615754563572
13599124212461123532357223464346833457545794456865
31254216394236532741534764385264587549637569865174
12931385212314249632342535174345364628545647573965
23119445813422155692453326671356443778246755488935
22748628533385973964449618417555172952866628316397
24924847833513595894462461691557357271266846838237
32476224394358733541546984465265719557637682166874
47151426715826253782693736489371484759148259586125
85745282229685639333179674144428178525553928963666
24212392483532341359464345246157545635726865674683
24611235323572234643468334575457944568656815567976
42365327415347643852645875496375698651748671976285
23142496323425351743453646285456475739656758684176
34221556924533266713564437782467554889357866599146
33859739644496184175551729528666283163977739427418
35135958944624616915573572712668468382377957949348
43587335415469844652657195576376821668748793277985
58262537826937364893714847591482595861259361697236
96856393331796741444281785255539289636664139174777
35323413594643452461575456357268656746837976785794
35722346434683345754579445686568155679767926678187
53476438526458754963756986517486719762859782187396
34253517434536462854564757396567586841767869795287
45332667135644377824675548893578665991468977611257
44961841755517295286662831639777394274188841538529
46246169155735727126684683823779579493488168151459
54698446526571955763768216687487932779859814388196
69373648937148475914825958612593616972361472718347
17967414442817852555392896366641391747775241285888
46434524615754563572686567468379767857948187896815
46833457545794456865681556797679266781878137789298
64587549637569865174867197628597821873961893298417
45364628545647573965675868417678697952878971816398
56443778246755488935786659914689776112579188722368
55172952866628316397773942741888415385299952649631
57357271266846838237795794934881681514599279262561
65719557637682166874879327798598143881961925499217
71484759148259586125936169723614727183472583829458
28178525553928963666413917477752412858886352396999
57545635726865674683797678579481878968159298917926
57944568656815567976792667818781377892989248891319
75698651748671976285978218739618932984172914319528
56475739656758684176786979528789718163989182927419
67554889357866599146897761125791887223681299833479
The total risk of this path is 315 (the starting position is still never entered, so its risk is not counted).
Using the full map, what is the lowest total risk of any path from the top left to the bottom right?
Your puzzle answer was 2976.
Both parts of this puzzle are complete! They provide two gold stars: **

100
code/src/15/15-input.txt Normal file
View file

@ -0,0 +1,100 @@
9197799967142949711924912559857266425989892895795349989935678852856491866597249883454355721838994689
9454699428952977916248797687374199797579937166959985575934687799286278395799834599823725191768264239
1476124567678962892998242114658368169969196949893799969968932492875835669928535888516585889557294857
5791918239996678837798182119995286749674958736799996579937942199999478117296491681956799173479469697
7169635399716469741872348399984999149999916841724586589959931149912818998567241788593818767699883858
2926741911914636315187918554497249439756557979631699768168949899866796175449994999986688215771687939
5589949979145888769995885998892975199254611397986145389381187633664799879995799643887357299151772988
8889465966717911191788336792214278123584765871499472917878297279329199386164989887784939824172612679
4449128566587999796639991816798948898951855942998816126957898821255977428897977658516999988855449929
3999895395663995233116579986688778269699389615982998939659193247918999668975597863299499276267179878
9989933899158995519999896763539929676935591584991626616943495964888658981438483529376937899999918183
4829998579654495951971971638691618176277519996856988429168266495831212992486396955413697829886599968
1853513748489779798696199795337967571689486839899518982881879699995999878971985995885285319954968987
3342299981292915486979299839195993258148889649679616595927478298168379999445161915519894982439638946
5741832898766672398489974989541186971799425919242686599739939448731546446299879192192895526548848951
3898679419518979696926476691872981828746218226918199699898828285487879261678997791767663979571336987
4545997398729587476481757668995896459799851954917678912468571968713532133518634849896488769111976969
7176919181998999666976198114775775798299797193972885999975499799991922929283534929891716288936629899
9795297985299599814789928888579191456982553599491674489819963299121598519964298979361694995981918669
5647159999798466469859785261859791688182892567989542289667144152647594189396864175439725912999894891
6854155179889746985993265989674997919485741213772961693991919182852979468522779889946746945979139453
6849999911316858193858699583834199555997997298798955876892868311369313778113995754199257992891592559
1988966163847446296579892411648896918797968187847519149178391233772828798998561969939976192876594877
7445186982744995399469915773579589785637114845746289739271566921956439346833864949599959561392652394
3457499487895199558673758745718298693289788928968598234991939776753988979879884594869769919728168682
6996592996822655364687387657828999681917991869422948671996356522399889425477419816794863249587691838
6963522693998786991158579735619989997779699892985724296997797588989857395266828998498892969725581196
9859966989665161194892178862589775985492499749698891478876986292862589878985699921967994865598972548
1951799998898999888869856412883984488695132895819836992634797721986196995697288654968728619832457546
7746279941985434489778669988695998998439885687679569278711958998865855737897118129117847196853321494
9957647198999793952568873984933619771962796482459488211592975286761921259894198995991177799599947499
5957899335983477859964986862162667699875586266873467199919735154293718617894984899199896937396169696
4896218869754451981289699181969462479929965399769819937374193998929686992335854771796763991919183598
7963369964836263326663688188689148549887888951793951217896899686213646979917379984981861249989999549
5651487588851599919775191184948759985836569954819197496898639599422949846969583849582827172889781259
9235786148996892968113972727222986857799699985848999699389987299798673597919859879142818978191972699
6268697925898964971528988971776886593959277157692478749421918568187987285285135794835198267899129444
9613855792729968968874877878798998856696549799999913939938579165969969665999919899989935397982894528
4997991949899429999159159577397714989959998878621218913971667491519691231899789262795929815768874159
9965848836163359381441957989236819923219977614754398952174759999868197879998492826999779999614619568
9916479998414596768939496337988287974996399692819868258768657938573834799119189969847332997799632969
5698447299748197429895187981999374113864719439577495356699467714279996684998225889418687785989668887
9688999296549647577489651538861651536198886343717392492893999157912496817872939573767915879229444698
7945998891978892984213828992819989424969949768551929992192128218217979514375299388969726393999499369
3584919181979999899979852691745679631417252595865981248933848728931198122729313884939499699196979282
8858721793437795394466977529919919969898771537432681496711998968886579589984829981259798525932187987
9588959797973868917749898922898847727866979662399888886799981719567732464855989797669812177692858535
7988797967989166987697149888751549873389785967924498738998179527778487979748999358518578993477944998
8392255427879688981984196873699686714549989266862782196183895285962499989186484692151849999723391279
8437165279966699964797868697998719161124994112294916994518516866198924776139989889587889979986973818
9999579881886267995145198999799886398912847997191746855988699599911799599898975959729735998989189975
8878929798597768927495551149914988384939936997932243691336699915979516239489822517874899851799315136
7999937717928948478557923788987292447971689615966385935897391982999178899753365199984698878762193326
8739178873349956119674999899899922517642862785199198189839768689799987895289957563983787873796927158
3817196699929999634811599428583198399931978688187175989163313588911897784917986562919151677117114699
5998827143845268748266989727984179597967556224858671494997248677843425189898194987624713779882979969
1291199757967569999681279489899999698569168979799631778127984994974999291683887763915481598891197984
6596739399885895975872877952961612873986668999381529399939575996779494715118543849969191539989723991
6488878279986978392869749226828917999488959898183448591336188881881342378769238973895889159556799994
7789977876961783236719451481787118498693824114361919936786189899181887229316982176859199279192424145
8187849893991985235499899257668519419992986629984899637874749832449368983739929946889995497697325581
1999982976844663788727661849815985519275791155239799816978282652839694868889597292189945989632996979
5996994949412446932824171982727298987629311193781981698399298991594594318144966895296816539941754949
4499757999646423149686819991849992649795216851367986996698575817689371687185996929563284536999154386
2781727997917211978984917918358938837999218781629649869594796149935179779682659626959939761694881741
9699391853588289298623919874976619984895139963999399988216318999974869174298698357691152898189998496
4692148898295579969948321265945989989678928997293841391798864427891761873993391876712881438989147999
9385356844999749799945931891327611796839596933696939993396192727919575919518191178749822279279367589
4178987198748999878181711949999695619267692321571299944319696913971989366952788997529689965967283949
9956943168197988495985856862549149864798959861938533689969366917899972839492619882179391815935536891
9994859897582628653476292984929998647975796929748931992994879889878464879929465595995992499919947572
6499868699811766722988787191388665966891869899747691981279799666949896666275972998579926239169811939
2572961395969294529184998258989427519999852294469971796436995767291982749996658711449539791567874971
9499369277479918778697894247918649998897952638574461819998871478917181981936547491991768414982337918
9139161883819343891979967499192937131885599318821172899173915229917976858689192989939199991289159588
4587788966993732467999991118887435975882488728997989199779497777813778259387411882768829389897869948
6997871988679928999697816865977788699836897997854449113119982463997827969671859996988242232984999889
7669989748189979988148659979989987372886949695793489235995874977587946688195985837946785781783754816
9949977989988894882969918629379321181514166935688979461975779949979998632331698911979279798659979815
5739999517928987777759268697378941991838969832887199538988396198131293696546792877869527666136992871
6911198997889976167798919887987969916181719673692949986396122688692969199128693334898362117657497517
9883388858893695671398924917987816149792972888297996689846999676959672799729896341199962982814179963
1987996499791423676141938518943291126997238886492375594975195733297999897928779997671984971349299794
9797999699795947998399566993717699681855989845386398419161478733246296117437796411784118959196917998
8918619981898886893637776664327129356976966478348969779281122928599816797994927899617318362459879958
9971138998498917194898897279183767784951818668325759559698816239496896576197991168919876998549693617
8864749334257944937895657676795539372789673639872688475887819638876957529359787979549486769488261586
5675561487189788698114476929665946299225219355166913169787589274369169599695999791361786439583994855
9999956599855466924168799196849941988317721987382287618899839584541991357959855181948139679757198596
9298494784765969999565792229687116986883978789756616279977893754489916919955299588991939854273184891
1996653993894556999967399479699996198846899917783471221742335181981132427871897521999889788298436396
9758778754778989199415992499539647886721912925345489999475288846844991977933449238525898929369479361
3799665999998683118595895926116918889199463219817924394877958956698592828621676399199495183592857893
5747926316986915679999389948959192389893246767655852888242899482429279815191681819582769989759282619
8557944289929978419989549449497998796197294159289979966862799744989186832759979889797777669569898889
8887698917197579219988794948269467999589319398686198699795225872219199592696935791919185797715588919
1498696799724916519515862974893197748928697249299992999324589578163647988841492955996651937876156824
8213962617983488919185253728699798941119614245999164229898897586922898965749999199113889146668885849
9547881767999183972817991938941799195699921244999582934834983168189915191587942659337539518189911869
9958877559791958745797981284916899539983986257869698291725831953753946984998659154999916977712958828

134
code/src/15/Main.hs Normal file
View file

@ -0,0 +1,134 @@
module Main where
-- to do - do a more efficient djikstras impl
import qualified Data.PSQueue as P
import Debug.Trace
import Data.List
import qualified Data.Map as M
import Data.Map.Strict (insertWith)
type Point = (Int,Int)
type Graph = M.Map Point Vertex
type Queue = M.Map Point QueueNode
type PQ = P.PSQ Point Int
data QueueNode = QueueNode
{ qDist :: Int
, qParent :: Maybe Point
, qProc :: Bool
} deriving Show
data Vertex = Vertex
{ vKey :: Point
, vWeight :: Int
, vAdjs :: [Point]
} deriving Show
main :: IO ()
main = do
raw <- getContents
let input = map (map (read . (:[]))) $ lines raw
vl = mkValList input
vl2 = mkValList $ extendList input
end s = (,) (((length (head input))*s) - 1) (((length input)*s) - 1)
putStrLn $ "day15a: " ++ (show $ solveA vl $ (end 1))
putStrLn $ "day15b: " ++ (show $ solveB vl2 $ (end 5))
solveA :: Graph -> Point -> Int
solveA g end = findWeight g end
solveB :: Graph -> Point -> Int
solveB = solveA
showPath :: Queue -> Point -> [Point]
showPath q p
| p == (0,0) = [(0,0)]
| otherwise = case qParent (q M.! p) of
Nothing -> []
Just k -> (p:(showPath q k))
findWeight :: Graph -> Point -> Int
findWeight g end = tracePath end q
where
(_,q) = dijk (0,0) end initQueue g (P.singleton (0,0) 0)
initQueue :: Queue
initQueue = M.singleton (0,0) $ QueueNode 0 Nothing False
tracePath :: Point -> Queue -> Int
tracePath c q = qDist (q M.! c)
getMin :: PQ -> (Point,PQ)
getMin pq = case P.minView pq of
Nothing -> error "empty pq"
Just ((k P.:-> _), pq') -> (k,pq')
dijk :: Point -> Point -> Queue -> Graph -> PQ -> (Point,Queue)
dijk start end q g pq
| P.null pq = error "no path found"
| otherwise =
let (k,pq') = getMin pq
in if qProc (q M.! k)
then dijk start end q g pq'
else if k == end
then (k,q)
else let
as = vAdjs (g M.! k)
q' = updateQ k q g
in dijk start end q' g (addAdjs q' as pq')
updateQ :: Point -> Queue -> Graph -> Queue
updateQ p q g = foldr ($) q $ (h:(map f as))
where
h = M.adjust (\o -> o { qProc = True }) p
as = vAdjs (g M.! p)
f a = let l = qDist (q M.! p)
d = l + (vWeight $ g M.! a)
in if betterRoute d a q
then insertWith
(\o n -> n { qProc = qProc o })
a
(QueueNode { qParent = Just p, qDist = d, qProc = False})
else id
betterRoute :: Int -> Point -> Queue -> Bool
betterRoute d k q =
if not (M.member k q)
then True
else d < (qDist (q M.! k))
addAdjs :: Queue -> [Point] -> PQ -> PQ
addAdjs _ [] pq = pq
addAdjs q (a:as) pq = addAdjs q as (P.insert a (qDist (q M.! a)) pq)
-- io stuff
modWeight :: Int -> Int
modWeight n = if n >= 9 then modWeight (n-9) else n+1
extendList :: [[Int]] -> [[Int]]
extendList rs = concat $ take 5 $ iterate (map (map modWeight)) $ map extend rs
extend :: [Int] -> [Int]
extend cs = concat $ take 5 $ iterate (map modWeight) cs
mkValList :: [[Int]] -> Graph
mkValList [] = M.empty
mkValList raw =
(M.fromList . concat)
$ map (\(y, vs) ->
map (\(x, v) ->
((x,y), (Vertex (x,y) v (mkDeltas w h (x,y)))))
$ zip [0.. ] vs)
$ zip [0..] $ raw
where
w = length (head raw)
h = length raw
mkDeltas :: Int -> Int -> (Int,Int) -> [(Int,Int)]
mkDeltas w h (x,y) = filter
(\(i,j) -> (i >= 0 && i < w && j >= 0 && j < h))
[ (i,j) | i <- [(x-1) .. (x+1)]
, j <- [(y-1) .. (y+1)]
, (i == x || j == y)]

53
timings.txt Normal file
View file

@ -0,0 +1,53 @@
# all performed on my Thinkpad T420
day1a: 1832
day1b: 1858
./result/bin/aoc2021 $f 0.01s user 0.00s system 111% cpu 0.013 total
day2a: 1698735
day2b: 1594785890
./result/bin/aoc2021 $f 0.01s user 0.00s system 117% cpu 0.011 total
day3a: 4160394
day3b: 4125600
./result/bin/aoc2021 $f 0.01s user 0.00s system 113% cpu 0.012 total
day4a: 45031
day4b: 2568
./result/bin/aoc2021 $f 0.05s user 0.01s system 103% cpu 0.049 total
day5a: 5690
day5b: 17741
./result/bin/aoc2021 $f 0.27s user 0.02s system 100% cpu 0.298 total
day6a: 395627
day6b: 1767323539209
./result/bin/aoc2021 $f 0.00s user 0.00s system 121% cpu 0.007 total
day7a: 344735
day7b: 96798233
./result/bin/aoc2021 $f 0.01s user 0.00s system 114% cpu 0.011 total
day8a: 330
day8b: 1010472
./result/bin/aoc2021 $f 0.02s user 0.00s system 107% cpu 0.020 total
day9a: 550
day9b: 1100682
./result/bin/aoc2021 $f 0.09s user 0.01s system 101% cpu 0.096 total
day10a: 392043
day10b: 1605968119
./result/bin/aoc2021 $f 0.01s user 0.00s system 121% cpu 0.008 total
day11a: 1655
day11b: 337
./result/bin/aoc2021 $f 0.11s user 0.01s system 101% cpu 0.120 total
day12a: 3563
day12b: 105453
./result/bin/aoc2021 $f 0.28s user 0.02s system 100% cpu 0.291 total
day13a: 837
day13b:
▉▉▉▉ ▉▉▉ ▉▉▉▉ ▉▉ ▉ ▉ ▉▉ ▉ ▉ ▉ ▉
▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉
▉▉▉ ▉ ▉ ▉ ▉ ▉▉ ▉ ▉▉▉▉ ▉ ▉
▉ ▉▉▉ ▉ ▉ ▉▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉
▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉ ▉
▉▉▉▉ ▉ ▉▉▉▉ ▉▉▉ ▉ ▉ ▉▉ ▉ ▉ ▉▉
./result/bin/aoc2021 $f 0.02s user 0.01s system 106% cpu 0.026 total
day14a: 3143
day14b: 4110215602456
./result/bin/aoc2021 $f 0.01s user 0.00s system 119% cpu 0.008 total
day15a: 741
day15b: 2976
./result/bin/aoc2021 $f 8.24s user 0.19s system 99% cpu 8.431 total