summaryrefslogtreecommitdiffstats
path: root/day07/app/Main.hs
diff options
context:
space:
mode:
authorShivesh Mandalia <mail@shivesh.org>2023-02-05 01:32:03 +0000
committerShivesh Mandalia <mail@shivesh.org>2023-02-05 01:32:03 +0000
commit4cb3fa6de434d287bb46ca94c3026880164cb774 (patch)
tree38be4bcf69883777d7243b1d732c4ee8f184df30 /day07/app/Main.hs
parent21c330dcd6f9b873a37e04487a24ac21606c3aee (diff)
downloadAOC_2022_haskell-4cb3fa6de434d287bb46ca94c3026880164cb774.tar.gz
AOC_2022_haskell-4cb3fa6de434d287bb46ca94c3026880164cb774.zip
complete day 6 and 7
Diffstat (limited to 'day07/app/Main.hs')
-rw-r--r--day07/app/Main.hs259
1 files changed, 259 insertions, 0 deletions
diff --git a/day07/app/Main.hs b/day07/app/Main.hs
new file mode 100644
index 0000000..413fcca
--- /dev/null
+++ b/day07/app/Main.hs
@@ -0,0 +1,259 @@
+{-
+--- Day 7: No Space Left On Device ---
+You can hear birds chirping and raindrops hitting leaves as the expedition proceeds.
+Occasionally, you can even hear much louder sounds in the distance; how big do the
+animals get out here, anyway?
+The device the Elves gave you has problems with more than just its communication system. You
+try to run a system update:
+```
+\$ system-update --please --pretty-please-with-sugar-on-top
+Error: No space left on device
+```
+Perhaps you can delete some files to make space for the update?
+You browse around the filesystem to assess the situation and save the resulting terminal output
+(your puzzle input). For example:
+```
+\$ cd /
+\$ ls
+dir a
+14848514 b.txt
+8504156 c.dat
+dir d
+\$ cd a
+\$ ls
+dir e
+29116 f
+2557 g
+62596 h.lst
+\$ cd e
+\$ ls
+584 i
+\$ cd ..
+\$ cd ..
+\$ cd d
+\$ ls
+4060174 j
+8033020 d.log
+5626152 d.ext
+7214296 k
+```
+The filesystem consists of a tree of files (plain data) and directories (which can contain
+other directories or files). The outermost directory is called /. You can navigate around the
+filesystem, moving into or out of directories and listing the contents of the directory you're
+currently in.
+Within the terminal output, lines that begin with $ are commands you executed, very much like
+some modern computers:
+ cd means change directory. This changes which directory is the current directory, but the
+ specific result depends on the argument:
+ cd x moves in one level: it looks in the current directory for the directory named x
+ and makes it the current directory.
+ cd .. moves out one level: it finds the directory that contains the current directory,
+ then makes that directory the current directory.
+ cd / switches the current directory to the outermost directory, /.
+ ls means list. It prints out all of the files and directories immediately contained by the
+ current directory:
+ 123 abc means that the current directory contains a file named abc with size 123.
+ dir xyz means that the current directory contains a directory named xyz.
+Given the commands and output in the example above, you can determine that the filesystem looks
+visually like this:
+```
+- / (dir)
+ - a (dir)
+ - e (dir)
+ - i (file, size=584)
+ - f (file, size=29116)
+ - g (file, size=2557)
+ - h.lst (file, size=62596)
+ - b.txt (file, size=14848514)
+ - c.dat (file, size=8504156)
+ - d (dir)
+ - j (file, size=4060174)
+ - d.log (file, size=8033020)
+ - d.ext (file, size=5626152)
+ - k (file, size=7214296)
+```
+Here, there are four directories: / (the outermost directory), a and d (which are in /), and e
+(which is in a). These directories also contain files of various sizes.
+Since the disk is full, your first step should probably be to find directories that are good
+candidates for deletion. To do this, you need to determine the total size of each directory.
+The total size of a directory is the sum of the sizes of the files it contains, directly or
+indirectly. (Directories themselves do not count as having any intrinsic size.)
+The total sizes of the directories above can be found as follows:
+ The total size of directory e is 584 because it contains a single file i of size 584 and no
+ other directories.
+ The directory a has total size 94853 because it contains files f (size 29116), g (size
+ 2557), and h.lst (size 62596), plus file i indirectly (a contains e which contains i).
+ Directory d has total size 24933642.
+ As the outermost directory, / contains every file. Its total size is 48381165, the sum of
+ the size of every file.
+To begin, find all of the directories with a total size of at most 100000, then calculate the
+sum of their total sizes. In the example above, these directories are a and e; the sum of
+their total sizes is 95437 (94853 + 584). (As in this example, this process can count files
+more than once!)
+Find all of the directories with a total size of at most 100000. What is the sum of the total
+sizes of those directories?
+
+--- Part Two ---
+
+Now, you're ready to choose a directory to delete.
+
+The total disk space available to the filesystem is 70000000. To run the update, you need
+unused space of at least 30000000. You need to find a directory you can delete that will free
+up enough space to run the update.
+
+In the example above, the total size of the outermost directory (and thus the total amount of
+used space) is 48381165; this means that the size of the unused space must currently be
+21618835, which isn't quite the 30000000 required by the update. Therefore, the update still
+requires a directory with total size of at least 8381165 to be deleted before it can run.
+
+To achieve this, you have the following options:
+
+ Delete directory e, which would increase unused space by 584.
+ Delete directory a, which would increase unused space by 94853.
+ Delete directory d, which would increase unused space by 24933642.
+ Delete directory /, which would increase unused space by 48381165.
+
+Directories e and a are both too small; deleting them would not free up enough space. However,
+directories d and / are both big enough! Between these, choose the smallest: d, increasing
+unused space by 24933642.
+
+Find the smallest directory that, if deleted, would free up enough space on the filesystem to
+run the update. What is the total size of that directory?
+-}
+{-# LANGUAGE DerivingStrategies #-}
+
+module Main (main) where
+
+import Data.ByteString.Lazy (ByteString)
+import Data.Char (digitToInt)
+import Data.Foldable
+import Data.List (filter)
+import Options.Applicative (Parser, ParserInfo, argument, execParser, fullDesc, help, helper, info, metavar, str)
+import Relude hiding (ByteString, elem, empty, filter, fromList, length, null, optional, readFile, splitAt, sum)
+import Text.Parsec (ParseError, parse, (<?>))
+import Text.Parsec.ByteString.Lazy (GenParser)
+import Text.Parsec.Char (anyChar, char, digit, string)
+import Text.Parsec.Combinator (eof, many1, manyTill)
+import Text.Parsec.Prim (parsecMap, try)
+
+type Opts :: Type
+newtype Opts = Opts {_filename :: Text} deriving stock (Show)
+
+type FileData :: Type
+data FileData = FileData {_name :: Text, _size :: Int} deriving stock (Show)
+
+type ParseDirOrFile :: Type
+data ParseDirOrFile = ParseDir | ParseFile FileData
+
+type Queries :: Type
+data Queries = ChangeDir Text | List [FileData] deriving stock (Show)
+
+type SystemEntry :: Type -> Type
+data SystemEntry a = File a | Directory Text [SystemEntry a] deriving stock (Show)
+
+root :: SystemEntry FileData
+root = Directory "/" []
+
+foldrEntry :: Monoid b => (a -> b -> b) -> b -> SystemEntry a -> b
+foldrEntry f b (File fd) = f fd b
+foldrEntry f b (Directory _ xs) = mconcat $ fmap (foldrEntry f b) xs
+
+instance Foldable SystemEntry where
+ foldMap fam = foldrEntry (mappend . fam) mempty
+
+parseInput :: FilePath -> ByteString -> Either ParseError [Queries]
+parseInput = parse $ queries <* (eol <|> eof)
+ where
+ queries :: GenParser t st [Queries]
+ queries = many1 (cd <|> ls)
+
+ cd :: GenParser t st Queries
+ cd = ChangeDir <$> (try (string "$ cd ") *> (toText <$> manyTill anyChar (eol <|> eof)))
+
+ ls :: GenParser t st Queries
+ ls = List . filterDir <$> ((try (string "$ ls") *> (eol <|> eof)) *> many1 (dir <|> file))
+
+ dir :: GenParser t st ParseDirOrFile
+ dir = ParseDir <$ try (string "dir ") <* manyTill anyChar (eol <|> eof)
+
+ file :: GenParser t st ParseDirOrFile
+ file = ParseFile <$> (flip FileData <$> (int <* char ' ') <*> (toText <$> manyTill anyChar (eol <|> eof)))
+
+ filterDir :: [ParseDirOrFile] -> [FileData]
+ filterDir [] = []
+ filterDir (ParseDir : xs) = filterDir xs
+ filterDir ((ParseFile fd) : xs) = fd : filterDir xs
+
+ 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"
+ )
+
+run :: SystemEntry FileData -> [Queries] -> (SystemEntry FileData, [Queries])
+run se [] = (se, [])
+run (Directory n ses) (ChangeDir ".." : qs) = (Directory n ses, qs)
+run (Directory n ses) (ChangeDir d : qs) = run (Directory n (ses' : ses)) qs'
+ where
+ ses' :: SystemEntry FileData
+ (ses', qs') = run (Directory d []) qs
+run (Directory n ses) (List fd : qs) = run (Directory n (fmap File fd ++ ses)) qs
+run _ _ = error "invalid operation"
+
+getSize :: SystemEntry FileData -> Int
+getSize = getSum . foldr ((<>) . Sum . _size) (Sum 0)
+
+getDirSizes :: SystemEntry FileData -> [Int]
+getDirSizes (File _) = []
+getDirSizes (Directory n ses) =
+ getSize (Directory n ses) : foldl (\a d -> a ++ getDirSizes d) [] ses
+
+runPart1 :: [Queries] -> Int
+runPart1 = sum . filter (<= minSize) . getDirSizes . fst . run root . drop 1
+ where
+ minSize :: Int
+ minSize = 100000
+
+runPart2 :: [Queries] -> Int
+runPart2 qs = minimum $ filter (>= requiredSpace - unusedSpace) $ getDirSizes systemEntry
+ where
+ systemEntry :: SystemEntry FileData
+ systemEntry = fst $ run root $ drop 1 qs
+
+ unusedSpace :: Int
+ unusedSpace = totalSpace - getSize systemEntry
+
+ requiredSpace :: Int
+ requiredSpace = 30000000
+
+ totalSpace :: Int
+ totalSpace = 70000000
+
+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
+ where
+ opts :: ParserInfo Opts
+ opts = info (helper <*> options) fullDesc
+
+ options :: Parser Opts
+ options = Opts <$> filename
+
+ filename :: Parser Text
+ filename = argument str $ metavar "filename" <> help "Input file"