48 lines
1.4 KiB
Haskell
48 lines
1.4 KiB
Haskell
|
module Day13 where
|
||
|
|
||
|
import AoC
|
||
|
|
||
|
import Data.List
|
||
|
import Data.List.Split
|
||
|
import Data.Maybe
|
||
|
import Data.Ord
|
||
|
import Data.Tuple
|
||
|
|
||
|
-- | inverse integer modulus, "remainder until the next multiple of d"
|
||
|
--
|
||
|
-- @(n + n `'invMod'` d) `'mod'` d == 0@
|
||
|
invMod :: Integral a => a -> a -> a
|
||
|
invMod n d | r == 0 = 0
|
||
|
| otherwise = d - r
|
||
|
where r = n `mod` d
|
||
|
|
||
|
-- | @'combineRemainders' (r1, d1) (r2, d2) = (r3, d3)@ combines a relation of the form
|
||
|
--
|
||
|
-- @
|
||
|
-- x = r1 (mod d1)
|
||
|
-- x = r2 (mod d2)
|
||
|
-- @
|
||
|
--
|
||
|
-- into a single relation
|
||
|
--
|
||
|
-- @
|
||
|
-- x = r3 (mod d3)
|
||
|
-- @
|
||
|
--
|
||
|
-- @d1@ should be larger than @d2@ for better performance.
|
||
|
combineRemainders :: (Integral a) => (a, a) -> (a, a) -> (a, a)
|
||
|
combineRemainders (r1, d1) (r2, d2) = (fromJust . find (\x -> x `mod` d2 == r2) $ [r1,d1+r1..], d1*d2)
|
||
|
|
||
|
part1 :: Int -> [Int] -> Int
|
||
|
part1 arr = uncurry (*) . minimumBy (comparing snd) . map (toSnd $ invMod arr)
|
||
|
where toSnd f x = (x, f x)
|
||
|
|
||
|
part2 :: [Maybe Int] -> Int
|
||
|
part2 = fst . foldl1 combineRemainders . map (\(r, d) -> (r `invMod` d, d)) . catMaybes . map sequence . enumerate 0
|
||
|
where enumerate start (x:xs) = (start, x) : enumerate (succ start) xs
|
||
|
enumerate _ [] = []
|
||
|
|
||
|
main = runAoC (intoTuple . map (map (fmap read . justIf (/="x")) . splitOn ",") . lines) (uncurry part1 . fmap catMaybes) (part2 . snd)
|
||
|
where intoTuple [[Just x], y] = (x, y)
|
||
|
justIf p x = if p x then Just x else Nothing
|