2020-12-10 12:30:34 +01:00
|
|
|
#! /usr/bin/env -S"ANSWER=42" nix-shell
|
|
|
|
#! nix-shell -p ghcid
|
2020-12-10 13:26:48 +01:00
|
|
|
#! nix-shell -p "haskellPackages.ghcWithPackages (p: with p; [pretty-simple containers])"
|
2020-12-10 12:30:34 +01:00
|
|
|
#! nix-shell -i "ghcid -c 'ghci' -T main"
|
|
|
|
|
|
|
|
{-# OPTIONS_GHC -Wall -Wincomplete-uni-patterns #-}
|
|
|
|
{-# OPTIONS_GHC -Wno-unused-top-binds -Wno-unused-imports #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
2020-12-10 14:25:15 +01:00
|
|
|
import Data.IntMap.Strict (IntMap)
|
2020-12-10 13:26:48 +01:00
|
|
|
import Data.IntSet (IntSet)
|
2020-12-10 14:25:15 +01:00
|
|
|
import Data.List (inits, tails, sortOn)
|
|
|
|
import Data.Monoid
|
2020-12-10 12:30:34 +01:00
|
|
|
import Debug.Trace (trace)
|
|
|
|
import Text.Pretty.Simple
|
2020-12-10 14:25:15 +01:00
|
|
|
import qualified Data.IntMap.Strict as M
|
2020-12-10 13:26:48 +01:00
|
|
|
import qualified Data.IntSet as S
|
|
|
|
|
2020-12-10 12:30:34 +01:00
|
|
|
|
|
|
|
exampleData :: [Int]
|
|
|
|
exampleData = [ 35,20,15,25,47,40,62,55,65,95,102,117,150
|
|
|
|
, 182,127,219,299,277,309,576 ];
|
|
|
|
|
2020-12-10 13:26:48 +01:00
|
|
|
pairSums :: [Int] -> IntSet
|
|
|
|
pairSums xs = S.fromList $ do
|
|
|
|
i1 <- xs
|
|
|
|
i2 <- xs
|
|
|
|
pure (i1 + i2)
|
|
|
|
|
|
|
|
isSumOfPreamble :: Int -> [Int] -> Bool
|
|
|
|
isSumOfPreamble size xs = go tx
|
|
|
|
where
|
|
|
|
go (x:_) = x `S.member` (pairSums preamble)
|
|
|
|
go ([]) = False
|
|
|
|
(preamble, tx) = splitAt size xs
|
|
|
|
|
|
|
|
solvePart1 :: Int -> [Int] -> (Int,Bool)
|
|
|
|
solvePart1 size message =
|
|
|
|
head $ dropWhile (snd) $
|
|
|
|
map go ( takeWhile ((> size) . length) $ tails message )
|
|
|
|
where
|
|
|
|
go xs = (head $ drop size xs,isSumOfPreamble size xs)
|
|
|
|
|
2020-12-10 14:25:15 +01:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
sortedContiguousSubLists :: [Int] -> [[Int]]
|
|
|
|
sortedContiguousSubLists =
|
|
|
|
dropWhile (== []) . sortOn length . concat . fmap inits . tails
|
|
|
|
|
|
|
|
listSums :: [[Int]] -> IntMap [Int]
|
|
|
|
listSums xss = M.fromList $ do
|
|
|
|
xs <- xss
|
|
|
|
pure $ (getSum $ foldMap Sum xs, xs)
|
|
|
|
|
|
|
|
solvePart2 :: Int -> [Int] -> Int
|
|
|
|
solvePart2 target message = (\x -> minimum x + maximum x) $ bigMap M.! target
|
|
|
|
where
|
|
|
|
bigMap = listSums $ sortedContiguousSubLists message
|
|
|
|
|
2020-12-10 12:30:34 +01:00
|
|
|
main :: IO ()
|
|
|
|
main = do
|
|
|
|
putStrLn "Test"
|
2020-12-10 13:26:48 +01:00
|
|
|
print exampleData
|
|
|
|
print $ 1 `S.member` (pairSums [])
|
|
|
|
print $ pairSums exampleData
|
2020-12-10 12:30:34 +01:00
|
|
|
putStrLn "Day 9 - Part 1"
|
2020-12-10 13:26:48 +01:00
|
|
|
print $ solvePart1 5 exampleData
|
|
|
|
input <- lines <$> readFile "day9/input"
|
|
|
|
print $ solvePart1 25 $ map read input
|
2020-12-10 14:25:15 +01:00
|
|
|
putStrLn "Test"
|
|
|
|
print $ take 10 $ drop 20 $ sortedContiguousSubLists exampleData
|
|
|
|
putStrLn "Day 9 - Part 2"
|
|
|
|
print $ solvePart2 127 exampleData
|
|
|
|
print $ solvePart2 3199139634 $ map read input
|