summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorTom Smeding <tom.smeding@gmail.com>2020-12-16 22:20:04 +0100
committerTom Smeding <tom.smeding@gmail.com>2020-12-16 22:20:04 +0100
commita5fd247a5e66ea63fc0826a884dd78e37888878b (patch)
tree0214c63ad93fb806453061a2216ba6e41408710f
parent9b0b5326ff4a5bfc20e24d44aaf967fb48db8eb8 (diff)
Day 15 (slow)
-rw-r--r--2020/15.hs30
-rw-r--r--2020/15.in1
2 files changed, 31 insertions, 0 deletions
diff --git a/2020/15.hs b/2020/15.hs
new file mode 100644
index 0000000..b568fb7
--- /dev/null
+++ b/2020/15.hs
@@ -0,0 +1,30 @@
+module Main where
+
+import Data.Foldable (toList)
+import qualified Data.IntMap.Strict as IM
+import Data.IntMap.Strict (IntMap)
+import Data.List (foldl')
+
+import Input
+import Util
+
+
+type State = IntMap Int
+
+next :: Int -> Int -> State -> Int
+next idx num mp = maybe 0 (idx -) (IM.lookup num mp)
+
+vaneck :: [Int] -> [Int]
+vaneck values = init values ++ expand (length values) (last values) (seed (init values))
+ where
+ expand idx num state =
+ let num' = next idx num state
+ in num : expand (idx + 1) num' (IM.insert num idx state)
+ seed = foldl' go mempty . zip [1..]
+ where go mp (idx, num) = IM.insert num idx mp
+
+main :: IO ()
+main = do
+ input <- map read . toList . splitOn (== ',') . head <$> getInput 15 :: IO [Int]
+ print (vaneck input !! 2019)
+ print (vaneck input !! 29999999)
diff --git a/2020/15.in b/2020/15.in
new file mode 100644
index 0000000..9e941d9
--- /dev/null
+++ b/2020/15.in
@@ -0,0 +1 @@
+1,20,11,6,12,0