Advent of Code 2025

Day 6

Changed files
+31 -7
src
+22 -3
src/Day6.hs
···
module Day6 where
+
import Data.List
+
import Debug.Trace
+
import Util
+
+
solveProblem :: ([Int], String) -> Int
+
solveProblem (terms, "+") = sum terms
+
solveProblem (terms, "*") = product terms
+
part1 :: String -> String
-
part1 _ = "Day 6 part 1"
-
+
part1 input =
+
let l = lines input
+
terms = map (map read) $ transpose $ map words $ init l
+
ops = words $ last l
+
in
+
show $
+
sum $
+
map solveProblem (zip terms ops)
+
part2 :: String -> String
-
part2 _ = "Day 6 part 2"
+
part2 input =
+
let l = lines input
+
terms :: [[Int]] = map (map read) $ splitOn null $ map trim $ transpose $ init l
+
ops = words $ last l
+
in show $ sum $ map solveProblem (zip terms ops)
+9 -4
src/Util.hs
···
module Util where
+
import Data.Char (isSpace)
import qualified Data.Map as Map
import Data.Map (Map)
-
splitOn :: (Char -> Bool) -> String -> [String]
+
splitOn :: (a -> Bool) -> [a] -> [[a]]
splitOn p s = case dropWhile p s of
-
"" -> []
+
[] -> []
s' -> w : splitOn p s''
where (w, s'') = break p s'
-
split :: Char -> String -> [String]
+
split :: (Eq a) => a -> [a] -> [[a]]
split c = splitOn (== c)
enumerate :: [a] -> [(Int,a)]
···
neighbors4 :: Point2 -> [Point2]
neighbors4 (x,y) =
-
[(x-1,y), (x+1,y), (x,y-1), (x,y+1)]
+
[(x-1,y), (x+1,y), (x,y-1), (x,y+1)]
+
+
trim :: String -> String
+
trim = f . f
+
where f = reverse . dropWhile isSpace