never executed always true always false
1 {-|
2 Module: Y2021.D01
3 Description: Advent of Code 2021 Day 01 Solutions.
4 License: MIT
5 Maintainer: @tylerjl
6
7 Solutions to the 2021 day 01 set of problems for <adventofcode.com>.
8 -}
9 module Y2021.D01 where
10
11 import Data.Attoparsec.Text
12 import Data.Either.Utils (fromRight)
13 import Data.Foldable (foldl')
14 import Data.Text (Text)
15
16 -- |First attempt at part a, not optimized.
17 part1A :: Text -> Int
18 part1A = stepwise . asInts
19
20 -- |Part a using high-level zip operations.
21 part1AZip :: Text -> Int
22 part1AZip = length . compareAdj . asInts
23
24 -- |Part a using simple recursion (maybe smaller big-O?)
25 part1ARecur :: Text -> Int
26 part1ARecur = go . asInts
27 where go (x:y:zs) = (if x < y then 1 else 0) + go (y:zs)
28 go _ = 0
29
30 -- |Part b first attempt, simple approach
31 part1B :: Text -> Int
32 part1B = stepwise . toWindows . asInts
33
34 -- |Part b using highl-elevel zips
35 part1BZip :: Text -> Int
36 part1BZip = length . compareAdj . map trisum . (zip3 <*> tail <*> tail . tail) . asInts
37
38 -- |Utility to transform a list into tuples of adjacent values.
39 compareAdj :: [Int] -> [(Int, Int)]
40 compareAdj = filter (uncurry (<)) . (zip <*> tail)
41
42 -- |Sum all values of a three-tuple
43 trisum :: Num a => (a, a, a) -> a
44 trisum (a, b, c) = a + b + c
45
46 -- |A fold sum of the structure for parsed values.
47 stepwise :: [Int] -> Int
48 stepwise = snd . foldl' steps (Nothing, 0)
49 where steps :: (Maybe Int, Int) -> Int -> (Maybe Int, Int)
50 steps (Nothing, acc) n = (Just n, acc)
51 steps (Just prev, acc) n
52 | prev < n = (Just n, succ acc)
53 | otherwise = (Just n, acc)
54
55 -- |Consolidate a list into a summed, shifting window.
56 toWindows :: [Int] -> [Int]
57 toWindows (w:x:y:zs) = (w+x+y) : toWindows (x:y:zs)
58 toWindows _ = []
59
60 -- |Unsafe-ish `Text` traversal to transform into a list of `Int`s.
61 asInts :: Text -> [Int]
62 asInts = fromRight . parseOnly parser
63 where
64 parser = decimal `sepBy1` endOfLine