git-annex/Utility/Directory.hs

100 lines
3.1 KiB
Haskell
Raw Normal View History

{- directory traversal and manipulation
-
2020-03-05 17:56:39 +00:00
- Copyright 2011-2020 Joey Hess <id@joeyh.name>
-
- License: BSD-2-clause
-}
{-# LANGUAGE CPP #-}
2020-03-05 17:56:39 +00:00
{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Directory (
module Utility.Directory,
module Utility.SystemDirectory
) where
2011-12-09 05:57:13 +00:00
import Control.Monad
2012-03-11 22:12:36 +00:00
import System.FilePath
import System.PosixCompat.Files hiding (removeLink)
2012-03-11 22:12:36 +00:00
import Control.Applicative
2012-05-31 23:25:33 +00:00
import System.IO.Unsafe (unsafeInterleaveIO)
import Data.Maybe
import Prelude
import Utility.SystemDirectory
import Utility.Exception
2012-04-22 03:32:33 +00:00
import Utility.Monad
import Utility.Applicative
2012-05-31 23:25:33 +00:00
dirCruft :: FilePath -> Bool
dirCruft "." = True
dirCruft ".." = True
dirCruft _ = False
2012-03-11 22:12:36 +00:00
{- Lists the contents of a directory.
- Unlike getDirectoryContents, paths are not relative to the directory. -}
dirContents :: FilePath -> IO [FilePath]
2012-05-31 23:25:33 +00:00
dirContents d = map (d </>) . filter (not . dirCruft) <$> getDirectoryContents d
2012-06-18 16:53:57 +00:00
{- Gets files in a directory, and then its subdirectories, recursively,
- and lazily.
-
- Does not follow symlinks to other subdirectories.
-
- When the directory does not exist, no exception is thrown,
- instead, [] is returned. -}
2012-05-31 23:25:33 +00:00
dirContentsRecursive :: FilePath -> IO [FilePath]
2014-04-26 23:25:05 +00:00
dirContentsRecursive = dirContentsRecursiveSkipping (const False) True
2012-05-31 23:25:33 +00:00
2013-10-07 17:03:05 +00:00
{- Skips directories whose basenames match the skipdir. -}
dirContentsRecursiveSkipping :: (FilePath -> Bool) -> Bool -> FilePath -> IO [FilePath]
dirContentsRecursiveSkipping skipdir followsubdirsymlinks topdir = go [topdir]
2012-12-13 04:24:19 +00:00
where
go [] = return []
2013-10-05 19:36:09 +00:00
go (dir:dirs)
2013-10-07 17:03:05 +00:00
| skipdir (takeFileName dir) = go dirs
2013-10-05 19:36:09 +00:00
| otherwise = unsafeInterleaveIO $ do
(files, dirs') <- collect [] []
=<< catchDefaultIO [] (dirContents dir)
files' <- go (dirs' ++ dirs)
return (files ++ files')
2012-12-13 04:24:19 +00:00
collect files dirs' [] = return (reverse files, reverse dirs')
collect files dirs' (entry:entries)
| dirCruft entry = collect files dirs' entries
| otherwise = do
2013-12-18 19:20:26 +00:00
let skip = collect (entry:files) dirs' entries
let recurse = collect files (entry:dirs') entries
ms <- catchMaybeIO $ getSymbolicLinkStatus entry
case ms of
2013-12-18 19:20:26 +00:00
(Just s)
| isDirectory s -> recurse
| isSymbolicLink s && followsubdirsymlinks ->
ifM (doesDirectoryExist entry)
( recurse
, skip
)
_ -> skip
2012-03-11 22:12:36 +00:00
{- Gets the directory tree from a point, recursively and lazily,
- with leaf directories **first**, skipping any whose basenames
- match the skipdir. Does not follow symlinks. -}
dirTreeRecursiveSkipping :: (FilePath -> Bool) -> FilePath -> IO [FilePath]
dirTreeRecursiveSkipping skipdir topdir = go [] [topdir]
where
go c [] = return c
go c (dir:dirs)
| skipdir (takeFileName dir) = go c dirs
| otherwise = unsafeInterleaveIO $ do
subdirs <- go []
=<< filterM (isDirectory <$$> getSymbolicLinkStatus)
=<< catchDefaultIO [] (dirContents dir)
go (subdirs++dir:c) dirs
{- Use with an action that removes something, which may or may not exist.
2012-06-06 17:13:13 +00:00
-
- If an exception is thrown due to it not existing, it is ignored.
-}
removeWhenExistsWith :: (a -> IO ()) -> a -> IO ()
removeWhenExistsWith f a = void $ tryWhenExists $ f a