summaryrefslogtreecommitdiffstats
path: root/day07
diff options
context:
space:
mode:
Diffstat (limited to 'day07')
-rw-r--r--day07/app/Main.hs28
1 files changed, 18 insertions, 10 deletions
diff --git a/day07/app/Main.hs b/day07/app/Main.hs
index 413fcca..223f7f7 100644
--- a/day07/app/Main.hs
+++ b/day07/app/Main.hs
@@ -121,6 +121,9 @@ Find the smallest directory that, if deleted, would free up enough space on the
run the update. What is the total size of that directory?
-}
{-# LANGUAGE DerivingStrategies #-}
+{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
+
+{-# HLINT ignore "Use 'foldl'' from Relude" #-}
module Main (main) where
@@ -154,12 +157,19 @@ data SystemEntry a = File a | Directory Text [SystemEntry a] deriving stock (Sho
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
+foldrFile :: Monoid b => (a -> b -> b) -> b -> SystemEntry a -> b
+foldrFile f b (File fd) = f fd b
+foldrFile f b (Directory _ xs) = mconcat $ fmap (foldrFile f b) xs
+
+foldrDirectory :: Monoid b => (a -> b -> b) -> b -> SystemEntry a -> [b]
+foldrDirectory _ _ (File _) = []
+foldrDirectory f b (Directory n xs) = b' : concatMap (foldrDirectory f mempty) xs
+ where
+ b' = foldrFile f b (Directory n xs)
+-- | Foldable over Files
instance Foldable SystemEntry where
- foldMap fam = foldrEntry (mappend . fam) mempty
+ foldMap fam = foldrFile (mappend . fam) mempty
parseInput :: FilePath -> ByteString -> Either ParseError [Queries]
parseInput = parse $ queries <* (eol <|> eof)
@@ -208,13 +218,8 @@ run (Directory n ses) (ChangeDir d : qs) = run (Directory n (ses' : ses)) 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
+getDirSizes = map getSum . foldrDirectory ((<>) . Sum. _size) (Sum 0)
runPart1 :: [Queries] -> Int
runPart1 = sum . filter (<= minSize) . getDirSizes . fst . run root . drop 1
@@ -228,6 +233,9 @@ runPart2 qs = minimum $ filter (>= requiredSpace - unusedSpace) $ getDirSizes sy
systemEntry :: SystemEntry FileData
systemEntry = fst $ run root $ drop 1 qs
+ getSize :: SystemEntry FileData -> Int
+ getSize = getSum . foldr ((<>) . Sum . _size) (Sum 0)
+
unusedSpace :: Int
unusedSpace = totalSpace - getSize systemEntry