aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAkshay <[email protected]>2020-12-09 06:13:55 +0000
committerAkshay <[email protected]>2020-12-09 06:13:55 +0000
commitac3191ae40b8df0873f2e04f5bc1017322941b5d (patch)
tree88e845ae69db0beb70c6e1b0d9d96b3699a77774
parent644c38de8b633dc5e03bff5216f68b2bfde4a645 (diff)
be more <<<functional>>>
-rw-r--r--execs/Day09.hs17
-rw-r--r--lib/Utils.hs4
2 files changed, 9 insertions, 12 deletions
diff --git a/execs/Day09.hs b/execs/Day09.hs
index e2e5fd4..f1c41f2 100644
--- a/execs/Day09.hs
+++ b/execs/Day09.hs
@@ -2,7 +2,7 @@
2module Main where 2module Main where
3 3
4import Utils 4import Utils
5import Data.List (inits, tails, find) 5import Data.List (inits, tails, find, sort)
6import Data.Bifunctor 6import Data.Bifunctor
7 7
8parseLine :: String -> Int 8parseLine :: String -> Int
@@ -12,24 +12,17 @@ doCheck :: [Int] -> Int -> Bool
12doCheck preamble target = target `elem` p 12doCheck preamble target = target `elem` p
13 where p = [x + y | x <- preamble, y <- preamble, x /= y] 13 where p = [x + y | x <- preamble, y <- preamble, x /= y]
14 14
15checkAll :: [Int] -> [Int] -> [(Int, Bool)] 15checkAll :: [[Int]] -> [Int] -> [(Int, Bool)]
16checkAll preamble [x] = [(x, doCheck preamble x)] 16checkAll = zipWith (\p t -> (t, doCheck p t))
17checkAll preamble@(p:ps) (x:xs) = (x, doCheck preamble x) : checkAll (ps++[x]) xs
18
19 17
20findWeakness :: [[Int]] -> Int -> Int 18findWeakness :: [[Int]] -> Int -> Int
21findWeakness subs target = mn + mx 19findWeakness subs target = minimum t + maximum t
22 where Just t = find ((== target) . sum) subs 20 where Just t = find ((== target) . sum) subs
23 mn = minimum t
24 mx = maximum t
25 21
26main :: IO () 22main :: IO ()
27main = do 23main = do
28 n <- map parseLine . lines <$> readFile "input/09" 24 n <- map parseLine . lines <$> readFile "input/09"
29 let preambleLen = 25 25 let preambleLen = 25
30 Just (target, _) = find (not . snd) 26 Just (target, _) = find (not . snd) $ checkAll (windows preambleLen n) (drop preambleLen n)
31 $ uncurry checkAll
32 $ bimap (take preambleLen) (drop preambleLen)
33 $ (,) n n
34 print target 27 print target
35 print $ findWeakness (sublists n) target 28 print $ findWeakness (sublists n) target
diff --git a/lib/Utils.hs b/lib/Utils.hs
index 89b1bd3..1381f16 100644
--- a/lib/Utils.hs
+++ b/lib/Utils.hs
@@ -6,6 +6,7 @@ module Utils ( binaryToInt
6 , (&+) 6 , (&+)
7 , howMany 7 , howMany
8 , sublists 8 , sublists
9 , windows
9 ) where 10 ) where
10 11
11import Data.Char (digitToInt) 12import Data.Char (digitToInt)
@@ -39,3 +40,6 @@ howMany predicate = length . filter predicate
39 40
40sublists :: [a] -> [[a]] 41sublists :: [a] -> [[a]]
41sublists = concatMap inits . tails 42sublists = concatMap inits . tails
43
44windows :: Int -> [a] -> [[a]]
45windows m = foldr (zipWith (:)) (repeat []) . take m . tails