Small refactoring

This commit is contained in:
daniele 2024-12-21 20:03:24 +01:00
parent a42f7bbbe1
commit 0e0442b9d9
Signed by: fuxino
GPG Key ID: 981A2B2A3BBF5514
9 changed files with 92 additions and 67 deletions

View File

@ -17,18 +17,22 @@ similarityScore xs ys =
let elemsY = [(fst . fromJust $ uncons y, length y) | y <- (group . sort) ys]
in sum [x * snd y | x <- xs, y <- elemsY, x == fst y]
day01_1 :: IO ()
day01_1 = do
parseInput :: IO [[Int]]
parseInput = do
contents <- lines <$> readFile "input/day1.txt"
let [x, y] = transpose $ map read . words <$> contents
return [x, y]
day01_1 :: IO ()
day01_1 = do
[x, y] <- parseInput
putStrLn $
"Day 1, Puzzle 1 solution: "
++ show (listDistance x y)
day01_2 :: IO ()
day01_2 = do
contents <- lines <$> readFile "input/day1.txt"
let [x, y] = transpose $ map read . words <$> contents
[x, y] <- parseInput
putStrLn $
"Day 1, Puzzle 2 solution: "
++ show (similarityScore x y)

View File

@ -20,18 +20,22 @@ removeLevel xs = filter (\x -> length x == l) $ filterM (const [True, False]) xs
where
l = length xs - 1
day02_1 :: IO ()
day02_1 = do
parseInput :: IO [[Int]]
parseInput = do
contents <- lines <$> readFile "input/day2.txt"
let reports = map read . words <$> contents
return reports
day02_1 :: IO ()
day02_1 = do
reports <- parseInput
putStrLn $
"Day 2, Puzzle 1 solution: "
++ show (length $ filter isSafe reports)
day02_2 :: IO ()
day02_2 = do
contents <- lines <$> readFile "input/day2.txt"
let reports = map read . words <$> contents
reports <- parseInput
putStrLn $
"Day 2, Puzzle 2 solution: "
++ show (length . filter (any isSafe) $ map removeLevel reports)

View File

@ -103,33 +103,30 @@ setGridObstacles startPosition grid =
let positions = [(x, y) | x <- [0 .. (length grid - 1)], y <- [0 .. (length (fst . fromJust $ uncons grid) - 1)], (x, y) /= startPosition, getGridVal (x, y) grid == 'X']
in zipWith (`markVisited` '#') positions (replicate (length positions) grid)
day06_1 :: IO ()
day06_1 = do
parseInput :: IO (Int, Int, Direction, [String])
parseInput = do
contents <- lines <$> readFile "input/day6.txt"
let (x, y) =
(\a b c d -> fst . fromJust $ uncons $ filter ((>= 0) . fst) [a, b, c, d])
(\a b c d -> fst . fromJust . uncons $ filter ((>= 0) . fst) [a, b, c, d])
<$> getStartPosition 'v'
<*> getStartPosition '^'
<*> getStartPosition '<'
<*> getStartPosition '>'
$ contents
direction = fromJust . getDirection $ (contents !! x) !! y
return (x, y, direction, contents)
day06_1 :: IO ()
day06_1 = do
(x, y, direction, grid) <- parseInput
putStrLn $
"Day 6, Puzzle 1 solution: "
++ show (1 + (length . concatMap (filter (== 'X')) $ visitGrid (x, y) direction contents))
++ show (1 + (length . concatMap (filter (== 'X')) $ visitGrid (x, y) direction grid))
day06_2 :: IO ()
day06_2 = do
contents <- lines <$> readFile "input/day6.txt"
let (x, y) =
(\a b c d -> fst . fromJust $ uncons $ filter ((>= 0) . fst) [a, b, c, d])
<$> getStartPosition 'v'
<*> getStartPosition '^'
<*> getStartPosition '<'
<*> getStartPosition '>'
$ contents
direction = fromJust . getDirection $ (contents !! x) !! y
grid = visitGrid (x, y) direction contents
(x, y, direction, initialGrid) <- parseInput
let grid = visitGrid (x, y) direction initialGrid
gridObstacles = setGridObstacles (x, y) grid
loops = filter (checkGridLoop (x, y) direction) gridObstacles
putStrLn $ "Day 6, Puzzle 2 solution: " ++ show (length loops)

View File

@ -35,22 +35,24 @@ isSolvable' cur (result, x : y : ys) =
|| isSolvable' ((cur `concatInt` x) * y) (result, ys)
|| isSolvable' ((cur `concatInt` x) `concatInt` y) (result, ys)
day07_1 :: IO ()
day07_1 = do
parseInput :: IO [(Int, [Int])]
parseInput = do
[x, y] <- transpose . map (splitOn ":") . lines <$> readFile "input/day7.txt"
let results = map read x
values = map read <$> map words y
equations = zip results values
return equations
day07_1 :: IO ()
day07_1 = do
equations <- parseInput
putStrLn $
"Day 7, Puzzle 1 solution: "
++ show (sum . map fst $ filter (isSolvable 0) equations)
day07_2 :: IO ()
day07_2 = do
[x, y] <- transpose . map (splitOn ":") . lines <$> readFile "input/day7.txt"
let results = map read x
values = map read <$> map words y
equations = zip results values
equations <- parseInput
putStrLn $
"Day 7, Puzzle 2 solution: "
++ show (sum . map fst $ filter (isSolvable' 0) equations)

View File

@ -61,20 +61,22 @@ getAntinodes' a b maxX maxY =
++ takeWhile (\c -> isInside c maxX maxY) (generateCoords (coordinates a) (distX, distY))
++ takeWhile (\c -> isInside c maxX maxY) (generateCoords (coordinates b) (-distX, -distY))
day08_1 :: IO ()
day08_1 = do
parseInput :: IO (Int, Int, [Antenna])
parseInput = do
contents <- lines <$> readFile "input/day8.txt"
let antennas = getAntennas contents
x = length contents
y = length $ fst . fromJust $ uncons contents
antinodes = fromList $ concat [getAntinodes a b x y | a <- antennas, b <- antennas, a /= b, frequency a == frequency b]
return (x, y, antennas)
day08_1 :: IO ()
day08_1 = do
(x, y, antennas) <- parseInput
let antinodes = fromList $ concat [getAntinodes a b x y | a <- antennas, b <- antennas, a /= b, frequency a == frequency b]
putStrLn $ "Day 8, Puzzle 1 solution: " ++ show (length antinodes)
day08_2 :: IO ()
day08_2 = do
contents <- lines <$> readFile "input/day8.txt"
let antennas = getAntennas contents
x = length contents
y = length $ fst . fromJust $ uncons contents
antinodes = fromList $ concat [getAntinodes' a b x y | a <- antennas, b <- antennas, a /= b, frequency a == frequency b]
(x, y, antennas) <- parseInput
let antinodes = fromList $ concat [getAntinodes' a b x y | a <- antennas, b <- antennas, a /= b, frequency a == frequency b]
putStrLn $ "Day 8, Puzzle 2 solution: " ++ show (length antinodes)

View File

@ -22,21 +22,28 @@ findAllPaths graph start end path = do
then return path'
else findAllPaths graph node end path'
day10_1 :: IO ()
day10_1 = do
parseInput :: IO (A.Array (Int, Int) Int)
parseInput = do
contents <- lines <$> readFile "input/day10.txt"
let trailMap = A.listArray ((0, 0), (52, 52)) $ map digitToInt $ concat contents
trailGraph = Graph {edges = M.fromList [(k, adjacent trailMap k (52, 52)) | k <- A.indices trailMap]}
let trailMap = A.listArray ((0, 0), (52, 52)) . map digitToInt $ concat contents
return trailMap
getTrailGraph :: A.Array Coords Int -> (Graph Coords, [Coords], [Coords])
getTrailGraph trailMap =
let trailGraph = Graph {edges = M.fromList [(k, adjacent trailMap k (52, 52)) | k <- A.indices trailMap]}
startList = map fst . filter (\(_, y) -> y == 0) $ A.assocs trailMap
endList = map fst . filter (\(_, y) -> y == 9) $ A.assocs trailMap
in (trailGraph, startList, endList)
day10_1 :: IO ()
day10_1 = do
trailMap <- parseInput
let (trailGraph, startList, endList) = getTrailGraph trailMap
putStrLn $ "Day 10, Puzzle 1 solution: " ++ show (length $ filter (not . null) [findAllPaths trailGraph x y [x] | x <- startList, y <- endList])
day10_2 :: IO ()
day10_2 = do
contents <- lines <$> readFile "input/day10.txt"
let trailMap = A.listArray ((0, 0), (52, 52)) $ map digitToInt $ concat contents
trailGraph = Graph {edges = M.fromList [(k, adjacent trailMap k (52, 52)) | k <- A.indices trailMap]}
startList = map fst . filter (\(_, y) -> y == 0) $ A.assocs trailMap
endList = map fst . filter (\(_, y) -> y == 9) $ A.assocs trailMap
trailMap <- parseInput
let (trailGraph, startList, endList) = getTrailGraph trailMap
paths = concat $ filter (not . null) [findAllPaths trailGraph x y [x] | x <- startList, y <- endList]
putStrLn $ "Day 10, Puzzle 2 solution: " ++ show (length paths)

View File

@ -62,11 +62,16 @@ findChristmasTree n rs =
then n
else findChristmasTree (n + 1) rs'
day14_1 :: IO ()
day14_1 = do
parseInput :: IO [Robot]
parseInput = do
contents <- lines <$> readFile "input/day14.txt"
let robots = map readRobot contents
robots' = map (moveRobot 100) robots
return robots
day14_1 :: IO ()
day14_1 = do
robots <- parseInput
let robots' = map (moveRobot 100) robots
firstQ = length $ filter (\r -> quadrant r == 0) robots'
secondQ = length $ filter (\r -> quadrant r == 1) robots'
thirdQ = length $ filter (\r -> quadrant r == 2) robots'
@ -77,8 +82,7 @@ day14_1 = do
day14_2 :: IO ()
day14_2 = do
contents <- lines <$> readFile "input/day14.txt"
let robots = map readRobot contents
robots <- parseInput
putStrLn $
"Day 14, Puzzle 2 solution: "
++ show (findChristmasTree 1 robots)

View File

@ -121,23 +121,25 @@ checkIfCreatesCopy c =
let o = map read . filter (not . null) . splitOn "," . output $ execState runProgram c
in o == program c
day17_1 :: IO ()
day17_1 = do
parseInput :: IO ([Integer], [Int])
parseInput = do
contents <- lines <$> readFile "input/day17.txt"
let [r, [p]] = splitOn [""] contents
registers = map (read . filter isDigit) r
prog = map (read . filter isDigit) $ splitOn "," p
computer = Computer {registerA = fst . fromJust $ uncons registers, registerB = registers !! 1, registerC = registers !! 2, pointer = 0, program = prog, output = ""}
return (registers, prog)
day17_1 :: IO ()
day17_1 = do
(registers, prog) <- parseInput
let computer = Computer {registerA = fst . fromJust $ uncons registers, registerB = registers !! 1, registerC = registers !! 2, pointer = 0, program = prog, output = ""}
putStr "Day 17, Puzzle 1 solution: "
print . drop 1 . output $ execState runProgram computer
day17_2 :: IO ()
day17_2 = do
contents <- lines <$> readFile "input/day17.txt"
let [r, [p]] = splitOn [""] contents
registers = map (read . filter isDigit) r
prog = map (read . filter isDigit) $ splitOn "," p
computer = Computer {registerA = 0, registerB = registers !! 1, registerC = registers !! 2, pointer = 0, program = prog, output = ""}
(registers, prog) <- parseInput
let computer = Computer {registerA = 0, registerB = registers !! 1, registerC = registers !! 2, pointer = 0, program = prog, output = ""}
regA = [805464 * 2 ^ 27 ..] -- Threshold derived empirically, a better threshold must be possible because this is very slow, but got the correct answer.
putStrLn $
"Day 17, Puzzle 2 solution: "

View File

@ -27,20 +27,23 @@ findFirstBlocker memory (c : cs) start end =
then c
else findFirstBlocker memory' cs start end
getCorruptedMemoryMap :: [[String]] -> A.Array Coords Char
getCorruptedMemoryMap fallingBytes =
let memory = A.listArray ((0, 0), (70, 70)) $ replicate 5041 '.'
bytesCoords = take 1024 [(read x, read y) | (x : y : _) <- fallingBytes]
corruptedMemory = corruptMemory memory bytesCoords
in corruptedMemory
day18_1 :: IO ()
day18_1 = do
contents <- map (splitOn ",") . lines <$> readFile "input/day18.txt"
let memory = A.listArray ((0, 0), (70, 70)) $ replicate 5041 '.'
coords = take 1024 [(read x, read y) | (x : y : _) <- contents]
memory' = corruptMemory memory coords
memoryGraph = Graph {edges = M.fromList [(k, adjacent memory' k (70, 70)) | k <- A.indices memory']}
let corruptedMemory = getCorruptedMemoryMap contents
memoryGraph = Graph {edges = M.fromList [(k, adjacent corruptedMemory k (70, 70)) | k <- A.indices corruptedMemory]}
putStrLn $ "Day 18, Puzzle 1 solution: " ++ show (findShortestPath memoryGraph (0, 0) (70, 70))
day18_2 :: IO ()
day18_2 = do
contents <- map (splitOn ",") . lines <$> readFile "input/day18.txt"
let memory = A.listArray ((0, 0), (70, 70)) $ replicate 5041 '.'
coords = take 1024 [(read x, read y) | (x : y : _) <- contents]
coords' = drop 1024 [(read x, read y) | (x : y : _) <- contents]
memory' = corruptMemory memory coords
putStrLn $ "Day 18, Puzzle 2 solution: " ++ show (findFirstBlocker memory' coords' (0, 0) (70, 70))
let corruptedMemory = getCorruptedMemoryMap contents
fallingBytesCoords = drop 1024 [(read x, read y) | (x : y : _) <- contents]
putStrLn $ "Day 18, Puzzle 2 solution: " ++ show (findFirstBlocker corruptedMemory fallingBytesCoords (0, 0) (70, 70))