module System.Directory.OsPath
(
createDirectory
, createDirectoryIfMissing
, removeDirectory
, removeDirectoryRecursive
, removePathForcibly
, renameDirectory
, listDirectory
, getDirectoryContents
, getCurrentDirectory
, setCurrentDirectory
, withCurrentDirectory
, getHomeDirectory
, XdgDirectory(..)
, getXdgDirectory
, XdgDirectoryList(..)
, getXdgDirectoryList
, getAppUserDataDirectory
, getUserDocumentsDirectory
, getTemporaryDirectory
, getExecSearchPath
, removeFile
, renameFile
, renamePath
, copyFile
, copyFileWithMetadata
, getFileSize
, canonicalizePath
, makeAbsolute
, makeRelativeToCurrentDirectory
, doesPathExist
, doesFileExist
, doesDirectoryExist
, findExecutable
, findExecutables
, findExecutablesInDirectories
, findFile
, findFiles
, findFileWith
, findFilesWith
, exeExtension
, createFileLink
, createDirectoryLink
, removeDirectoryLink
, pathIsSymbolicLink
, getSymbolicLinkTarget
, Permissions
, emptyPermissions
, readable
, writable
, executable
, searchable
, setOwnerReadable
, setOwnerWritable
, setOwnerExecutable
, setOwnerSearchable
, getPermissions
, setPermissions
, copyPermissions
, getAccessTime
, getModificationTime
, setAccessTime
, setModificationTime
) where
import Prelude ()
import System.Directory.Internal
import System.Directory.Internal.Prelude
import qualified System.File.OsPath as OS
import System.OsPath
( (<.>)
, (</>)
, addTrailingPathSeparator
, dropTrailingPathSeparator
, hasTrailingPathSeparator
, isAbsolute
, joinPath
, makeRelative
, splitDirectories
, splitSearchPath
, takeDirectory
, encodeWith
)
import qualified Data.List.NonEmpty as NE
import Data.Time (UTCTime)
import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds)
import GHC.IO.Encoding.UTF8 ( mkUTF8 )
import GHC.IO.Encoding.UTF16 ( mkUTF16le )
import GHC.IO.Encoding.Failure ( CodingFailureMode(..) )
emptyPermissions :: Permissions
emptyPermissions :: Permissions
emptyPermissions = Permissions {
readable :: Bool
readable = Bool
False,
writable :: Bool
writable = Bool
False,
executable :: Bool
executable = Bool
False,
searchable :: Bool
searchable = Bool
False
}
setOwnerReadable :: Bool -> Permissions -> Permissions
setOwnerReadable :: Bool -> Permissions -> Permissions
setOwnerReadable Bool
b Permissions
p = Permissions
p { readable = b }
setOwnerWritable :: Bool -> Permissions -> Permissions
setOwnerWritable :: Bool -> Permissions -> Permissions
setOwnerWritable Bool
b Permissions
p = Permissions
p { writable = b }
setOwnerExecutable :: Bool -> Permissions -> Permissions
setOwnerExecutable :: Bool -> Permissions -> Permissions
setOwnerExecutable Bool
b Permissions
p = Permissions
p { executable = b }
setOwnerSearchable :: Bool -> Permissions -> Permissions
setOwnerSearchable :: Bool -> Permissions -> Permissions
setOwnerSearchable Bool
b Permissions
p = Permissions
p { searchable = b }
getPermissions :: OsPath -> IO Permissions
getPermissions :: OsString -> IO Permissions
getPermissions OsString
path =
(IOError -> String -> IOError
`ioeAddLocation` String
"getPermissions") (IOError -> IOError) -> IO Permissions -> IO Permissions
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> IO Permissions
getAccessPermissions (OsString -> OsString
emptyToCurDir OsString
path)
setPermissions :: OsPath -> Permissions -> IO ()
setPermissions :: OsString -> Permissions -> IO ()
setPermissions OsString
path Permissions
p =
(IOError -> String -> IOError
`ioeAddLocation` String
"setPermissions") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> Permissions -> IO ()
setAccessPermissions (OsString -> OsString
emptyToCurDir OsString
path) Permissions
p
copyPermissions :: OsPath -> OsPath -> IO ()
copyPermissions :: OsString -> OsString -> IO ()
copyPermissions OsString
src OsString
dst =
(IOError -> String -> IOError
`ioeAddLocation` String
"copyPermissions") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
m <- OsString -> IO Metadata
getFileMetadata OsString
src
copyPermissionsFromMetadata m dst
copyPermissionsFromMetadata :: Metadata -> OsPath -> IO ()
copyPermissionsFromMetadata :: Metadata -> OsString -> IO ()
copyPermissionsFromMetadata Metadata
m OsString
dst = do
OsString -> Mode -> IO ()
setFilePermissions OsString
dst (Metadata -> Mode
modeFromMetadata Metadata
m)
createDirectory :: OsPath -> IO ()
createDirectory :: OsString -> IO ()
createDirectory = OsString -> IO ()
createDirectoryInternal
createDirectoryIfMissing :: Bool
-> OsPath
-> IO ()
createDirectoryIfMissing :: Bool -> OsString -> IO ()
createDirectoryIfMissing Bool
create_parents OsString
path0
| Bool
create_parents = [OsString] -> IO ()
createDirs (OsString -> [OsString]
parents OsString
path0)
| Bool
otherwise = [OsString] -> IO ()
createDirs (Int -> [OsString] -> [OsString]
forall a. Int -> [a] -> [a]
take Int
1 (OsString -> [OsString]
parents OsString
path0))
where
parents :: OsString -> [OsString]
parents = [OsString] -> [OsString]
forall a. [a] -> [a]
reverse ([OsString] -> [OsString])
-> (OsString -> [OsString]) -> OsString -> [OsString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (OsString -> OsString -> OsString) -> [OsString] -> [OsString]
forall a. (a -> a -> a) -> [a] -> [a]
scanl1 OsString -> OsString -> OsString
(</>) ([OsString] -> [OsString])
-> (OsString -> [OsString]) -> OsString -> [OsString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsString -> [OsString]
splitDirectories (OsString -> [OsString])
-> (OsString -> OsString) -> OsString -> [OsString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsString -> OsString
simplify
createDirs :: [OsString] -> IO ()
createDirs [] = () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
createDirs (OsString
dir:[]) = OsString -> (IOError -> IO ()) -> IO ()
createDir OsString
dir IOError -> IO ()
forall a. HasCallStack => IOError -> IO a
ioError
createDirs (OsString
dir:[OsString]
dirs) =
OsString -> (IOError -> IO ()) -> IO ()
createDir OsString
dir ((IOError -> IO ()) -> IO ()) -> (IOError -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IOError
_ -> do
[OsString] -> IO ()
createDirs [OsString]
dirs
OsString -> (IOError -> IO ()) -> IO ()
createDir OsString
dir IOError -> IO ()
forall a. HasCallStack => IOError -> IO a
ioError
createDir :: OsString -> (IOError -> IO ()) -> IO ()
createDir OsString
dir IOError -> IO ()
notExistHandler = do
r <- IO () -> IO (Either IOError ())
forall a. IO a -> IO (Either IOError a)
tryIOError (OsString -> IO ()
createDirectory OsString
dir)
case r of
Right () -> () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Left IOError
e
| IOError -> Bool
isDoesNotExistError IOError
e -> IOError -> IO ()
notExistHandler IOError
e
| IOError -> Bool
isAlreadyExistsError IOError
e
Bool -> Bool -> Bool
|| IOError -> Bool
isPermissionError IOError
e -> do
canIgnore <- OsString -> IO Bool
pathIsDirectory OsString
dir
IO Bool -> (IOError -> IO Bool) -> IO Bool
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` \ IOError
_ ->
Bool -> IO Bool
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IOError -> Bool
isAlreadyExistsError IOError
e)
unless canIgnore (ioError e)
| Bool
otherwise -> IOError -> IO ()
forall a. HasCallStack => IOError -> IO a
ioError IOError
e
removeDirectory :: OsPath -> IO ()
removeDirectory :: OsString -> IO ()
removeDirectory = Bool -> OsString -> IO ()
removePathInternal Bool
True
type Preremover = Maybe RawHandle -> OsPath -> Metadata -> IO ()
noPreremover :: Preremover
noPreremover :: Preremover
noPreremover Maybe RawHandle
_ OsString
_ Metadata
_ = () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
forcePreremover :: Preremover
forcePreremover :: Preremover
forcePreremover Maybe RawHandle
dir OsString
path Metadata
metadata = do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (FileType -> Bool
fileTypeIsDirectory (Metadata -> FileType
fileTypeFromMetadata Metadata
metadata)
Bool -> Bool -> Bool
|| Bool -> Bool
not Bool
filesAlwaysRemovable) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
WhetherFollow -> Maybe RawHandle -> OsString -> Mode -> IO ()
setModeAt WhetherFollow
NoFollow Maybe RawHandle
dir OsString
path Mode
mode
IO () -> (IOError -> IO ()) -> IO ()
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` \ IOError
_ -> () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
where
mode :: Mode
mode = Mode -> Mode
setForceRemoveMode (Metadata -> Mode
modeFromMetadata Metadata
metadata)
removeRecursivelyAt
:: (IO () -> IO ())
-> ([IO ()] -> IO ())
-> Preremover
-> Maybe RawHandle
-> OsPath
-> IO ()
removeRecursivelyAt :: (IO () -> IO ())
-> ([IO ()] -> IO ())
-> Preremover
-> Maybe RawHandle
-> OsString
-> IO ()
removeRecursivelyAt IO () -> IO ()
catcher [IO ()] -> IO ()
sequencer Preremover
preremover Maybe RawHandle
dir OsString
name = IO () -> IO ()
catcher (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
metadata <- WhetherFollow -> Maybe RawHandle -> OsString -> IO Metadata
getMetadataAt WhetherFollow
NoFollow Maybe RawHandle
dir OsString
name
preremover dir name metadata
let
fileType = Metadata -> FileType
fileTypeFromMetadata Metadata
metadata
subremovals = do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (FileType
fileType FileType -> FileType -> Bool
forall a. Eq a => a -> a -> Bool
== FileType
Directory) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
IO RawHandle
-> (RawHandle -> IO ()) -> (RawHandle -> IO ()) -> IO ()
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (WhetherFollow -> Maybe RawHandle -> OsString -> IO RawHandle
openRaw WhetherFollow
NoFollow Maybe RawHandle
dir OsString
name) RawHandle -> IO ()
closeRaw ((RawHandle -> IO ()) -> IO ()) -> (RawHandle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ RawHandle
handle -> do
names <- [OsString] -> [OsString]
dropSpecialDotDirs ([OsString] -> [OsString]) -> IO [OsString] -> IO [OsString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RawHandle -> IO [OsString]
readDirToEnd RawHandle
handle
sequencer (recurse (Just handle) <$> names)
sequencer [subremovals, removePathAt fileType dir name]
where recurse :: Maybe RawHandle -> OsString -> IO ()
recurse = (IO () -> IO ())
-> ([IO ()] -> IO ())
-> Preremover
-> Maybe RawHandle
-> OsString
-> IO ()
removeRecursivelyAt IO () -> IO ()
catcher [IO ()] -> IO ()
sequencer Preremover
preremover
removeDirectoryRecursive :: OsPath -> IO ()
removeDirectoryRecursive :: OsString -> IO ()
removeDirectoryRecursive OsString
path =
(IOError -> String -> IOError
`ioeAddLocation` String
"removeDirectoryRecursive") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
m <- OsString -> IO Metadata
getSymbolicLinkMetadata OsString
path
case fileTypeFromMetadata m of
FileType
Directory ->
(IO () -> IO ())
-> ([IO ()] -> IO ())
-> Preremover
-> Maybe RawHandle
-> OsString
-> IO ()
removeRecursivelyAt IO () -> IO ()
forall a. a -> a
id [IO ()] -> IO ()
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Applicative f) =>
t (f a) -> f ()
sequenceA_ Preremover
noPreremover Maybe RawHandle
forall a. Maybe a
Nothing OsString
path
FileType
DirectoryLink ->
IOError -> IO ()
forall a. HasCallStack => IOError -> IO a
ioError (IOError
err IOError -> String -> IOError
`ioeSetErrorString` String
"is a directory symbolic link")
FileType
_ ->
IOError -> IO ()
forall a. HasCallStack => IOError -> IO a
ioError (IOError
err IOError -> String -> IOError
`ioeSetErrorString` String
"not a directory")
where err :: IOError
err = IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError
mkIOError IOErrorType
InappropriateType String
"" Maybe Handle
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing IOError -> OsString -> IOError
`ioeSetOsPath` OsString
path
removePathForcibly :: OsPath -> IO ()
removePathForcibly :: OsString -> IO ()
removePathForcibly OsString
path =
(IOError -> String -> IOError
`ioeAddLocation` String
"removePathForcibly") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
(IO () -> IO ())
-> ([IO ()] -> IO ())
-> Preremover
-> Maybe RawHandle
-> OsString
-> IO ()
removeRecursivelyAt
IO () -> IO ()
ignoreDoesNotExistError
[IO ()] -> IO ()
sequenceWithIOErrors_
Preremover
forcePreremover
Maybe RawHandle
forall a. Maybe a
Nothing
OsString
path
where
ignoreDoesNotExistError :: IO () -> IO ()
ignoreDoesNotExistError :: IO () -> IO ()
ignoreDoesNotExistError IO ()
action =
() () -> IO (Either IOError ()) -> IO ()
forall a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (IOError -> Bool) -> IO () -> IO (Either IOError ())
forall a. (IOError -> Bool) -> IO a -> IO (Either IOError a)
tryIOErrorType IOError -> Bool
isDoesNotExistError IO ()
action
removeFile :: OsPath -> IO ()
removeFile :: OsString -> IO ()
removeFile = Bool -> OsString -> IO ()
removePathInternal Bool
False
renameDirectory :: OsPath -> OsPath -> IO ()
renameDirectory :: OsString -> OsString -> IO ()
renameDirectory OsString
opath OsString
npath =
(IOError -> String -> IOError
`ioeAddLocation` String
"renameDirectory") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
isDir <- OsString -> IO Bool
pathIsDirectory OsString
opath
when (not isDir) . ioError $
mkIOError InappropriateType "renameDirectory" Nothing Nothing
`ioeSetErrorString` "not a directory"
`ioeSetOsPath` opath
renamePath opath npath
renameFile :: OsPath -> OsPath -> IO ()
renameFile :: OsString -> OsString -> IO ()
renameFile OsString
opath OsString
npath =
(IOError -> String -> IOError
`ioeAddLocation` String
"renameFile") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> IO ()
checkNotDir OsString
opath
OsString -> OsString -> IO ()
renamePath OsString
opath OsString
npath
IO () -> (IOError -> IO ()) -> IO ()
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` \ IOError
err -> do
OsString -> IO ()
checkNotDir OsString
npath
IOError -> IO ()
forall a. HasCallStack => IOError -> IO a
ioError IOError
err
where checkNotDir :: OsString -> IO ()
checkNotDir OsString
path = do
m <- IO Metadata -> IO (Either IOError Metadata)
forall a. IO a -> IO (Either IOError a)
tryIOError (OsString -> IO Metadata
getSymbolicLinkMetadata OsString
path)
case fileTypeIsDirectory . fileTypeFromMetadata <$> m of
Right Bool
True ->
IOError -> IO ()
forall a. HasCallStack => IOError -> IO a
ioError (IOError -> IO ()) -> IOError -> IO ()
forall a b. (a -> b) -> a -> b
$
IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError
mkIOError IOErrorType
InappropriateType String
"" Maybe Handle
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
IOError -> String -> IOError
`ioeSetErrorString` String
"is a directory"
IOError -> OsString -> IOError
`ioeSetOsPath` OsString
path
Either IOError Bool
_ -> () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
renamePath :: OsPath
-> OsPath
-> IO ()
renamePath :: OsString -> OsString -> IO ()
renamePath OsString
opath OsString
npath =
(IOError -> String -> IOError
`ioeAddLocation` String
"renamePath") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> OsString -> IO ()
renamePathInternal OsString
opath OsString
npath
copyFile :: OsPath
-> OsPath
-> IO ()
copyFile :: OsString -> OsString -> IO ()
copyFile OsString
fromFPath OsString
toFPath =
(IOError -> String -> IOError
`ioeAddLocation` String
"copyFile") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> OsString -> (OsString -> IO ()) -> IO ()
atomicCopyFileContents OsString
fromFPath OsString
toFPath
(IO () -> IO ()
ignoreIOExceptions (IO () -> IO ()) -> (OsString -> IO ()) -> OsString -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsString -> OsString -> IO ()
copyPermissions OsString
fromFPath)
copyFileToHandle :: OsPath
-> Handle
-> IO ()
copyFileToHandle :: OsString -> Handle -> IO ()
copyFileToHandle OsString
fromFPath Handle
hTo =
(IOError -> String -> IOError
`ioeAddLocation` String
"copyFileToHandle") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. OsString -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile OsString
fromFPath IOMode
ReadMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Handle
hFrom ->
Handle -> Handle -> IO ()
copyHandleData Handle
hFrom Handle
hTo
atomicCopyFileContents :: OsPath
-> OsPath
-> (OsPath -> IO ())
-> IO ()
atomicCopyFileContents :: OsString -> OsString -> (OsString -> IO ()) -> IO ()
atomicCopyFileContents OsString
fromFPath OsString
toFPath OsString -> IO ()
postAction =
(IOError -> String -> IOError
`ioeAddLocation` String
"atomicCopyFileContents") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> (OsString -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a.
OsString -> (OsString -> IO ()) -> (Handle -> IO a) -> IO a
withReplacementFile OsString
toFPath OsString -> IO ()
postAction ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Handle
hTo -> do
OsString -> Handle -> IO ()
copyFileToHandle OsString
fromFPath Handle
hTo
withReplacementFile :: OsPath
-> (OsPath -> IO ())
-> (Handle -> IO a)
-> IO a
withReplacementFile :: forall a.
OsString -> (OsString -> IO ()) -> (Handle -> IO a) -> IO a
withReplacementFile OsString
path OsString -> IO ()
postAction Handle -> IO a
action =
(IOError -> String -> IOError
`ioeAddLocation` String
"withReplacementFile") (IOError -> IOError) -> IO a -> IO a
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
((forall a. IO a -> IO a) -> IO a) -> IO a
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
mask (((forall a. IO a -> IO a) -> IO a) -> IO a)
-> ((forall a. IO a -> IO a) -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \ forall a. IO a -> IO a
restore -> do
let tmpPath :: OsString
tmpPath = case TextEncoding
-> TextEncoding -> String -> Either EncodingException OsString
encodeWith (CodingFailureMode -> TextEncoding
mkUTF8 CodingFailureMode
ErrorOnCodingFailure)
(CodingFailureMode -> TextEncoding
mkUTF16le CodingFailureMode
ErrorOnCodingFailure)
String
".copyFile.tmp"
of
Left EncodingException
err -> String -> OsString
forall a. HasCallStack => String -> a
error (String
"withReplacementFile: invalid encoding: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ EncodingException -> String
forall a. Show a => a -> String
show EncodingException
err)
Right OsString
p -> OsString
p
(tmpFPath, hTmp) <- OsString -> OsString -> IO (OsString, Handle)
OS.openBinaryTempFile (OsString -> OsString
takeDirectory OsString
path) OsString
tmpPath
(`onException` ignoreIOExceptions (removeFile tmpFPath)) $ do
r <- (`onException` ignoreIOExceptions (hClose hTmp)) $ do
restore (action hTmp)
hClose hTmp
restore (postAction tmpFPath)
renameFile tmpFPath path
pure r
copyFileWithMetadata :: OsPath
-> OsPath
-> IO ()
copyFileWithMetadata :: OsString -> OsString -> IO ()
copyFileWithMetadata OsString
src OsString
dst =
(IOError -> String -> IOError
`ioeAddLocation` String
"copyFileWithMetadata") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError`
(Metadata -> OsString -> IO ())
-> (Metadata -> OsString -> IO ()) -> OsString -> OsString -> IO ()
copyFileWithMetadataInternal Metadata -> OsString -> IO ()
copyPermissionsFromMetadata
Metadata -> OsString -> IO ()
copyTimesFromMetadata
OsString
src
OsString
dst
copyTimesFromMetadata :: Metadata -> OsPath -> IO ()
copyTimesFromMetadata :: Metadata -> OsString -> IO ()
copyTimesFromMetadata Metadata
st OsString
dst = do
let atime :: UTCTime
atime = Metadata -> UTCTime
accessTimeFromMetadata Metadata
st
let mtime :: UTCTime
mtime = Metadata -> UTCTime
modificationTimeFromMetadata Metadata
st
OsString -> (Maybe UTCTime, Maybe UTCTime) -> IO ()
setFileTimes OsString
dst (UTCTime -> Maybe UTCTime
forall a. a -> Maybe a
Just UTCTime
atime, UTCTime -> Maybe UTCTime
forall a. a -> Maybe a
Just UTCTime
mtime)
canonicalizePath :: OsPath -> IO OsPath
canonicalizePath :: OsString -> IO OsString
canonicalizePath = \ OsString
path ->
((IOError -> String -> IOError
`ioeAddLocation` String
"canonicalizePath") (IOError -> IOError) -> (IOError -> IOError) -> IOError -> IOError
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(IOError -> OsString -> IOError
`ioeSetOsPath` OsString
path)) (IOError -> IOError) -> IO OsString -> IO OsString
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> OsString
dropTrailingPathSeparator (OsString -> OsString)
-> (OsString -> OsString) -> OsString -> OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsString -> OsString
simplify (OsString -> OsString) -> IO OsString -> IO OsString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
((OsString -> IO OsString) -> OsString -> IO OsString
attemptRealpath OsString -> IO OsString
realPath (OsString -> IO OsString) -> IO OsString -> IO OsString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< OsString -> IO OsString
prependCurrentDirectory OsString
path)
where
attemptRealpath :: (OsString -> IO OsString) -> OsString -> IO OsString
attemptRealpath OsString -> IO OsString
realpath =
Int
-> Maybe OsString
-> (OsString -> IO OsString)
-> OsString
-> IO OsString
forall {a}.
(Ord a, Num a) =>
a
-> Maybe OsString
-> (OsString -> IO OsString)
-> OsString
-> IO OsString
attemptRealpathWith (Int
64 :: Int) Maybe OsString
forall a. Maybe a
Nothing OsString -> IO OsString
realpath
(OsString -> IO OsString)
-> (OsString -> IO OsString) -> OsString -> IO OsString
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< OsString -> IO OsString
canonicalizePathSimplify
attemptRealpathWith :: a
-> Maybe OsString
-> (OsString -> IO OsString)
-> OsString
-> IO OsString
attemptRealpathWith a
n Maybe OsString
mFallback OsString -> IO OsString
realpath OsString
path =
case Maybe OsString
mFallback of
Just OsString
fallback | a
n a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
0 -> OsString -> IO OsString
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OsString
fallback
Maybe OsString
_ -> [(OsString, OsString)] -> IO OsString
realpathPrefix ([(OsString, OsString)] -> [(OsString, OsString)]
forall a. [a] -> [a]
reverse ([OsString] -> [OsString] -> [(OsString, OsString)]
forall a b. [a] -> [b] -> [(a, b)]
zip [OsString]
prefixes [OsString]
suffixes))
where
segments :: [OsString]
segments = OsString -> [OsString]
splitDirectories OsString
path
prefixes :: [OsString]
prefixes = (OsString -> OsString -> OsString) -> [OsString] -> [OsString]
forall a. (a -> a -> a) -> [a] -> [a]
scanl1 OsString -> OsString -> OsString
(</>) [OsString]
segments
suffixes :: [OsString]
suffixes = NonEmpty OsString -> [OsString]
forall a. NonEmpty a -> [a]
NE.tail ((OsString -> OsString -> OsString)
-> OsString -> [OsString] -> NonEmpty OsString
forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> f a -> NonEmpty b
NE.scanr OsString -> OsString -> OsString
(</>) OsString
forall a. Monoid a => a
mempty [OsString]
segments)
realpathPrefix :: [(OsString, OsString)] -> IO OsString
realpathPrefix [(OsString, OsString)]
candidates =
case [(OsString, OsString)]
candidates of
[] -> OsString -> IO OsString
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OsString
path
(OsString
prefix, OsString
suffix) : [(OsString, OsString)]
rest -> do
exist <- OsString -> IO Bool
doesPathExist OsString
prefix
if not exist
then realpathPrefix rest
else do
mp <- tryIOError (realpath prefix)
case mp of
Left IOError
_ -> [(OsString, OsString)] -> IO OsString
realpathPrefix [(OsString, OsString)]
rest
Right OsString
p -> OsString -> OsString -> OsString -> IO OsString
realpathFurther (OsString
p OsString -> OsString -> OsString
</> OsString
suffix) OsString
p OsString
suffix
realpathFurther :: OsString -> OsString -> OsString -> IO OsString
realpathFurther OsString
fallback OsString
p OsString
suffix =
case OsString -> [OsString]
splitDirectories OsString
suffix of
[] -> OsString -> IO OsString
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OsString
fallback
OsString
next : [OsString]
restSuffix -> do
mTarget <- IO OsString -> IO (Either IOError OsString)
forall a. IO a -> IO (Either IOError a)
tryIOError (OsString -> IO OsString
getSymbolicLinkTarget (OsString
p OsString -> OsString -> OsString
</> OsString
next))
case mTarget of
Left IOError
_ -> OsString -> IO OsString
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OsString
fallback
Right OsString
target -> do
let mFallback' :: Maybe OsString
mFallback' = OsString -> Maybe OsString
forall a. a -> Maybe a
Just (OsString -> Maybe OsString -> OsString
forall a. a -> Maybe a -> a
fromMaybe OsString
fallback Maybe OsString
mFallback)
path' <- OsString -> IO OsString
canonicalizePathSimplify
(OsString
p OsString -> OsString -> OsString
</> OsString
target OsString -> OsString -> OsString
</> [OsString] -> OsString
joinPath [OsString]
restSuffix)
attemptRealpathWith (n - 1) mFallback' realpath path'
makeAbsolute :: OsPath -> IO OsPath
makeAbsolute :: OsString -> IO OsString
makeAbsolute OsString
path =
((IOError -> String -> IOError
`ioeAddLocation` String
"makeAbsolute") (IOError -> IOError) -> (IOError -> IOError) -> IOError -> IOError
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(IOError -> OsString -> IOError
`ioeSetOsPath` OsString
path)) (IOError -> IOError) -> IO OsString -> IO OsString
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> OsString -> OsString
matchTrailingSeparator OsString
path (OsString -> OsString)
-> (OsString -> OsString) -> OsString -> OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsString -> OsString
simplify (OsString -> OsString) -> IO OsString -> IO OsString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsString -> IO OsString
prependCurrentDirectory OsString
path
matchTrailingSeparator :: OsPath -> OsPath -> OsPath
matchTrailingSeparator :: OsString -> OsString -> OsString
matchTrailingSeparator OsString
path
| OsString -> Bool
hasTrailingPathSeparator OsString
path = OsString -> OsString
addTrailingPathSeparator
| Bool
otherwise = OsString -> OsString
dropTrailingPathSeparator
makeRelativeToCurrentDirectory :: OsPath -> IO OsPath
makeRelativeToCurrentDirectory :: OsString -> IO OsString
makeRelativeToCurrentDirectory OsString
x = do
(OsString -> OsString -> OsString
`makeRelative` OsString
x) (OsString -> OsString) -> IO OsString -> IO OsString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO OsString
getCurrentDirectory
findExecutable :: OsString -> IO (Maybe OsPath)
findExecutable :: OsString -> IO (Maybe OsString)
findExecutable OsString
binary =
ListT IO OsString -> IO (Maybe OsString)
forall (m :: * -> *) a. Functor m => ListT m a -> m (Maybe a)
listTHead
(([OsString] -> OsString -> ListT IO OsString)
-> OsString -> ListT IO OsString
findExecutablesLazyInternal [OsString] -> OsString -> ListT IO OsString
findExecutablesInDirectoriesLazy OsString
binary)
findExecutables :: OsString -> IO [OsPath]
findExecutables :: OsString -> IO [OsString]
findExecutables OsString
binary =
ListT IO OsString -> IO [OsString]
forall (m :: * -> *) a. Monad m => ListT m a -> m [a]
listTToList
(([OsString] -> OsString -> ListT IO OsString)
-> OsString -> ListT IO OsString
findExecutablesLazyInternal [OsString] -> OsString -> ListT IO OsString
findExecutablesInDirectoriesLazy OsString
binary)
findExecutablesInDirectories :: [OsPath] -> OsString -> IO [OsPath]
findExecutablesInDirectories :: [OsString] -> OsString -> IO [OsString]
findExecutablesInDirectories [OsString]
path OsString
binary =
ListT IO OsString -> IO [OsString]
forall (m :: * -> *) a. Monad m => ListT m a -> m [a]
listTToList ([OsString] -> OsString -> ListT IO OsString
findExecutablesInDirectoriesLazy [OsString]
path OsString
binary)
findExecutablesInDirectoriesLazy :: [OsPath] -> OsString -> ListT IO OsPath
findExecutablesInDirectoriesLazy :: [OsString] -> OsString -> ListT IO OsString
findExecutablesInDirectoriesLazy [OsString]
path OsString
binary =
(OsString -> IO Bool)
-> [OsString] -> OsString -> ListT IO OsString
findFilesWithLazy OsString -> IO Bool
isExecutable [OsString]
path (OsString
binary OsString -> OsString -> OsString
<.> OsString
exeExtension)
isExecutable :: OsPath -> IO Bool
isExecutable :: OsString -> IO Bool
isExecutable OsString
file = Permissions -> Bool
executable (Permissions -> Bool) -> IO Permissions -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsString -> IO Permissions
getPermissions OsString
file
findFile :: [OsPath] -> OsString -> IO (Maybe OsPath)
findFile :: [OsString] -> OsString -> IO (Maybe OsString)
findFile = (OsString -> IO Bool)
-> [OsString] -> OsString -> IO (Maybe OsString)
findFileWith (\ OsString
_ -> Bool -> IO Bool
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True)
findFiles :: [OsPath] -> OsString -> IO [OsPath]
findFiles :: [OsString] -> OsString -> IO [OsString]
findFiles = (OsString -> IO Bool) -> [OsString] -> OsString -> IO [OsString]
findFilesWith (\ OsString
_ -> Bool -> IO Bool
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True)
findFileWith :: (OsPath -> IO Bool) -> [OsPath] -> OsString -> IO (Maybe OsPath)
findFileWith :: (OsString -> IO Bool)
-> [OsString] -> OsString -> IO (Maybe OsString)
findFileWith OsString -> IO Bool
f [OsString]
ds OsString
name = ListT IO OsString -> IO (Maybe OsString)
forall (m :: * -> *) a. Functor m => ListT m a -> m (Maybe a)
listTHead ((OsString -> IO Bool)
-> [OsString] -> OsString -> ListT IO OsString
findFilesWithLazy OsString -> IO Bool
f [OsString]
ds OsString
name)
findFilesWith :: (OsPath -> IO Bool) -> [OsPath] -> OsString -> IO [OsPath]
findFilesWith :: (OsString -> IO Bool) -> [OsString] -> OsString -> IO [OsString]
findFilesWith OsString -> IO Bool
f [OsString]
ds OsString
name = ListT IO OsString -> IO [OsString]
forall (m :: * -> *) a. Monad m => ListT m a -> m [a]
listTToList ((OsString -> IO Bool)
-> [OsString] -> OsString -> ListT IO OsString
findFilesWithLazy OsString -> IO Bool
f [OsString]
ds OsString
name)
findFilesWithLazy
:: (OsPath -> IO Bool) -> [OsPath] -> OsString -> ListT IO OsPath
findFilesWithLazy :: (OsString -> IO Bool)
-> [OsString] -> OsString -> ListT IO OsString
findFilesWithLazy OsString -> IO Bool
f [OsString]
dirs OsString
path
| OsString -> Bool
isAbsolute OsString
path = IO (Maybe (OsString, ListT IO OsString)) -> ListT IO OsString
forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT ([OsString] -> IO (Maybe (OsString, ListT IO OsString))
find [OsString
forall a. Monoid a => a
mempty])
| Bool
otherwise = IO (Maybe (OsString, ListT IO OsString)) -> ListT IO OsString
forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT ([OsString] -> IO (Maybe (OsString, ListT IO OsString))
find [OsString]
dirs)
where
find :: [OsString] -> IO (Maybe (OsString, ListT IO OsString))
find [] = Maybe (OsString, ListT IO OsString)
-> IO (Maybe (OsString, ListT IO OsString))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (OsString, ListT IO OsString)
forall a. Maybe a
Nothing
find (OsString
d : [OsString]
ds) = do
let p :: OsString
p = OsString
d OsString -> OsString -> OsString
</> OsString
path
found <- OsString -> IO Bool
doesFileExist OsString
p IO Bool -> IO Bool -> IO Bool
forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
`andM` OsString -> IO Bool
f OsString
p
if found
then pure (Just (p, ListT (find ds)))
else find ds
exeExtension :: OsString
exeExtension :: OsString
exeExtension = OsString
exeExtensionInternal
getDirectoryContents :: OsPath -> IO [OsPath]
getDirectoryContents :: OsString -> IO [OsString]
getDirectoryContents OsString
path =
((IOError -> OsString -> IOError
`ioeSetOsPath` OsString
path) (IOError -> IOError) -> (IOError -> IOError) -> IOError -> IOError
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(IOError -> String -> IOError
`ioeAddLocation` String
"getDirectoryContents")) (IOError -> IOError) -> IO [OsString] -> IO [OsString]
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> IO [OsString]
getDirectoryContentsInternal OsString
path
listDirectory :: OsPath -> IO [OsPath]
listDirectory :: OsString -> IO [OsString]
listDirectory OsString
path = [OsString] -> [OsString]
dropSpecialDotDirs ([OsString] -> [OsString]) -> IO [OsString] -> IO [OsString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsString -> IO [OsString]
getDirectoryContents OsString
path
getCurrentDirectory :: IO OsPath
getCurrentDirectory :: IO OsString
getCurrentDirectory =
(IOError -> String -> IOError
`ioeAddLocation` String
"getCurrentDirectory") (IOError -> IOError) -> IO OsString -> IO OsString
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
String -> (IOError -> Bool) -> IO OsString -> IO OsString
forall a. String -> (IOError -> Bool) -> IO a -> IO a
specializeErrorString
String
"Current working directory no longer exists"
IOError -> Bool
isDoesNotExistError
IO OsString
getCurrentDirectoryInternal
setCurrentDirectory :: OsPath -> IO ()
setCurrentDirectory :: OsString -> IO ()
setCurrentDirectory = OsString -> IO ()
setCurrentDirectoryInternal
withCurrentDirectory :: OsPath
-> IO a
-> IO a
withCurrentDirectory :: forall a. OsString -> IO a -> IO a
withCurrentDirectory OsString
dir IO a
action =
IO OsString -> (OsString -> IO ()) -> (OsString -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO OsString
getCurrentDirectory OsString -> IO ()
setCurrentDirectory ((OsString -> IO a) -> IO a) -> (OsString -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \ OsString
_ -> do
OsString -> IO ()
setCurrentDirectory OsString
dir
IO a
action
getFileSize :: OsPath -> IO Integer
getFileSize :: OsString -> IO Integer
getFileSize OsString
path =
(IOError -> String -> IOError
`ioeAddLocation` String
"getFileSize") (IOError -> IOError) -> IO Integer -> IO Integer
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
Metadata -> Integer
fileSizeFromMetadata (Metadata -> Integer) -> IO Metadata -> IO Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsString -> IO Metadata
getFileMetadata OsString
path
doesPathExist :: OsPath -> IO Bool
doesPathExist :: OsString -> IO Bool
doesPathExist OsString
path = do
(Bool
True Bool -> IO Metadata -> IO Bool
forall a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ OsString -> IO Metadata
getFileMetadata OsString
path)
IO Bool -> (IOError -> IO Bool) -> IO Bool
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` \ IOError
_ ->
Bool -> IO Bool
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
doesDirectoryExist :: OsPath -> IO Bool
doesDirectoryExist :: OsString -> IO Bool
doesDirectoryExist OsString
path = do
OsString -> IO Bool
pathIsDirectory OsString
path
IO Bool -> (IOError -> IO Bool) -> IO Bool
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` \ IOError
_ ->
Bool -> IO Bool
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
doesFileExist :: OsPath -> IO Bool
doesFileExist :: OsString -> IO Bool
doesFileExist OsString
path = do
(Bool -> Bool
not (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsString -> IO Bool
pathIsDirectory OsString
path)
IO Bool -> (IOError -> IO Bool) -> IO Bool
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` \ IOError
_ ->
Bool -> IO Bool
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
pathIsDirectory :: OsPath -> IO Bool
pathIsDirectory :: OsString -> IO Bool
pathIsDirectory OsString
path =
(IOError -> String -> IOError
`ioeAddLocation` String
"pathIsDirectory") (IOError -> IOError) -> IO Bool -> IO Bool
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
FileType -> Bool
fileTypeIsDirectory (FileType -> Bool) -> (Metadata -> FileType) -> Metadata -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> FileType
fileTypeFromMetadata (Metadata -> Bool) -> IO Metadata -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsString -> IO Metadata
getFileMetadata OsString
path
createFileLink
:: OsPath
-> OsPath
-> IO ()
createFileLink :: OsString -> OsString -> IO ()
createFileLink OsString
target OsString
link =
(IOError -> String -> IOError
`ioeAddLocation` String
"createFileLink") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
Bool -> OsString -> OsString -> IO ()
createSymbolicLink Bool
False OsString
target OsString
link
createDirectoryLink
:: OsPath
-> OsPath
-> IO ()
createDirectoryLink :: OsString -> OsString -> IO ()
createDirectoryLink OsString
target OsString
link =
(IOError -> String -> IOError
`ioeAddLocation` String
"createDirectoryLink") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
Bool -> OsString -> OsString -> IO ()
createSymbolicLink Bool
True OsString
target OsString
link
removeDirectoryLink :: OsPath -> IO ()
removeDirectoryLink :: OsString -> IO ()
removeDirectoryLink OsString
path =
(IOError -> String -> IOError
`ioeAddLocation` String
"removeDirectoryLink") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
Bool -> OsString -> IO ()
removePathInternal Bool
linkToDirectoryIsDirectory OsString
path
pathIsSymbolicLink :: OsPath -> IO Bool
pathIsSymbolicLink :: OsString -> IO Bool
pathIsSymbolicLink OsString
path =
((IOError -> String -> IOError
`ioeAddLocation` String
"pathIsSymbolicLink") (IOError -> IOError) -> (IOError -> IOError) -> IOError -> IOError
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(IOError -> OsString -> IOError
`ioeSetOsPath` OsString
path)) (IOError -> IOError) -> IO Bool -> IO Bool
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
FileType -> Bool
fileTypeIsLink (FileType -> Bool) -> (Metadata -> FileType) -> Metadata -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> FileType
fileTypeFromMetadata (Metadata -> Bool) -> IO Metadata -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsString -> IO Metadata
getSymbolicLinkMetadata OsString
path
getSymbolicLinkTarget :: OsPath -> IO OsPath
getSymbolicLinkTarget :: OsString -> IO OsString
getSymbolicLinkTarget OsString
path =
(IOError -> String -> IOError
`ioeAddLocation` String
"getSymbolicLinkTarget") (IOError -> IOError) -> IO OsString -> IO OsString
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> IO OsString
readSymbolicLink OsString
path
getAccessTime :: OsPath -> IO UTCTime
getAccessTime :: OsString -> IO UTCTime
getAccessTime OsString
path =
(IOError -> String -> IOError
`ioeAddLocation` String
"getAccessTime") (IOError -> IOError) -> IO UTCTime -> IO UTCTime
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
Metadata -> UTCTime
accessTimeFromMetadata (Metadata -> UTCTime) -> IO Metadata -> IO UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsString -> IO Metadata
getFileMetadata (OsString -> OsString
emptyToCurDir OsString
path)
getModificationTime :: OsPath -> IO UTCTime
getModificationTime :: OsString -> IO UTCTime
getModificationTime OsString
path =
(IOError -> String -> IOError
`ioeAddLocation` String
"getModificationTime") (IOError -> IOError) -> IO UTCTime -> IO UTCTime
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
Metadata -> UTCTime
modificationTimeFromMetadata (Metadata -> UTCTime) -> IO Metadata -> IO UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsString -> IO Metadata
getFileMetadata (OsString -> OsString
emptyToCurDir OsString
path)
setAccessTime :: OsPath -> UTCTime -> IO ()
setAccessTime :: OsString -> UTCTime -> IO ()
setAccessTime OsString
path UTCTime
atime =
(IOError -> String -> IOError
`ioeAddLocation` String
"setAccessTime") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> (Maybe UTCTime, Maybe UTCTime) -> IO ()
setFileTimes OsString
path (UTCTime -> Maybe UTCTime
forall a. a -> Maybe a
Just UTCTime
atime, Maybe UTCTime
forall a. Maybe a
Nothing)
setModificationTime :: OsPath -> UTCTime -> IO ()
setModificationTime :: OsString -> UTCTime -> IO ()
setModificationTime OsString
path UTCTime
mtime =
(IOError -> String -> IOError
`ioeAddLocation` String
"setModificationTime") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> (Maybe UTCTime, Maybe UTCTime) -> IO ()
setFileTimes OsString
path (Maybe UTCTime
forall a. Maybe a
Nothing, UTCTime -> Maybe UTCTime
forall a. a -> Maybe a
Just UTCTime
mtime)
setFileTimes :: OsPath -> (Maybe UTCTime, Maybe UTCTime) -> IO ()
setFileTimes :: OsString -> (Maybe UTCTime, Maybe UTCTime) -> IO ()
setFileTimes OsString
_ (Maybe UTCTime
Nothing, Maybe UTCTime
Nothing) = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
setFileTimes OsString
path (Maybe UTCTime
atime, Maybe UTCTime
mtime) =
((IOError -> String -> IOError
`ioeAddLocation` String
"setFileTimes") (IOError -> IOError) -> (IOError -> IOError) -> IOError -> IOError
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(IOError -> OsString -> IOError
`ioeSetOsPath` OsString
path)) (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> (Maybe POSIXTime, Maybe POSIXTime) -> IO ()
setTimes (OsString -> OsString
emptyToCurDir OsString
path)
(UTCTime -> POSIXTime
utcTimeToPOSIXSeconds (UTCTime -> POSIXTime) -> Maybe UTCTime -> Maybe POSIXTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe UTCTime
atime, UTCTime -> POSIXTime
utcTimeToPOSIXSeconds (UTCTime -> POSIXTime) -> Maybe UTCTime -> Maybe POSIXTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe UTCTime
mtime)
getHomeDirectory :: IO OsPath
getHomeDirectory :: IO OsString
getHomeDirectory =
(IOError -> String -> IOError
`ioeAddLocation` String
"getHomeDirectory") (IOError -> IOError) -> IO OsString -> IO OsString
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
getHomeDirectoryInternal
getXdgDirectory :: XdgDirectory
-> OsPath
-> IO OsPath
getXdgDirectory :: XdgDirectory -> OsString -> IO OsString
getXdgDirectory XdgDirectory
xdgDir OsString
suffix =
(IOError -> String -> IOError
`ioeAddLocation` String
"getXdgDirectory") (IOError -> IOError) -> IO OsString -> IO OsString
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> OsString
simplify (OsString -> OsString)
-> (OsString -> OsString) -> OsString -> OsString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (OsString -> OsString -> OsString
</> OsString
suffix) (OsString -> OsString) -> IO OsString -> IO OsString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
env <- OsString -> IO (Maybe OsString)
lookupEnvOs (OsString -> IO (Maybe OsString))
-> (String -> OsString) -> String -> IO (Maybe OsString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> OsString
os (String -> IO (Maybe OsString)) -> String -> IO (Maybe OsString)
forall a b. (a -> b) -> a -> b
$ case XdgDirectory
xdgDir of
XdgDirectory
XdgData -> String
"XDG_DATA_HOME"
XdgDirectory
XdgConfig -> String
"XDG_CONFIG_HOME"
XdgDirectory
XdgCache -> String
"XDG_CACHE_HOME"
XdgDirectory
XdgState -> String
"XDG_STATE_HOME"
case env of
Just OsString
path | OsString -> Bool
isAbsolute OsString
path -> OsString -> IO OsString
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OsString
path
Maybe OsString
_ -> IO OsString -> XdgDirectory -> IO OsString
getXdgDirectoryFallback IO OsString
getHomeDirectory XdgDirectory
xdgDir
getXdgDirectoryList :: XdgDirectoryList
-> IO [OsPath]
getXdgDirectoryList :: XdgDirectoryList -> IO [OsString]
getXdgDirectoryList XdgDirectoryList
xdgDirs =
(IOError -> String -> IOError
`ioeAddLocation` String
"getXdgDirectoryList") (IOError -> IOError) -> IO [OsString] -> IO [OsString]
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
env <- OsString -> IO (Maybe OsString)
lookupEnvOs (OsString -> IO (Maybe OsString))
-> (String -> OsString) -> String -> IO (Maybe OsString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> OsString
os (String -> IO (Maybe OsString)) -> String -> IO (Maybe OsString)
forall a b. (a -> b) -> a -> b
$ case XdgDirectoryList
xdgDirs of
XdgDirectoryList
XdgDataDirs -> String
"XDG_DATA_DIRS"
XdgDirectoryList
XdgConfigDirs -> String
"XDG_CONFIG_DIRS"
case env of
Maybe OsString
Nothing -> XdgDirectoryList -> IO [OsString]
getXdgDirectoryListFallback XdgDirectoryList
xdgDirs
Just OsString
paths -> [OsString] -> IO [OsString]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (OsString -> [OsString]
splitSearchPath OsString
paths)
getAppUserDataDirectory :: OsPath
-> IO OsPath
getAppUserDataDirectory :: OsString -> IO OsString
getAppUserDataDirectory OsString
appName = do
(IOError -> String -> IOError
`ioeAddLocation` String
"getAppUserDataDirectory") (IOError -> IOError) -> IO OsString -> IO OsString
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
OsString -> IO OsString
getAppUserDataDirectoryInternal OsString
appName
getUserDocumentsDirectory :: IO OsPath
getUserDocumentsDirectory :: IO OsString
getUserDocumentsDirectory = do
(IOError -> String -> IOError
`ioeAddLocation` String
"getUserDocumentsDirectory") (IOError -> IOError) -> IO OsString -> IO OsString
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
getUserDocumentsDirectoryInternal
getTemporaryDirectory :: IO OsPath
getTemporaryDirectory :: IO OsString
getTemporaryDirectory = IO OsString
getTemporaryDirectoryInternal
getExecSearchPath :: IO [OsPath]
getExecSearchPath :: IO [OsString]
getExecSearchPath = IO [OsString]
getPath