My solutions to Advent of Code 2025
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 

66 lines
1.9 KiB

module Main where
import Control.Arrow ((***))
import Data.Ix (inRange)
import Data.List (foldl', sort)
import System.Environment (getArgs)
main :: IO ()
main = do
input <- readFile . head =<< getArgs
putStrLn $ unwords ["Part 1:", show $ part1 input]
putStrLn $ unwords ["Part 2:", show $ part2 input]
part1 :: String -> Int
part1 = length . uncurry (filter . isFresh) . parse
where
isFresh :: [(Int, Int)] -> Int -> Bool
isFresh fresh ing = any (contained ing) fresh
contained :: Int -> (Int, Int) -> Bool
contained = flip inRange
-- Splits input on empty line and parses the first half with genRanges
-- and the second half into ints with read.
parse :: String -> ([(Int, Int)], [Int])
parse = (genRanges *** (map read . drop 1)) . span (/= "") . lines
where
genRanges :: [String] -> [(Int, Int)]
genRanges = foldl' (mergeRanges) mempty . sort . map parseRange
-- Parse "X-Y" -> (X, Y)
parseRange :: String -> (Int, Int)
parseRange s = case span (/= '-') s of
(start, '-' : end) -> (read start, read end)
_ -> error $ "parseRange: expected a string on the form \"NUM-NUM\", got \"" <> s <> "\""
-- Generate ranges by combining adjacent ranges if they overlap.
--
-- Ignores ranges that are fully enclosed by previous range.
-- N.B. Assumes ranges are sorted on first component.
mergeRanges :: [(Int, Int)] -> (Int, Int) -> [(Int, Int)]
mergeRanges [] i = [i]
mergeRanges fresh@((a, b) : rest) (x, y)
| x `contained` (a, b) && y > b = (a, y) : rest
| x < a && y `contained` (a, b) = (x, b) : rest
| x `contained` (a, b) && y `contained` (a, b) = fresh
| otherwise = (x, y) : fresh
part2 :: String -> Int
part2 = sum . map ((+ 1) . uncurry (flip (-))) . fst . parse
testInput :: String
testInput =
unlines
[ "3-5",
"10-14",
"16-20",
"12-18",
"",
"1",
"5",
"8",
"11",
"17",
"32"
]