Created
December 3, 2025 12:01
-
-
Save lotusirous/b5f9efba4c7b1b371c474e53b1992f41 to your computer and use it in GitHub Desktop.
advent of code 2025 in haskell
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| module Main where | |
| data Direction = R | L deriving (Show, Eq) | |
| data State = State {pos :: Int, hit :: Int} deriving (Show, Eq) | |
| type Step = Int | |
| type Instruction = (Direction, Step) | |
| parse :: String -> Instruction | |
| parse ('R' : xs) = (R, read xs) | |
| parse ('L' : xs) = (L, read xs) | |
| parse s = error $ "invalid instruction: " ++ s | |
| rotate :: Int -> Int -> Instruction -> Int | |
| rotate n pos (R, step) = (pos + step) `mod` n | |
| rotate n pos (L, step) = (pos - step) `mod` n | |
| step :: Int -> State -> Instruction -> State | |
| step n (State p h) instr = | |
| State newPos newHit | |
| where | |
| newPos = rotate n p instr | |
| newHit = h + (if newPos == 0 then 1 else 0) | |
| passesZero :: Int -> Instruction -> Int | |
| passesZero p (R, s) = (p + s) `div` 100 | |
| passesZero p (L, s) | |
| | s >= p = 1 + (s - p) `div` 100 | |
| | otherwise = 0 | |
| step2 :: Int -> State -> Instruction -> State | |
| step2 n (State p h) instr = | |
| State newPos newHit | |
| where | |
| newPos = rotate n p instr | |
| newHit = h + passesZero p instr | |
| solve1 :: [String] -> State | |
| solve1 lines = | |
| let initState = State 50 0 | |
| instructions = map parse lines | |
| in foldl (step 100) initState instructions | |
| solve2 :: [String] -> State | |
| solve2 lines = | |
| let initState = State 50 0 | |
| instructions = map parse lines | |
| in foldl (step2 100) initState instructions | |
| -- Tests | |
| test :: String -> Bool -> IO () | |
| test name True = putStrLn $ "OK: " ++ name | |
| test name False = putStrLn $ "FAIL: " ++ name | |
| tests :: IO () | |
| tests = do | |
| -- Parsing | |
| test "parse R5" $ parse "R5" == (R, 5) | |
| test "parse L37" $ parse "L37" == (L, 37) | |
| -- Rotation | |
| test "rotate right" $ rotate 10 5 (R, 3) == 8 | |
| test "rotate left" $ rotate 10 5 (L, 3) == 2 | |
| test "wrap around" $ rotate 10 8 (R, 5) == 3 | |
| -- Part 1 | |
| test "hit zero" $ solve1 ["R50"] == State 0 1 | |
| test "multiple hits" $ solve1 ["R50", "R100"] == State 0 2 | |
| test "roundtrip" $ solve1 ["R30", "L30"] == State 50 0 | |
| -- Part 2 | |
| test "L68 from 50 passes 0" $ passesZero 50 (L, 68) == 1 | |
| test "L30 from 82 no pass" $ passesZero 82 (L, 30) == 0 | |
| test "R48 from 52 lands 0" $ passesZero 52 (R, 48) == 1 | |
| test "R60 from 95 passes 0" $ passesZero 95 (R, 60) == 1 | |
| main :: IO () | |
| main = do | |
| tests | |
| content <- lines <$> readFile "./_input/day01.txt" | |
| putStrLn $ "\nPart 1: " ++ show (solve1 content) | |
| putStrLn $ "Part 2: " ++ show (solve2 content) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment