aboutsummaryrefslogtreecommitdiff
path: root/execs
diff options
context:
space:
mode:
authorAkshay <[email protected]>2020-12-09 05:33:39 +0000
committerAkshay <[email protected]>2020-12-09 05:33:39 +0000
commit644c38de8b633dc5e03bff5216f68b2bfde4a645 (patch)
treeac2c0056739d38bba7855c3aa988ae190a1b158c /execs
parent06b14ed84c0a8ec11462f0a6f7397c3e3a52654d (diff)
add initial solution for day09
Diffstat (limited to 'execs')
-rw-r--r--execs/Day08.hs4
-rw-r--r--execs/Day09.hs35
2 files changed, 37 insertions, 2 deletions
diff --git a/execs/Day08.hs b/execs/Day08.hs
index 7d3fce8..6546990 100644
--- a/execs/Day08.hs
+++ b/execs/Day08.hs
@@ -40,6 +40,6 @@ genAll (acc:rest) = map (acc:) $ genAll rest
40main :: IO () 40main :: IO ()
41main = do 41main = do
42 n <- map (parseLine . words) . lines <$> readFile "input/08" 42 n <- map (parseLine . words) . lines <$> readFile "input/08"
43 let solve1 = run 0 0 Set.empty . Map.fromList . zip [0..] 43 let solve1 = run 0 0 mempty . Map.fromList . zip [0..]
44 print $ solve1 n 44 print $ solve1 n
45 print $ solve1 $ head $ filter (doesEnd 0 0 Set.empty . Map.fromList . zip [0..]) $ genAll n 45 print $ solve1 $ head $ filter (doesEnd 0 0 mempty . Map.fromList . zip [0..]) $ genAll n
diff --git a/execs/Day09.hs b/execs/Day09.hs
new file mode 100644
index 0000000..e2e5fd4
--- /dev/null
+++ b/execs/Day09.hs
@@ -0,0 +1,35 @@
1
2module Main where
3
4import Utils
5import Data.List (inits, tails, find)
6import Data.Bifunctor
7
8parseLine :: String -> Int
9parseLine = read
10
11doCheck :: [Int] -> Int -> Bool
12doCheck preamble target = target `elem` p
13 where p = [x + y | x <- preamble, y <- preamble, x /= y]
14
15checkAll :: [Int] -> [Int] -> [(Int, Bool)]
16checkAll preamble [x] = [(x, doCheck preamble x)]
17checkAll preamble@(p:ps) (x:xs) = (x, doCheck preamble x) : checkAll (ps++[x]) xs
18
19
20findWeakness :: [[Int]] -> Int -> Int
21findWeakness subs target = mn + mx
22 where Just t = find ((== target) . sum) subs
23 mn = minimum t
24 mx = maximum t
25
26main :: IO ()
27main = do
28 n <- map parseLine . lines <$> readFile "input/09"
29 let preambleLen = 25
30 Just (target, _) = find (not . snd)
31 $ uncurry checkAll
32 $ bimap (take preambleLen) (drop preambleLen)
33 $ (,) n n
34 print target
35 print $ findWeakness (sublists n) target