summaryrefslogtreecommitdiff
path: root/2020/13.hs
diff options
context:
space:
mode:
Diffstat (limited to '2020/13.hs')
-rw-r--r--2020/13.hs40
1 files changed, 40 insertions, 0 deletions
diff --git a/2020/13.hs b/2020/13.hs
new file mode 100644
index 0000000..5bb6a39
--- /dev/null
+++ b/2020/13.hs
@@ -0,0 +1,40 @@
+module Main where
+
+import Data.Foldable (toList)
+import Data.Maybe (catMaybes)
+import Data.Ord (comparing)
+import Data.List (minimumBy)
+
+import Input
+import Util
+
+
+ceilDiv :: Integral a => a -> a -> a
+ceilDiv a b = (a + b - 1) `div` b
+
+-- Returns (gcd m n, (x, y)) such that x * m + y * m = gcd m n
+egcd :: Integral a => a -> a -> (a, (a, a))
+egcd m n = egcd' 1 0 m 0 1 n
+ where
+ egcd' x y g _ _ 0 = (g, (x, y))
+ egcd' x y g x2 y2 g2 = -- invariant: x * m + y * n = g && x2 * m + y2 * n = g2
+ let (q, r) = g `divMod` g2
+ in egcd' x2 y2 g2 (x - q * x2) (y - q * y2) r
+
+crt :: Integral a => (a, a) -> (a, a) -> (a, a)
+crt (x, m) (y, n)
+ | (1, (u, v)) <- egcd m n = ((x * v * n + y * u * m) `mod` (n * m), n * m)
+ | otherwise = error "crt: non-coprime moduli"
+
+crt' :: Integral a => [(a, a)] -> a
+crt' = fst . foldl1 crt
+
+main :: IO ()
+main = do
+ [deptimestr, ivsstr] <- getInput 13
+ let arrivetime = read deptimestr :: Integer
+ ivs = [if x == "x" then Nothing else Just (read x) | x <- toList (splitOn (== ',') ivsstr)]
+ (earliest, leavetime) = minimumBy (comparing snd) [(iv, arrivetime `ceilDiv` iv * iv) | iv <- catMaybes ivs]
+ print (earliest * (leavetime - arrivetime))
+
+ print (crt' [(iv - idx, iv) | (Just iv, idx) <- zip ivs [0..]])