diff options
Diffstat (limited to 'execs')
-rw-r--r-- | execs/Day08.hs | 4 | ||||
-rw-r--r-- | execs/Day09.hs | 35 |
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 | |||
40 | main :: IO () | 40 | main :: IO () |
41 | main = do | 41 | main = 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 | |||
2 | module Main where | ||
3 | |||
4 | import Utils | ||
5 | import Data.List (inits, tails, find) | ||
6 | import Data.Bifunctor | ||
7 | |||
8 | parseLine :: String -> Int | ||
9 | parseLine = read | ||
10 | |||
11 | doCheck :: [Int] -> Int -> Bool | ||
12 | doCheck preamble target = target `elem` p | ||
13 | where p = [x + y | x <- preamble, y <- preamble, x /= y] | ||
14 | |||
15 | checkAll :: [Int] -> [Int] -> [(Int, Bool)] | ||
16 | checkAll preamble [x] = [(x, doCheck preamble x)] | ||
17 | checkAll preamble@(p:ps) (x:xs) = (x, doCheck preamble x) : checkAll (ps++[x]) xs | ||
18 | |||
19 | |||
20 | findWeakness :: [[Int]] -> Int -> Int | ||
21 | findWeakness subs target = mn + mx | ||
22 | where Just t = find ((== target) . sum) subs | ||
23 | mn = minimum t | ||
24 | mx = maximum t | ||
25 | |||
26 | main :: IO () | ||
27 | main = 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 | ||