Solve 2024-05
This commit is contained in:
parent
c45f28f35d
commit
efeaf96999
4 changed files with 1484 additions and 5 deletions
28
data/Y2024/D05/example
Normal file
28
data/Y2024/D05/example
Normal file
|
|
@ -0,0 +1,28 @@
|
||||||
|
47|53
|
||||||
|
97|13
|
||||||
|
97|61
|
||||||
|
97|47
|
||||||
|
75|29
|
||||||
|
61|13
|
||||||
|
75|53
|
||||||
|
29|13
|
||||||
|
97|29
|
||||||
|
53|29
|
||||||
|
61|53
|
||||||
|
97|53
|
||||||
|
61|29
|
||||||
|
47|13
|
||||||
|
75|47
|
||||||
|
97|75
|
||||||
|
47|61
|
||||||
|
75|61
|
||||||
|
47|29
|
||||||
|
75|13
|
||||||
|
53|13
|
||||||
|
|
||||||
|
75,47,61,53,29
|
||||||
|
97,61,53,29,13
|
||||||
|
75,29,13
|
||||||
|
75,97,47,61,53
|
||||||
|
61,13,29
|
||||||
|
97,13,75,29,47
|
||||||
File diff suppressed because it is too large
Load diff
|
|
@ -1,6 +1,88 @@
|
||||||
|
{- HLINT ignore "Use bimapF" -}
|
||||||
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
|
|
||||||
module AoC.Y2024.D05 (solve) where
|
module AoC.Y2024.D05 (solve) where
|
||||||
|
|
||||||
import AoC.Riddle
|
import AoC.Riddle
|
||||||
|
|
||||||
|
-- import Data.Set qualified as S
|
||||||
|
|
||||||
|
import Data.Set qualified as S
|
||||||
|
import Data.String (lines)
|
||||||
|
import Data.Text (splitOn)
|
||||||
|
import Prelude hiding (lines)
|
||||||
|
|
||||||
|
data Puzzle = Puzzle
|
||||||
|
{ orderingRules :: Rules
|
||||||
|
, updates :: [Update]
|
||||||
|
}
|
||||||
|
deriving stock (Show)
|
||||||
|
|
||||||
|
type Rules = Set (Page, Page)
|
||||||
|
type Page = Int
|
||||||
|
type Update = [Page]
|
||||||
|
|
||||||
|
parse :: Riddle -> Maybe Puzzle
|
||||||
|
parse riddle = do
|
||||||
|
let
|
||||||
|
(p1, p2) = break null $ lines $ toString riddle
|
||||||
|
p2' <- nonEmpty p2
|
||||||
|
Puzzle <$> parseOrderings p1 <*> parseRules (tail p2')
|
||||||
|
|
||||||
|
parseOrderings :: [String] -> Maybe Rules
|
||||||
|
parseOrderings s = do
|
||||||
|
p <- traverse (\l -> (,) <$> readMaybe (take 2 l) <*> readMaybe (drop 3 l)) s
|
||||||
|
pure $ fromList p
|
||||||
|
|
||||||
|
parseRules :: [String] -> Maybe [Update]
|
||||||
|
parseRules = mapM parseRule
|
||||||
|
|
||||||
|
parseRule :: String -> Maybe Update
|
||||||
|
parseRule = mapM readMaybe . fmap toString . splitOn "," . toText
|
||||||
|
|
||||||
|
isSafe :: Rules -> Update -> Bool
|
||||||
|
isSafe _ [] = True
|
||||||
|
isSafe rules (u : us) = correctlyPositioned rules u us && isSafe rules us
|
||||||
|
|
||||||
|
correctlyPositioned :: Rules -> Page -> Update -> Bool
|
||||||
|
correctlyPositioned rules page = all (correctlyPositionedAgainst rules page)
|
||||||
|
|
||||||
|
correctlyPositionedAgainst :: Rules -> Page -> Page -> Bool
|
||||||
|
correctlyPositionedAgainst rules a b = S.member (a, b) rules && S.notMember (b, a) rules
|
||||||
|
|
||||||
|
middlePage :: [a] -> Maybe a
|
||||||
|
middlePage update = case length update `mod` 2 of
|
||||||
|
0 -> Nothing
|
||||||
|
_ ->
|
||||||
|
let
|
||||||
|
half = length update `div` 2
|
||||||
|
m = drop half $ take (half + 1) update
|
||||||
|
in
|
||||||
|
case m of
|
||||||
|
[p] -> Just p
|
||||||
|
_ -> Nothing
|
||||||
|
|
||||||
|
sortCorrectly :: Puzzle -> Puzzle
|
||||||
|
sortCorrectly Puzzle{..} = Puzzle{orderingRules, updates = fixedUpdates}
|
||||||
|
where
|
||||||
|
fixedUpdates :: [Update]
|
||||||
|
fixedUpdates = sortBy f <$> filter (not . isSafe orderingRules) updates
|
||||||
|
|
||||||
|
f :: Page -> Page -> Ordering
|
||||||
|
f a b = case (S.member (a, b) orderingRules, S.member (b, a) orderingRules) of
|
||||||
|
(True, _) -> LT
|
||||||
|
(_, True) -> GT
|
||||||
|
_ -> EQ
|
||||||
|
|
||||||
|
part1 :: Riddle -> Maybe Int
|
||||||
|
part1 riddle = do
|
||||||
|
Puzzle{..} <- parse riddle
|
||||||
|
sum <$> mapM middlePage (filter (isSafe orderingRules) updates)
|
||||||
|
|
||||||
|
part2 :: Riddle -> Maybe Int
|
||||||
|
part2 riddle = do
|
||||||
|
Puzzle{..} <- sortCorrectly <$> parse riddle
|
||||||
|
sum <$> mapM middlePage (filter (isSafe orderingRules) updates)
|
||||||
|
|
||||||
solve :: (MonadIO m) => Text -> m (Either Text Solution)
|
solve :: (MonadIO m) => Text -> m (Either Text Solution)
|
||||||
solve _ = pure $ Left "not yet implemented"
|
solve riddle = pure $ Right [fromIntegral $ fromMaybe 0 (part1 riddle), fromIntegral $ fromMaybe 0 (part2 riddle)]
|
||||||
|
|
|
||||||
|
|
@ -21,8 +21,6 @@ spec = do
|
||||||
it "calculates correctly" do
|
it "calculates correctly" do
|
||||||
runAoC Y2024 D04 `shouldReturn` Right [2567, 2029]
|
runAoC Y2024 D04 `shouldReturn` Right [2567, 2029]
|
||||||
|
|
||||||
{-
|
|
||||||
describe "Day 5" do
|
describe "Day 5" do
|
||||||
it "calculates the example correctly" do
|
it "calculates correctly" do
|
||||||
runAoCExample Y2023 D05 `shouldReturn` Right [35]
|
runAoC Y2024 D05 `shouldReturn` Right [5452, 4598]
|
||||||
-}
|
|
||||||
|
|
|
||||||
Loading…
Add table
Add a link
Reference in a new issue