Advent of Code 2022 - Day 4: Camp Cleanup
In Day 4: Camp Cleanup, each elf has been assigned a range of segments to clean. We're given a list of these pairs, and we're tasked with comparing whether the ranges overlap completely (Part 1) or at all (Part 2).
The numbers in our input are all relatively small, to the point where we could brute-force check the elements of each range. But, let's try to avoid that by only examing the endpoints of the range.
This type of representation is bound to be more efficient. It also lends itself well to sweep line algorithms, which I bet we will see later this season.
The Range type
Our Range type is a data type that stores only its endpoints:
data Range = Range Int Int
In solving this challenge, I wanted to make the interface for this Range as reusable as possible. Most of the helper functions are analogs to similar functions on Data.Set
or Data.List
. For Part 1, we need to detect if one Range is a subset of another.
-- So reusable!
elem :: Int -> Range -> Bool
i `elem` Range a b = a <= i && i <= b
-- Much consistency!
isSubsetOf :: Range -> Range -> Bool
Range a b `isSubsetOf` target = a `elem` target && b `elem` target
-- Specific to Part 1:
isOverlap :: Range -> Range -> Bool
isOverlap a b = a `isSubsetOf` b || b `isSubsetOf` a
part1 :: [(Range, Range)] -> Int
part1 = length . filter (uncurry isOverlap)
For Part 2, we are looking for any overlap. We can also define some more commonly found functions:
-- Just like Sets!
intersection :: Range -> Range -> Range
intersection (Range a b) (Range x y) = Range (max a x) (min b y)
-- Just like Foldables, and Sets, and Maps...
null :: Range -> Bool
null (Range a b) = b < a
part2 :: [(Range, Range)] -> Int
part2 = length . filter (not . null . uncurry intersection)
Parsing
The final piece is to parse the input into a list of (Range, Range)
pairs. To do this, I used Parsec.
parseRangePair :: GenParser Char u (Range, Range)
parseRangePair = do
r1 <- parseRange
_ <- char ','
r2 <- parseRange
return (r1, r2)
where
parseRange = do
a <- read <$> many1 digit
_ <- char '-'
b <- read <$> many1 digit
return $ Range a b
input :: IO (Either ParseError [(Range, Range)])
input = traverse (parse parseRangePair "") . lines <$> readDay 2022 4
This is pretty verbose, and I'm sure it can be optimized.
Full Code
Here it is all together:
module AOC2022.Day04 (spec) where
import Input
import Test.Hspec
import Text.ParserCombinators.Parsec
import Prelude hiding (elem, null)
input :: IO (Either ParseError [(Range, Range)])
input = traverse (parse parseRangePair "") . lines <$> readDay 2022 4
spec :: IO ()
spec = hspec $ do
describe "Part 1" $ do
it "runs on custom input" $ do
myInput <- input
part1 <$> myInput `shouldBe` Right 0 -- redacted
describe "Part 2" $ do
it "runs on custom input" $ do
myInput <- input
part2 <$> myInput `shouldBe` Right 0 -- redacted
data Range = Range Int Int
parseRangePair :: GenParser Char u (Range, Range)
parseRangePair = do
r1 <- parseRange
_ <- char ','
r2 <- parseRange
return (r1, r2)
where
parseRange = do
a <- read <$> many1 digit
_ <- char '-'
b <- read <$> many1 digit
return $ Range a b
elem :: Int -> Range -> Bool
i `elem` Range a b = a <= i && i <= b
isSubsetOf :: Range -> Range -> Bool
Range a b `isSubsetOf` target = a `elem` target && b `elem` target
isOverlap :: Range -> Range -> Bool
isOverlap a b = a `isSubsetOf` b || b `isSubsetOf` a
part1 :: [(Range, Range)] -> Int
part1 = length . filter (uncurry isOverlap)
intersection :: Range -> Range -> Range
intersection (Range a b) (Range x y) = Range (max a x) (min b y)
null :: Range -> Bool
null (Range a b) = b < a
part2 :: [(Range, Range)] -> Int
part2 = length . filter (not . null . uncurry intersection)
Advent of Code 2022 Series
This post is part of a series describing my Haskell solutions to Advent of Code 2022.
See Also: Day 4 Bonus: Parsing
Next: Day 5: Supply Stacks Previous: Day 3: Rucksack Reorganization
Cheers!