diff options
author | Tom Smeding <tom.smeding@gmail.com> | 2020-12-16 21:26:58 +0100 |
---|---|---|
committer | Tom Smeding <tom.smeding@gmail.com> | 2020-12-16 21:26:58 +0100 |
commit | 2d324ad69e72e56ff99ce53c55e248661a363b82 (patch) | |
tree | 64fc33f35393703a066a6dd37b08292722a45937 /2020 | |
parent | ac45449f8882a76612dcca699f84f54f08edcff4 (diff) |
Day 13
Diffstat (limited to '2020')
-rw-r--r-- | 2020/13.hs | 40 | ||||
-rw-r--r-- | 2020/13.in | 2 | ||||
-rw-r--r-- | 2020/6.hs | 8 | ||||
-rw-r--r-- | 2020/Makefile | 2 | ||||
-rw-r--r-- | 2020/Util.hs | 10 |
5 files changed, 54 insertions, 8 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..]]) diff --git a/2020/13.in b/2020/13.in new file mode 100644 index 0000000..88ee6c1 --- /dev/null +++ b/2020/13.in @@ -0,0 +1,2 @@ +1000340 +13,x,x,x,x,x,x,37,x,x,x,x,x,401,x,x,x,x,x,x,x,x,x,x,x,x,x,17,x,x,x,x,19,x,x,x,23,x,x,x,x,x,29,x,613,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,x,41 @@ -1,18 +1,12 @@ module Main (main) where import qualified Data.List.NonEmpty as NE -import Data.List.NonEmpty (NonEmpty(..), (<|)) import qualified Data.Set as Set import Input +import Util -splitOn :: (a -> Bool) -> [a] -> NonEmpty [a] -splitOn _ [] = [] :| [] -splitOn f (x:xs) | f x = [] <| splitOn f xs - | otherwise = let l :| ls = splitOn f xs - in (x : l) :| ls - main :: IO () main = do input <- getInput 6 diff --git a/2020/Makefile b/2020/Makefile index b85c185..36738bc 100644 --- a/2020/Makefile +++ b/2020/Makefile @@ -6,7 +6,7 @@ CXXFLAGS = -Wall -Wextra -std=c++17 -O2 OBJDIR = obj -HASKELL_AUX := Input.hs Asm.hs +HASKELL_AUX := Input.hs Util.hs Asm.hs CPP_AUX := HASKELL_SRC := $(filter-out $(HASKELL_AUX),$(wildcard *.hs)) CPP_SRC := $(filter-out $(CPP_AUX),$(wildcard *.cpp)) diff --git a/2020/Util.hs b/2020/Util.hs new file mode 100644 index 0000000..7f5f941 --- /dev/null +++ b/2020/Util.hs @@ -0,0 +1,10 @@ +module Util where + +import Data.List.NonEmpty (NonEmpty(..), (<|)) + + +splitOn :: (a -> Bool) -> [a] -> NonEmpty [a] +splitOn _ [] = [] :| [] +splitOn f (x:xs) | f x = [] <| splitOn f xs + | otherwise = let l :| ls = splitOn f xs + in (x : l) :| ls |