Skip to content
Snippets Groups Projects
Commit 61019ecd authored by Arjun Kathuria's avatar Arjun Kathuria :rocket:
Browse files

Adds reporting remaining leftover files sorted by Depth.

parent bed06d13
No related branches found
No related tags found
1 merge request!101[WIP] Feature "nuke"
......@@ -1437,10 +1437,22 @@ rmGhcupDirs = do
reportRemainingFiles ghcupDir = do
remainingFiles <- liftIO $ getDirectoryContentsRecursive ghcupDir
remainingFilesAbsolute <- makePathsAbsolute remainingFiles
let normalizedFilePaths = fmap normalise remainingFiles
let sortedByDepthRemainingFiles = reverse $ sortBy compareFn normalizedFilePaths
remainingFilesAbsolute <- makePathsAbsolute sortedByDepthRemainingFiles
pure remainingFilesAbsolute
makePathsAbsolute paths = liftIO $ traverse makeAbsolute paths
where
calcDepth :: FilePath -> Int
calcDepth = length . filter isPathSeparator
compareFn :: FilePath -> FilePath -> Ordering
compareFn fp1 fp2 = compare (calcDepth fp1) (calcDepth fp2)
makePathsAbsolute :: (MonadIO m) => [FilePath] -> m [FilePath]
makePathsAbsolute paths = liftIO $
traverse (makeAbsolute . normalise) paths
-- we expect only files inside cache/log dir
-- we report remaining files/dirs later,
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment