Advent of Code 2025
1module Day10 where 2 3import Data.Ratio ((%), Ratio) 4import Util (split) 5import Data.Maybe (catMaybes) 6import Data.Ord (comparing) 7import Data.List (sortBy) 8import qualified Data.Map as Map 9import Data.Map (Map) 10import Debug.Trace 11 12type Button = [Int] 13type Display = [Int] 14type Machine = (Button, [Button], [Int]) 15 16parse :: String -> [Machine] 17parse = map parseLine . lines 18 where parseDisplay :: String -> [Int] 19 parseDisplay s = [i | (i,c) <- zip [0..] (init (tail s)), c == '#'] 20 21 parseInts :: String -> [Int] 22 parseInts s = map read $ split ',' $ (init (tail s)) 23 24 parseLine line = 25 let w = words line 26 disp = head w 27 jolt = last w 28 in (parseDisplay disp, map parseInts (init (tail w)), parseInts jolt) 29 30xor :: [Int] -> [Int] -> [Int] 31xor a [] = a 32xor [] b = b 33xor (a:as) (b:bs) | a < b = (a : xor as (b:bs)) 34xor (a:as) (b:bs) | a == b = xor as bs 35xor (a:as) (b:bs) | a > b = (b : xor (a:as) bs) 36 37minimumMaybe :: [Maybe Int] -> Maybe Int 38minimumMaybe ns = 39 case catMaybes ns of 40 [] -> Nothing 41 ns' -> Just $ minimum ns' 42 43solveMachine :: Machine -> Maybe Int 44solveMachine ([],[],_) = Just 0 45solveMachine (_,[],_) = Nothing 46solveMachine (goal, (b:bs), jolt) = 47 minimumMaybe [solveMachine (goal, bs, jolt), 48 (+ 1) <$> solveMachine (xor goal b, bs, jolt)] 49 50part1 :: String -> String 51part1 input = 52 let machines = parse input 53 solutions = map solveMachine machines 54 in case sequence solutions of 55 Just ss -> show $ sum ss 56 Nothing -> "Failed" 57 58buttonToRepeat :: Int -> Button -> [Int] 59buttonToRepeat i button = go 0 button 60 where go n [] = repeat 0 61 go n (b:bs) = 62 if n == b then 63 (i : go (n+1) bs) 64 else 65 (0 : go (n+1) (b:bs)) 66 67gaussJordan :: Map (Int,Int) (Ratio Int) -> Map Int (Ratio Int) -> (Map (Int,Int) (Ratio Int), Map Int (Ratio Int), Int) 68gaussJordan m g = error "GJ" 69 70solveMachine2 :: [Button] -> [Int] -> Maybe Int 71solveMachine2 buttons goal = 72 let mat = Map.fromList [((i,j),1 % 1) | (i,b) <- zip [0..] buttons, j <- b] 73 g = Map.fromList $ zip [0..] (map (% 1) goal) 74 (mat', g', rank) = gaussJordan mat g 75 in Just 0 76 77part2 :: String -> String 78part2 input = 79 let machines = parse input 80 solutions = map (\(_,b,g) -> solveMachine2 b g) machines 81 in case sequence solutions of 82 Just ss -> show $ sum ss 83 Nothing -> "Failed"