summaryrefslogtreecommitdiffstats
path: root/day03/app
diff options
context:
space:
mode:
authorShivesh Mandalia <mail@shivesh.org>2023-01-21 22:58:00 +0000
committerShivesh Mandalia <mail@shivesh.org>2023-01-21 22:58:00 +0000
commit5bcfb4a05124116d374c5b6696f52599de2f47f1 (patch)
tree24196a68ac13fc4ac26119a02bae3ede2199fea9 /day03/app
parent49400fd9a4e25a26a5a7c833983971de75542648 (diff)
downloadAOC_2022_haskell-5bcfb4a05124116d374c5b6696f52599de2f47f1.tar.gz
AOC_2022_haskell-5bcfb4a05124116d374c5b6696f52599de2f47f1.zip
complete day 3
Diffstat (limited to 'day03/app')
-rw-r--r--day03/app/Main.hs194
1 files changed, 194 insertions, 0 deletions
diff --git a/day03/app/Main.hs b/day03/app/Main.hs
new file mode 100644
index 0000000..6584c4a
--- /dev/null
+++ b/day03/app/Main.hs
@@ -0,0 +1,194 @@
+{-
+-- Day 3: Rucksack Reorganization ---
+
+One Elf has the important job of loading all of the rucksacks with supplies for the jungle
+journey. Unfortunately, that Elf didn't quite follow the packing instructions, and so a few
+items now need to be rearranged.
+
+Each rucksack has two large compartments. All items of a given type are meant to go into
+exactly one of the two compartments. The Elf that did the packing failed to follow this rule
+for exactly one item type per rucksack.
+
+The Elves have made a list of all of the items currently in each rucksack (your puzzle input),
+but they need your help finding the errors. Every item type is identified by a single lowercase
+or uppercase letter (that is, a and A refer to different types of items).
+
+The list of items for each rucksack is given as characters all on a single line. A given
+rucksack always has the same number of items in each of its two compartments, so the first half
+of the characters represent items in the first compartment, while the second half of the
+characters represent items in the second compartment.
+
+For example, suppose you have the following list of contents from six rucksacks:
+
+```
+vJrwpWtwJgWrhcsFMMfFFhFp
+jqHRNqRjqzjGDLGLrsFMfFZSrLrFZsSL
+PmmdzqPrVvPwwTWBwg
+wMqvLMZHhHMvwLHjbvcjnnSBnvTQFn
+ttgJtRGJQctTZtZT
+CrZsJsPPZsGzwwsLwLmpwMDw
+```
+
+ The first rucksack contains the items vJrwpWtwJgWrhcsFMMfFFhFp, which means its first
+ compartment contains the items vJrwpWtwJgWr, while the second compartment contains the
+ items hcsFMMfFFhFp. The only item type that appears in both compartments is lowercase p.
+ The second rucksack's compartments contain jqHRNqRjqzjGDLGL and rsFMfFZSrLrFZsSL. The only
+ item type that appears in both compartments is uppercase L.
+ The third rucksack's compartments contain PmmdzqPrV and vPwwTWBwg; the only common item
+ type is uppercase P.
+ The fourth rucksack's compartments only share item type v.
+ The fifth rucksack's compartments only share item type t.
+ The sixth rucksack's compartments only share item type s.
+
+To help prioritize item rearrangement, every item type can be converted to a priority:
+
+ Lowercase item types a through z have priorities 1 through 26.
+ Uppercase item types A through Z have priorities 27 through 52.
+
+In the above example, the priority of the item type that appears in both compartments of each
+rucksack is 16 (p), 38 (L), 42 (P), 22 (v), 20 (t), and 19 (s); the sum of these is 157.
+
+Find the item type that appears in both compartments of each rucksack. What is the sum of the
+priorities of those item types?
+
+--- Part Two ---
+
+As you finish identifying the misplaced items, the Elves come to you with another issue.
+
+For safety, the Elves are divided into groups of three. Every Elf carries a badge that
+identifies their group. For efficiency, within each group of three Elves, the badge is the
+only item type carried by all three Elves. That is, if a group's badge is item type B, then
+all three Elves will have item type B somewhere in their rucksack, and at most two of the Elves
+will be carrying any other item type.
+
+The problem is that someone forgot to put this year's updated authenticity sticker on the
+badges. All of the badges need to be pulled out of the rucksacks so the new authenticity
+stickers can be attached.
+
+Additionally, nobody wrote down which item type corresponds to each group's badges. The only
+way to tell which item type is the right one is by finding the one item type that is common
+between all three Elves in each group.
+
+Every set of three lines in your list corresponds to a single group, but each group can have a
+different badge item type. So, in the above example, the first group's rucksacks are the first
+three lines:
+
+```
+vJrwpWtwJgWrhcsFMMfFFhFp
+jqHRNqRjqzjGDLGLrsFMfFZSrLrFZsSL
+PmmdzqPrVvPwwTWBwg
+```
+
+And the second group's rucksacks are the next three lines:
+
+```
+wMqvLMZHhHMvwLHjbvcjnnSBnvTQFn
+ttgJtRGJQctTZtZT
+CrZsJsPPZsGzwwsLwLmpwMDw
+```
+
+In the first group, the only item type that appears in all three rucksacks is lowercase r; this
+must be their badges. In the second group, their badge item type must be Z.
+
+Priorities for these items must still be found to organize the sticker attachment efforts:
+here, they are 18 (r) for the first group and 52 (Z) for the second group. The sum of these is
+70.
+
+Find the item type that corresponds to the badges of each three-Elf group. What is the sum of
+the priorities of those item types?
+-}
+{-# LANGUAGE DerivingStrategies #-}
+
+module Main (main) where
+
+import Data.ByteString.Lazy (ByteString)
+import Data.Char (isLower, isUpper)
+import Data.Text (elem, filter, index, length, splitAt)
+import Data.Foldable (foldl1)
+import Options.Applicative (Parser, ParserInfo, argument, execParser, fullDesc, help, helper, info, metavar, str)
+import Relude hiding (ByteString, elem, empty, filter, length, readFile, splitAt)
+import Text.Parsec (ParseError, parse, (<?>))
+import Text.Parsec.ByteString.Lazy (GenParser)
+import Text.Parsec.Char (letter, 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 [Text]
+parseInput = parse parser
+
+eol :: GenParser t st ()
+eol =
+ parsecMap
+ (const ())
+ ( try (string "\n\r")
+ <|> try (string "\r\n")
+ <|> string "\n"
+ <|> string "\r"
+ <?> "end of line"
+ )
+
+parser :: GenParser t st [Text]
+parser = many1 block <* eof
+
+block :: GenParser t st Text
+block = toText <$> many1 letter <* (eol <|> eof)
+
+halve :: Text -> (Text, Text)
+halve xs = splitAt (length xs `div` 2) xs
+
+intersection :: Text -> Text -> Text
+intersection xs ys = filter (`elem` ys) xs
+
+getItem :: Text -> Char
+getItem x = intersection lhs rhs `index` 0
+ where
+ (lhs, rhs) = halve x
+
+toPriority :: Char -> Int
+toPriority x
+ | isLower x = ord x - ord 'a' + 1
+ | isUpper x = ord x - ord 'A' + 27
+ | otherwise = error "unrecognized character"
+
+runPart1 :: [Text] -> Int
+runPart1 = sum . map (toPriority . getItem)
+
+chunksOf :: Int -> [a] -> [[a]]
+chunksOf n xs
+ | n <= 0 = error "The number of elements per chunk must be greater than 0"
+ | otherwise = chunks xs
+ where
+ chunks :: [a] -> [[a]]
+ chunks [] = []
+ chunks ys = take n ys : chunks (drop n ys)
+
+commonItem :: [Text] -> Text
+commonItem [] = error "Chunk length must be greater than 0"
+commonItem xs = foldl1 intersection xs
+
+runPart2 :: [Text] -> Int
+runPart2 xs = sum $ map (toPriority . (`index` 0) . commonItem) (chunksOf 3 xs)
+
+main :: IO ()
+main = do
+ fileName <- toString . _filename <$> execParser opts
+ rawInput <- readFileLBS fileName
+ case parseInput fileName rawInput of
+ Left e -> do
+ putTextLn "Error parsing input:"
+ print e
+ Right r -> do
+ print $ runPart1 r
+ print $ runPart2 r