summaryrefslogtreecommitdiffstats
path: root/day01/app/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'day01/app/Main.hs')
-rw-r--r--day01/app/Main.hs153
1 files changed, 151 insertions, 2 deletions
diff --git a/day01/app/Main.hs b/day01/app/Main.hs
index 65ae4a0..4525289 100644
--- a/day01/app/Main.hs
+++ b/day01/app/Main.hs
@@ -1,4 +1,153 @@
-module Main where
+{-
+--- Day 1: Calorie Counting ---
+
+Santa's reindeer typically eat regular reindeer food, but they need a lot of magical energy to
+deliver presents on Christmas. For that, their favourite snack is a special type of star fruit
+that only grows deep in the jungle. The Elves have brought you on their annual expedition to
+the grove where the fruit grows.
+
+To supply enough magical energy, the expedition needs to retrieve a minimum of fifty stars by
+December 25th. Although the Elves assure you that the grove has plenty of fruit, you decide to
+grab any fruit you see along the way, just in case.
+
+Collect stars by solving puzzles. Two puzzles will be made available on each day in the Advent
+calendar; the second puzzle is unlocked when you complete the first. Each puzzle grants one
+star. Good luck!
+
+The jungle must be too overgrown and difficult to navigate in vehicles or access from the air;
+the Elves' expedition traditionally goes on foot. As your boats approach land, the Elves begin
+taking inventory of their supplies. One important consideration is food - in particular, the
+number of Calories each Elf is carrying (your puzzle input).
+
+The Elves take turns writing down the number of Calories contained by the various meals,
+snacks, rations, etc. that they've brought with them, one item per line. Each Elf separates
+their own inventory from the previous Elf's inventory (if any) by a blank line.
+
+For example, suppose the Elves finish writing their items' Calories and end up with the
+following list:
+
+```
+1000
+2000
+3000
+
+4000
+
+5000
+6000
+
+7000
+8000
+9000
+
+10000
+```
+
+This list represents the Calories of the food carried by five Elves:
+
+ The first Elf is carrying food with 1000, 2000, and 3000 Calories, a total of 6000 Calories.
+ The second Elf is carrying one food item with 4000 Calories.
+ The third Elf is carrying food with 5000 and 6000 Calories, a total of 11000 Calories.
+ The fourth Elf is carrying food with 7000, 8000, and 9000 Calories, a total of 24000 Calories.
+ The fifth Elf is carrying one food item with 10000 Calories.
+
+In case the Elves get hungry and need extra snacks, they need to know which Elf to ask: they'd
+like to know how many Calories are being carried by the Elf carrying the most Calories. In the
+example above, this is 24000 (carried by the fourth Elf).
+
+Find the Elf carrying the most Calories. How many total Calories is that Elf carrying?
+
+--- Part Two ---
+
+By the time you calculate the answer to the Elves' question, they've already realized that the
+Elf carrying the most Calories of food might eventually run out of snacks.
+
+To avoid this unacceptable situation, the Elves would instead like to know the total Calories
+carried by the top three Elves carrying the most Calories. That way, even if one of those Elves
+runs out of snacks, they still have two backups.
+
+In the example above, the top three Elves are the fourth Elf (with 24000 Calories), then the
+third Elf (with 11000 Calories), then the fifth Elf (with 10000 Calories). The sum of the
+Calories carried by these three elves is 45000.
+
+Find the top three Elves carrying the most Calories. How many Calories are those Elves carrying
+in total?
+-}
+{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
+
+{-# HLINT ignore "Use readFileLBS" #-}
+module Main (main) where
+
+import Data.ByteString.Lazy (ByteString, readFile)
+import Data.Char (digitToInt)
+import Options.Applicative (Parser, ParserInfo, argument, execParser, fullDesc, help, helper, info, metavar, str)
+import Relude (Either (Left, Right), FilePath, IO, Int, Integer, String, Text, Type, concat, const, fmap, foldl', fst, map, max, pass, print, readFileText, return, reverse, show, snd, sort, sum, take, zip, ($), ($!), (*), (+), (.), (<), (<$>), (<*), (<*>), (<>), (<|>), (>), (>>), (>>=))
+import Relude.Print (putTextLn)
+import Relude.String.Conversion (toString)
+import Text.Parsec (ParseError, parse, (<?>))
+import Text.Parsec.ByteString.Lazy (GenParser)
+import Text.Parsec.Char (digit, string)
+import Text.Parsec.Combinator (eof, many1)
+import Text.Parsec.Prim (parsecMap, try)
+
+type Opts :: Type
+newtype Opts = Opts {_filename :: Text}
+
+options :: Parser Opts
+options = Opts <$> filename
+ where
+ filename :: Parser Text
+ filename = argument str $ metavar "filename" <> help "Input file"
+
+opts :: ParserInfo Opts
+opts = info (helper <*> options) fullDesc
+
+parseInput :: FilePath -> ByteString -> Either ParseError [[Int]]
+parseInput = parse parser
+
+parser :: GenParser t st [[Int]]
+parser = many1 block <* eof
+
+block :: GenParser t st [Int]
+block = many1 (int <* eol) <* (eol <|> eof)
+
+int :: GenParser t st Int
+int = foldl' (\a i -> a * 10 + digitToInt i) 0 <$> many1 digit
+
+eol :: GenParser t st ()
+eol =
+ parsecMap
+ (const ())
+ ( try (string "\n\r")
+ <|> try (string "\r\n")
+ <|> string "\n"
+ <|> string "\r"
+ <?> "end of line"
+ )
+
+-- imax :: (Int, Int) -> (Int, Int) -> (Int, Int)
+-- imax (aidx, asum) (idx, _sum) =
+-- if _sum > asum
+-- then (idx, _sum)
+-- else (aidx, asum)
+--
+-- run :: [[Int]] -> Int
+-- run = snd . foldl' imax (0, 0) . zip [1 ..] . map sum
+
+runPart1 :: [[Int]] -> Int
+runPart1 = foldl' max 0 . map sum
+
+runPart2 :: [[Int]] -> Int
+runPart2= sum . take 3 . reverse . sort . map sum
main :: IO ()
-main = putStrLn "Hello, Haskell!"
+main = do
+ fileName <- toString . _filename <$> execParser opts
+ rawInput <- readFile fileName
+ case parseInput fileName rawInput of
+ Left e -> do
+ putTextLn "Error parsing input:"
+ print e
+ Right r -> do
+ print $ runPart1 r
+ print $ runPart2 r