{-# LANGUAGE OverloadedStrings #-} import qualified Data.Text as T import Data.Char (isSpace) import Data.List (uncons, nub, isPrefixOf) import GHC.Data.Maybe (mapMaybe) evaluateCD :: [String] -> String -> [String] evaluateCD dir command = case cdTo of ".." -> init dir "/" -> [] d -> dir ++ [d] where cdTo = words command !! 1 evaluateLS :: [String] -> [([String], Int)] -> [String] -> [([String], Int)] evaluateLS dir files cr = files ++ map (\[size, file] -> (dir ++ [file], read size)) onlyFiles where onlyFiles = filter (\[h,_] -> h /= "dir") splitFiles splitFiles = map words cr evaluateCommand :: [String] -> [([String], Int)] -> (String, [String]) -> ([String], [([String], Int)]) evaluateCommand dir files (c, cr) = case head $ words $ c of "cd" -> (evaluateCD dir c, files) "ls" -> (dir, evaluateLS dir files cr) c -> error $ "Unknown command: " ++ c -- takes in a starting directory, a list of files, and a sequence of commands, and evaluates them, -- returning the a list of tuples representing the filepath and the filesize evaluateCommands :: [String] -> [([String], Int)] -> [(String, [String])] -> [([String], Int)] evaluateCommands dir files (c:xs) = evaluateCommands newDir newFiles xs where (newDir, newFiles) = evaluateCommand dir files c evaluateCommands dir files [] = files getAllPossibleDirectoriesOfPath :: [String] -> [[String]] getAllPossibleDirectoriesOfPath [] = [[]] getAllPossibleDirectoriesOfPath p = p : getAllPossibleDirectoriesOfPath (init p) filterByListPrefix :: [String] -> [[String]] -> [[String]] filterByListPrefix prefix = filter (`elem` decomposedPrefix) where decomposedPrefix = getAllPossibleDirectoriesOfPath prefix -- takes in a list of filepaths, and transforms them into a deduplicated list of only the -- directories those files are stored in getDirectories :: [[String]] -> [[String]] getDirectories = nub . concatMap (getAllPossibleDirectoriesOfPath . init) fromFileSizesToPaths :: [([String], Int)] -> [[String]] fromFileSizesToPaths = map fst calculateDirSize :: [[String]] -> [([String], Int)] -> [String] -> Int calculateDirSize dirs files dir = sum $ map snd justFiles where justFiles = filter (isPrefixOf dir . fst) files getDirectorySums f = map (calculateDirSize (getDirectories $ fromFileSizesToPaths f) f) (getDirectories $ fromFileSizesToPaths f) main = interact $ show . sum . filter (<= 100000) . getDirectorySums . evaluateCommands [] [] . mapMaybe (uncons . lines . dropWhile isSpace) . takeWhile (not . null) . dropWhile null . map T.unpack . T.splitOn "$" . T.pack