summaryrefslogtreecommitdiff
path: root/2020/9.hs
blob: d59368126245d4a30ffa5442443cef118af0c715 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
module Main where

import Data.List (find)
import Data.Maybe (fromJust)
import qualified Data.Set as Set
import qualified Data.Map.Strict as Map
import Data.Map.Strict (Map)

import Input


preludeLen :: Int
preludeLen = 25

findRun :: Int -> [Int] -> (Int, Int)
findRun target input = go input 0 0 mempty
  where
    go :: [Int] -> Int -> Int -> Map Int Int -> (Int, Int)
    go (x:xs) index beforeTotal prevs
      | Just index' <- Map.lookup (beforeTotal + x - target) prevs
      , index - index' >= 2
      = (index', index)
      | otherwise
      = go xs (index + 1) (beforeTotal + x) (Map.insert (beforeTotal + x) index prevs)
    go [] _ _ _ = error "Run not found"

main :: IO ()
main = do
    input <- map read <$> getInput 9 :: IO [Int]
    let (prelude, rest) = splitAt preludeLen input
        sets = scanl (\s (i1, i2) -> Set.insert i2 (Set.delete i1 s))
                     (Set.fromList prelude)
                     (zip input rest)
        isValid s i = any (`Set.member` s) [i - n | n <- Set.toList s, n /= i - n]
        weakness = snd (fromJust (find (not . uncurry isValid) (zip sets rest)))
    print weakness

    let (index1, index2) = findRun weakness input
        run = drop (index1 + 1) (take index2 input)
    print (minimum run + maximum run)