summaryrefslogtreecommitdiff
path: root/2019
diff options
context:
space:
mode:
authortomsmeding <tom.smeding@gmail.com>2019-12-18 21:52:25 +0100
committertomsmeding <tom.smeding@gmail.com>2019-12-18 21:52:34 +0100
commite689580094e12993d44996e6b9d933155e735e27 (patch)
tree092301adec1300caa2571670b006780ee404de03 /2019
parent238edbb3475461e1b8e51d5819e12ab535261c17 (diff)
Day 16 (lazy slow solution)
Diffstat (limited to '2019')
-rw-r--r--2019/16.hs45
-rw-r--r--2019/16.in1
2 files changed, 46 insertions, 0 deletions
diff --git a/2019/16.hs b/2019/16.hs
new file mode 100644
index 0000000..004cbf7
--- /dev/null
+++ b/2019/16.hs
@@ -0,0 +1,45 @@
+{-# LANGUAGE BangPatterns #-}
+module Main where
+
+import qualified Data.Array.Unboxed as A
+
+import Input
+
+
+lastDigit :: Int -> Int
+lastDigit = abs . (`rem` 10)
+
+type Array = A.UArray Int
+
+prefixSums :: Array Int -> Array Int
+prefixSums input = A.listArray (0, snd (A.bounds input) + 1) (scanl (+) 0 (A.elems input))
+
+phase :: Array Int -> Array Int
+phase !input =
+ let end = snd (A.bounds input)
+ prefixes = prefixSums input
+ rangeSum from to = prefixes A.! to - prefixes A.! from
+ intervalSum acc offset step sign
+ | offset + step > end =
+ if offset > end
+ then acc
+ else acc + sign * rangeSum offset (end + 1)
+ | otherwise =
+ let acc' = acc + sign * rangeSum offset (offset + step)
+ in intervalSum acc' (offset + 2 * step) step (negate sign)
+ in A.listArray (0, end) [lastDigit (intervalSum 0 (i-1) i 1) | i <- [1..end+1]]
+
+fft :: Int -> [Int] -> [Int]
+fft times list = A.elems (iterate phase (A.listArray (0, length list - 1) list) !! times)
+
+main :: IO ()
+main = do
+ inpString <- head <$> getInput 16
+
+ let inpList = map (read . pure) inpString
+ putStrLn (concatMap show (take 8 (fft 100 inpList)))
+
+ let messageOffset = read (take 7 inpString)
+
+ -- Note: Part 2 takes 3m20s for me
+ putStrLn (concatMap show (take 8 (drop messageOffset (fft 100 (concat (replicate 10000 inpList))))))
diff --git a/2019/16.in b/2019/16.in
new file mode 100644
index 0000000..1055f5d
--- /dev/null
+++ b/2019/16.in
@@ -0,0 +1 @@
+59777373021222668798567802133413782890274127408951008331683345339720122013163879481781852674593848286028433137581106040070180511336025315315369547131580038526194150218831127263644386363628622199185841104247623145887820143701071873153011065972442452025467973447978624444986367369085768018787980626750934504101482547056919570684842729787289242525006400060674651940042434098846610282467529145541099887483212980780487291529289272553959088376601234595002785156490486989001949079476624795253075315137318482050376680864528864825100553140541159684922903401852101186028076448661695003394491692419964366860565639600430440581147085634507417621986668549233797848