Skip to content

Commit

Permalink
WIP: removePathForcibly
Browse files Browse the repository at this point in the history
OUTSTANDING ISSUES:
- No Windows support
  • Loading branch information
Rufflewind committed Jul 5, 2024
1 parent b9b2cda commit aaf9cf7
Show file tree
Hide file tree
Showing 5 changed files with 146 additions and 36 deletions.
6 changes: 2 additions & 4 deletions System/Directory/Internal/C_utimensat.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ module System.Directory.Internal.C_utimensat where
import Prelude ()
import System.Directory.Internal.Prelude
import Data.Time.Clock.POSIX (POSIXTime)
import qualified System.Posix as Posix

data CTimeSpec = CTimeSpec EpochTime CLong

Expand All @@ -29,9 +30,6 @@ instance Storable CTimeSpec where
nsec <- #{peek struct timespec, tv_nsec} p
return (CTimeSpec sec nsec)

c_AT_FDCWD :: CInt
c_AT_FDCWD = (#const AT_FDCWD)

utimeOmit :: CTimeSpec
utimeOmit = CTimeSpec (CTime 0) (#const UTIME_OMIT)

Expand All @@ -42,6 +40,6 @@ toCTimeSpec t = CTimeSpec (CTime sec) (truncate $ 10 ^ (9 :: Int) * frac)
(sec', frac') = properFraction (toRational t)

foreign import capi "sys/stat.h utimensat" c_utimensat
:: CInt -> CString -> Ptr CTimeSpec -> CInt -> IO CInt
:: Posix.Fd -> CString -> Ptr CTimeSpec -> CInt -> IO CInt

#endif
4 changes: 4 additions & 0 deletions System/Directory/Internal/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,10 @@ tryIOErrorType check action = do
Left err -> if check err then pure (Left err) else throwIO err
Right val -> pure (Right val)

ignoreDoesNotExistError :: IO () -> IO ()
ignoreDoesNotExistError action =
() <$ tryIOErrorType isDoesNotExistError action

-- | Attempt to perform the given action, silencing any IO exception thrown by
-- it.
ignoreIOExceptions :: IO () -> IO ()
Expand Down
101 changes: 99 additions & 2 deletions System/Directory/Internal/Posix.hsc
Original file line number Diff line number Diff line change
@@ -1,9 +1,14 @@
{-# LANGUAGE CApiFFI #-}
module System.Directory.Internal.Posix where
#include <HsDirectoryConfig.h>
#if !defined(mingw32_HOST_OS)
#include <fcntl.h>
#ifdef HAVE_LIMITS_H
# include <limits.h>
#endif
#ifdef HAVE_SYS_STAT_H
# include <sys/stat.h>
#endif
import Prelude ()
import System.Directory.Internal.Prelude
#ifdef HAVE_UTIMENSAT
Expand All @@ -17,16 +22,36 @@ import System.OsPath ((</>), isRelative, splitSearchPath)
import System.OsString.Internal.Types (OsString(OsString, getOsString))
import qualified Data.Time.Clock.POSIX as POSIXTime
import qualified System.OsPath.Internal as OsPath
import qualified System.Posix.Directory.Fd as Posix
import qualified System.Posix.Directory.PosixPath as Posix
import qualified System.Posix.Env.PosixString as Posix
import qualified System.Posix.Files as Posix (FileStatus(..))
import qualified System.Posix.Files.PosixString as Posix
import qualified System.Posix.Internals as Posix (CStat)
import qualified System.Posix.IO.PosixString as Posix
import qualified System.Posix.PosixPath.FilePath as Posix
import qualified System.Posix.Types as Posix
import qualified System.Posix.User.ByteString as Posix

createDirectoryInternal :: OsPath -> IO ()
createDirectoryInternal (OsString path) = Posix.createDirectory path 0o777

c_AT_FDCWD :: Posix.Fd
c_AT_FDCWD = Posix.Fd (#const AT_FDCWD)

foreign import ccall "unistd.h unlinkat" c_unlinkat
:: Posix.Fd -> CString -> CInt -> IO CInt

removePathAt :: FileType -> Maybe FileRef -> OsPath -> IO ()
removePathAt fType dirRef (OsString path) =
Posix.withFilePath path $ \ pPath -> do
Posix.throwErrnoPathIfMinus1_ "unlinkat" path
(c_unlinkat (fromMaybe c_AT_FDCWD dirRef) pPath flag)
pure ()
where
flag | fileTypeIsDirectory fType = (#const AT_REMOVEDIR)
| otherwise = 0

removePathInternal :: Bool -> OsPath -> IO ()
removePathInternal True = Posix.removeDirectory . getOsString
removePathInternal False = Posix.removeLink . getOsString
Expand Down Expand Up @@ -101,9 +126,13 @@ exeExtensionInternal :: OsString
exeExtensionInternal = exeExtension

getDirectoryContentsInternal :: OsPath -> IO [OsPath]
getDirectoryContentsInternal (OsString path) =
getDirectoryContentsInternal path =
withFileRef Nothing path getDirectoryContentsRef

getDirectoryContentsRef :: FileRef -> IO [OsPath]
getDirectoryContentsRef fileRef =
bracket
(Posix.openDirStream path)
(Posix.unsafeOpenDirStreamFd =<< Posix.dup fileRef)
Posix.closeDirStream
start
where
Expand Down Expand Up @@ -151,8 +180,62 @@ createSymbolicLink _ (OsString p1) (OsString p2) =
readSymbolicLink :: OsPath -> IO OsPath
readSymbolicLink = (OsString <$>) . Posix.readSymbolicLink . getOsString

defaultFlags :: Posix.OpenFileFlags
defaultFlags =
Posix.defaultFileFlags
{ Posix.noctty = True
, Posix.nonBlock = True
, Posix.cloexec = True
}

type FileRef = Posix.Fd

withFileRef :: Maybe FileRef -> OsPath -> (FileRef -> IO r) -> IO r
withFileRef dirRef (OsString name) =
bracket
(Posix.openFdAt dirRef name Posix.ReadOnly defaultFlags)
Posix.closeFd

data Subref = NotSubdir -- ^ Not a directory (perhaps regular file or symlink).
| SubdirRef FileRef deriving (Show) -- ^ Is a subdirectory.

openSubref :: Maybe FileRef -> OsPath -> IO Subref
openSubref dirRef (OsString name) = do
let flags = defaultFlags { Posix.nofollow = True, Posix.directory = True }
result <- tryIOError (Posix.openFdAt dirRef name Posix.ReadOnly flags)
case result of
Left err -> do
errno <- getErrno
if errno == eLOOP || errno == eNOTDIR
then pure NotSubdir
else throwIO err
Right ref -> pure (SubdirRef ref)

closeSubref :: Subref -> IO ()
closeSubref NotSubdir = pure ()
closeSubref (SubdirRef ref) = Posix.closeFd ref

withSubref :: Maybe FileRef -> OsPath -> (Subref -> IO r) -> IO r
withSubref dirRef name action =
bracket (openSubref dirRef name) closeSubref action

type Metadata = Posix.FileStatus

foreign import capi "sys/stat.h fstatat" c_fstatat
:: Posix.Fd -> CString -> Ptr Posix.CStat -> CInt -> IO CInt

c_AT_SYMLINK_NOFOLLOW :: CInt
c_AT_SYMLINK_NOFOLLOW = (#const AT_SYMLINK_NOFOLLOW)

getSymbolicLinkMetadataAt :: Maybe FileRef -> OsPath -> IO Metadata
getSymbolicLinkMetadataAt dirRef (OsString path) =
Posix.withFilePath path $ \ pPath -> do
stat <- mallocForeignPtrBytes (#const sizeof(struct stat))
withForeignPtr stat $ \ pStat -> do
Posix.throwErrnoPathIfMinus1_ "fstatat" path $ do
c_fstatat (fromMaybe c_AT_FDCWD dirRef) pPath pStat c_AT_SYMLINK_NOFOLLOW
pure (Posix.FileStatus stat)

getSymbolicLinkMetadata :: OsPath -> IO Metadata
getSymbolicLinkMetadata = Posix.getSymbolicLinkStatus . getOsString

Expand Down Expand Up @@ -197,6 +280,20 @@ setWriteMode :: Bool -> Mode -> Mode
setWriteMode False m = m .&. complement allWriteMode
setWriteMode True m = m .|. allWriteMode

foreign import capi "sys/stat.h fchmodat" c_fchmodat
:: Posix.Fd -> CString -> Posix.FileMode -> CInt -> IO CInt

setSymbolicLinkModeAt :: Maybe FileRef -> OsPath -> Posix.FileMode -> IO ()
setSymbolicLinkModeAt dirRef (OsString path) mode = do
Posix.withFilePath path $ \ pPath ->
Posix.throwErrnoPathIfMinus1_ "fchmodat" path
(c_fchmodat (fromMaybe c_AT_FDCWD dirRef) pPath mode c_AT_SYMLINK_NOFOLLOW)

forceRemovable :: Maybe FileRef -> OsPath -> Metadata -> IO ()
forceRemovable dirRef path metadata = do
let mode = modeFromMetadata metadata .|. Posix.ownerModes
setSymbolicLinkModeAt dirRef path mode

setFileMode :: OsPath -> Mode -> IO ()
setFileMode = Posix.setFileMode . getOsString

Expand Down
7 changes: 6 additions & 1 deletion System/Directory/Internal/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -80,11 +80,13 @@ import Foreign
, allocaArray
, allocaBytes
, allocaBytesAligned
, mallocForeignPtrBytes
, maybeWith
, nullPtr
, plusPtr
, with
, withArray
, withForeignPtr
)
import Foreign.C
( CInt(..)
Expand All @@ -96,6 +98,9 @@ import Foreign.C
, CUShort(..)
, CWString
, CWchar(..)
, eLOOP
, eNOTDIR
, getErrno
, throwErrnoIfMinus1Retry_
, throwErrnoIfMinus1_
, throwErrnoIfNull
Expand Down Expand Up @@ -145,5 +150,5 @@ import System.IO.Error
, tryIOError
, userError
)
import System.Posix.Types (EpochTime)
import System.Posix.Types (CMode, EpochTime)
import System.Timeout (timeout)
64 changes: 35 additions & 29 deletions System/Directory/OsPath.hs
Original file line number Diff line number Diff line change
Expand Up @@ -441,6 +441,30 @@ removeContentsRecursive path =
for_ [path </> x | x <- cont] removePathRecursive
removeDirectory path

forceRemovableIfPossible :: Maybe FileRef -> OsPath -> IO ()

Check failure on line 444 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, lts-13.30, bytestring-0.11.3.0, file-io-0.1.2, filepath-1.4.100.0, time-1....

Not in scope: type constructor or class `FileRef'

Check failure on line 444 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, lts-17.5, bytestring-0.11.3.0, file-io-0.1.2, filepath-1.4.100.0, time-1.9...

Not in scope: type constructor or class `FileRef'

Check failure on line 444 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, lts-22.7, bytestring-0.11.5.3, file-io-0.1.2, filepath-1.5.2.0, os-string-...

Not in scope: type constructor or class `FileRef'
forceRemovableIfPossible dirRef name = do
metadata <- getSymbolicLinkMetadataAt dirRef name
when (fileTypeIsDirectory (fileTypeFromMetadata metadata)
|| not filesAlwaysRemovable) $ do
forceRemovable dirRef name metadata `catchIOError` \ _ -> pure ()

removePathForciblyAt :: Maybe FileRef -> OsPath -> IO ()

Check failure on line 451 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, lts-13.30, bytestring-0.11.3.0, file-io-0.1.2, filepath-1.4.100.0, time-1....

Not in scope: type constructor or class `FileRef'

Check failure on line 451 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, lts-17.5, bytestring-0.11.3.0, file-io-0.1.2, filepath-1.4.100.0, time-1.9...

Not in scope: type constructor or class `FileRef'

Check failure on line 451 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, lts-22.7, bytestring-0.11.5.3, file-io-0.1.2, filepath-1.5.2.0, os-string-...

Not in scope: type constructor or class `FileRef'
removePathForciblyAt dirRef name = do
forceRemovableIfPossible dirRef name
withSubref dirRef name $ \ subref -> do
case subref of
NotSubdir -> do

Check failure on line 456 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, lts-13.30, bytestring-0.11.3.0, file-io-0.1.2, filepath-1.4.100.0, time-1....

Not in scope: data constructor `NotSubdir'

Check failure on line 456 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, lts-17.5, bytestring-0.11.3.0, file-io-0.1.2, filepath-1.4.100.0, time-1.9...

Not in scope: data constructor `NotSubdir'

Check failure on line 456 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, lts-22.7, bytestring-0.11.5.3, file-io-0.1.2, filepath-1.5.2.0, os-string-...

Not in scope: data constructor `NotSubdir'
removePathAt File dirRef name -- TODO: What about windows dir links?
SubdirRef subdirRef -> do

Check failure on line 458 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, lts-13.30, bytestring-0.11.3.0, file-io-0.1.2, filepath-1.4.100.0, time-1....

Not in scope: data constructor `SubdirRef'

Check failure on line 458 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, lts-17.5, bytestring-0.11.3.0, file-io-0.1.2, filepath-1.4.100.0, time-1.9...

Not in scope: data constructor `SubdirRef'

Check failure on line 458 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, lts-22.7, bytestring-0.11.5.3, file-io-0.1.2, filepath-1.5.2.0, os-string-...

Not in scope: data constructor `SubdirRef'
names <-
-- This filter is very important! Otherwise it will
-- recurse into the parent directory and do bad things.
filter (not . isSpecialDir) <$>
getDirectoryContentsRef subdirRef
sequenceWithIOErrors_ $
(removeForcibly (Just subdirRef) <$> names) <>

Check failure on line 465 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (macOS-13, lts-13.30, bytestring-0.11.3.0, file-io-0.1.2, filepath-1.4.100.0, unix-2.8.0.0)

• Variable not in scope:

Check failure on line 465 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (macos-latest, lts-22.7, bytestring-0.11.5.3, file-io-0.1.2, filepath-1.5.2.0, os-string-2....

Variable not in scope:

Check failure on line 465 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.6.5, 3.0.0.0, before_prepare() { sed -i.bak /utimensat/d configure.ac; })

• Variable not in scope:

Check failure on line 465 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 8.10.7, 3.8.1.0)

• Variable not in scope:

Check failure on line 465 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.0.2, 3.8.1.0)

• Variable not in scope:

Check failure on line 465 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.2.4, 3.8.1.0)

• Variable not in scope:

Check failure on line 465 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, 9.4.3, 3.8.1.0)

Variable not in scope:

Check failure on line 465 in System/Directory/OsPath.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, latest, latest, +os-string, -Werror=deprecations)

Variable not in scope:
[removePathAt Directory dirRef name]

-- | Removes a file or directory at /path/ together with its contents and
-- subdirectories. Symbolic links are removed without affecting their
-- targets. If the path does not exist, nothing happens.
Expand All @@ -460,33 +484,7 @@ removeContentsRecursive path =
removePathForcibly :: OsPath -> IO ()
removePathForcibly path =
(`ioeAddLocation` "removePathForcibly") `modifyIOError` do
ignoreDoesNotExistError $ do
m <- getSymbolicLinkMetadata path
case fileTypeFromMetadata m of
DirectoryLink -> do
makeRemovable path
removeDirectory path
Directory -> do
makeRemovable path
names <- listDirectory path
sequenceWithIOErrors_ $
[ removePathForcibly (path </> name) | name <- names ] ++
[ removeDirectory path ]
_ -> do
unless filesAlwaysRemovable (makeRemovable path)
removeFile path
where

ignoreDoesNotExistError :: IO () -> IO ()
ignoreDoesNotExistError action =
() <$ tryIOErrorType isDoesNotExistError action

makeRemovable :: OsPath -> IO ()
makeRemovable p = (`catchIOError` \ _ -> pure ()) $ do
perms <- getPermissions p
setPermissions path perms{ readable = True
, searchable = True
, writable = True }
ignoreDoesNotExistError (removePathForciblyAt Nothing path)

{- |'removeFile' /file/ removes the directory entry for an existing file
/file/, where /file/ is not itself a directory. The
Expand Down Expand Up @@ -1100,6 +1098,15 @@ findFilesWithLazy f dirs path
exeExtension :: OsString
exeExtension = exeExtensionInternal

curDir :: OsPath
curDir = os "."

parDir :: OsPath
parDir = os ".."

isSpecialDir :: OsPath -> Bool
isSpecialDir = (`elem` [curDir, parDir])

-- | Similar to 'listDirectory', but always includes the special entries (@.@
-- and @..@). (This applies to Windows as well.)
--
Expand Down Expand Up @@ -1140,8 +1147,7 @@ getDirectoryContents path =
-- @[ENOTDIR]@
--
listDirectory :: OsPath -> IO [OsPath]
listDirectory path = filter f <$> getDirectoryContents path
where f filename = filename /= os "." && filename /= os ".."
listDirectory path = filter (not . isSpecialDir) <$> getDirectoryContents path

-- | Obtain the current working directory as an absolute path.
--
Expand Down

0 comments on commit aaf9cf7

Please sign in to comment.