module System.Directory.OsPath
   (
    
    
      createDirectory
    , createDirectoryIfMissing
    , removeDirectory
    , removeDirectoryRecursive
    , removePathForcibly
    , renameDirectory
    , listDirectory
    , getDirectoryContents
    
    , getCurrentDirectory
    , setCurrentDirectory
    , withCurrentDirectory
    
    , getHomeDirectory
    , XdgDirectory(..)
    , getXdgDirectory
    , XdgDirectoryList(..)
    , getXdgDirectoryList
    , getAppUserDataDirectory
    , getUserDocumentsDirectory
    , getTemporaryDirectory
    
    , 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 System.OsPath
  ( (<.>)
  , (</>)
  , addTrailingPathSeparator
  , decodeFS
  , dropTrailingPathSeparator
  , encodeFS
  , hasTrailingPathSeparator
  , isAbsolute
  , joinPath
  , makeRelative
  , splitDirectories
  , splitSearchPath
  , takeDirectory
  )
import qualified Data.List.NonEmpty as NE
import Data.Time (UTCTime)
import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds)
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 :: OsPath -> IO Permissions
getPermissions OsPath
path =
  (IOError -> String -> IOError
`ioeAddLocation` String
"getPermissions") (IOError -> IOError) -> IO Permissions -> IO Permissions
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> IO Permissions
getAccessPermissions (OsPath -> OsPath
emptyToCurDir OsPath
path)
setPermissions :: OsPath -> Permissions -> IO ()
setPermissions :: OsPath -> Permissions -> IO ()
setPermissions OsPath
path Permissions
p =
  (IOError -> String -> IOError
`ioeAddLocation` String
"setPermissions") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> Permissions -> IO ()
setAccessPermissions (OsPath -> OsPath
emptyToCurDir OsPath
path) Permissions
p
copyPermissions :: OsPath -> OsPath -> IO ()
copyPermissions :: OsPath -> OsPath -> IO ()
copyPermissions OsPath
src OsPath
dst =
  (IOError -> String -> IOError
`ioeAddLocation` String
"copyPermissions") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    Metadata
m <- OsPath -> IO Metadata
getFileMetadata OsPath
src
    Metadata -> OsPath -> IO ()
copyPermissionsFromMetadata Metadata
m OsPath
dst
copyPermissionsFromMetadata :: Metadata -> OsPath -> IO ()
copyPermissionsFromMetadata :: Metadata -> OsPath -> IO ()
copyPermissionsFromMetadata Metadata
m OsPath
dst = do
  
  
  OsPath -> Mode -> IO ()
setFilePermissions OsPath
dst (Metadata -> Mode
modeFromMetadata Metadata
m)
createDirectory :: OsPath -> IO ()
createDirectory :: OsPath -> IO ()
createDirectory = OsPath -> IO ()
createDirectoryInternal
createDirectoryIfMissing :: Bool     
                         -> OsPath 
                         -> IO ()
createDirectoryIfMissing :: Bool -> OsPath -> IO ()
createDirectoryIfMissing Bool
create_parents OsPath
path0
  | Bool
create_parents = [OsPath] -> IO ()
createDirs (OsPath -> [OsPath]
parents OsPath
path0)
  | Bool
otherwise      = [OsPath] -> IO ()
createDirs (Int -> [OsPath] -> [OsPath]
forall a. Int -> [a] -> [a]
take Int
1 (OsPath -> [OsPath]
parents OsPath
path0))
  where
    parents :: OsPath -> [OsPath]
parents = [OsPath] -> [OsPath]
forall a. [a] -> [a]
reverse ([OsPath] -> [OsPath])
-> (OsPath -> [OsPath]) -> OsPath -> [OsPath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (OsPath -> OsPath -> OsPath) -> [OsPath] -> [OsPath]
forall a. (a -> a -> a) -> [a] -> [a]
scanl1 OsPath -> OsPath -> OsPath
(</>) ([OsPath] -> [OsPath])
-> (OsPath -> [OsPath]) -> OsPath -> [OsPath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> [OsPath]
splitDirectories (OsPath -> [OsPath]) -> (OsPath -> OsPath) -> OsPath -> [OsPath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath
simplify
    createDirs :: [OsPath] -> IO ()
createDirs []         = () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
    createDirs (OsPath
dir:[])   = OsPath -> (IOError -> IO ()) -> IO ()
createDir OsPath
dir IOError -> IO ()
forall a. IOError -> IO a
ioError
    createDirs (OsPath
dir:[OsPath]
dirs) =
      OsPath -> (IOError -> IO ()) -> IO ()
createDir OsPath
dir ((IOError -> IO ()) -> IO ()) -> (IOError -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IOError
_ -> do
        [OsPath] -> IO ()
createDirs [OsPath]
dirs
        OsPath -> (IOError -> IO ()) -> IO ()
createDir OsPath
dir IOError -> IO ()
forall a. IOError -> IO a
ioError
    createDir :: OsPath -> (IOError -> IO ()) -> IO ()
createDir OsPath
dir IOError -> IO ()
notExistHandler = do
      Either IOError ()
r <- IO () -> IO (Either IOError ())
forall a. IO a -> IO (Either IOError a)
tryIOError (OsPath -> IO ()
createDirectory OsPath
dir)
      case Either IOError ()
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
              Bool
canIgnore <- OsPath -> IO Bool
pathIsDirectory OsPath
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)
              Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
canIgnore (IOError -> IO ()
forall a. IOError -> IO a
ioError IOError
e)
          | Bool
otherwise              -> IOError -> IO ()
forall a. IOError -> IO a
ioError IOError
e
removeDirectory :: OsPath -> IO ()
removeDirectory :: OsPath -> IO ()
removeDirectory = Bool -> OsPath -> IO ()
removePathInternal Bool
True
removeDirectoryRecursive :: OsPath -> IO ()
removeDirectoryRecursive :: OsPath -> IO ()
removeDirectoryRecursive OsPath
path =
  (IOError -> String -> IOError
`ioeAddLocation` String
"removeDirectoryRecursive") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    Metadata
m <- OsPath -> IO Metadata
getSymbolicLinkMetadata OsPath
path
    case Metadata -> FileType
fileTypeFromMetadata Metadata
m of
      FileType
Directory ->
        OsPath -> IO ()
removeContentsRecursive OsPath
path
      FileType
DirectoryLink ->
        IOError -> IO ()
forall a. IOError -> IO a
ioError (IOError
err IOError -> String -> IOError
`ioeSetErrorString` String
"is a directory symbolic link")
      FileType
_ ->
        IOError -> IO ()
forall a. 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 -> OsPath -> IOError
`ioeSetOsPath` OsPath
path
removePathRecursive :: OsPath -> IO ()
removePathRecursive :: OsPath -> IO ()
removePathRecursive OsPath
path =
  (IOError -> String -> IOError
`ioeAddLocation` String
"removePathRecursive") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    Metadata
m <- OsPath -> IO Metadata
getSymbolicLinkMetadata OsPath
path
    case Metadata -> FileType
fileTypeFromMetadata Metadata
m of
      FileType
Directory     -> OsPath -> IO ()
removeContentsRecursive OsPath
path
      FileType
DirectoryLink -> OsPath -> IO ()
removeDirectory OsPath
path
      FileType
_             -> OsPath -> IO ()
removeFile OsPath
path
removeContentsRecursive :: OsPath -> IO ()
removeContentsRecursive :: OsPath -> IO ()
removeContentsRecursive OsPath
path =
  (IOError -> String -> IOError
`ioeAddLocation` String
"removeContentsRecursive") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    [OsPath]
cont <- OsPath -> IO [OsPath]
listDirectory OsPath
path
    [OsPath] -> (OsPath -> IO ()) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [OsPath
path OsPath -> OsPath -> OsPath
</> OsPath
x | OsPath
x <- [OsPath]
cont] OsPath -> IO ()
removePathRecursive
    OsPath -> IO ()
removeDirectory OsPath
path
removePathForcibly :: OsPath -> IO ()
removePathForcibly :: OsPath -> IO ()
removePathForcibly OsPath
path =
  (IOError -> String -> IOError
`ioeAddLocation` String
"removePathForcibly") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    IO () -> IO ()
ignoreDoesNotExistError (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
      Metadata
m <- OsPath -> IO Metadata
getSymbolicLinkMetadata OsPath
path
      case Metadata -> FileType
fileTypeFromMetadata Metadata
m of
        FileType
DirectoryLink -> do
          OsPath -> IO ()
makeRemovable OsPath
path
          OsPath -> IO ()
removeDirectory OsPath
path
        FileType
Directory -> do
          OsPath -> IO ()
makeRemovable OsPath
path
          [OsPath]
names <- OsPath -> IO [OsPath]
listDirectory OsPath
path
          [IO ()] -> IO ()
sequenceWithIOErrors_ ([IO ()] -> IO ()) -> [IO ()] -> IO ()
forall a b. (a -> b) -> a -> b
$
            [ OsPath -> IO ()
removePathForcibly (OsPath
path OsPath -> OsPath -> OsPath
</> OsPath
name) | OsPath
name <- [OsPath]
names ] [IO ()] -> [IO ()] -> [IO ()]
forall a. [a] -> [a] -> [a]
++
            [ OsPath -> IO ()
removeDirectory OsPath
path ]
        FileType
_ -> do
          Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
filesAlwaysRemovable (OsPath -> IO ()
makeRemovable OsPath
path)
          OsPath -> IO ()
removeFile OsPath
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
    makeRemovable :: OsPath -> IO ()
    makeRemovable :: OsPath -> IO ()
makeRemovable OsPath
p = (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 ()) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
      Permissions
perms <- OsPath -> IO Permissions
getPermissions OsPath
p
      OsPath -> Permissions -> IO ()
setPermissions OsPath
path Permissions
perms{ readable = True
                               , searchable = True
                               , writable = True }
removeFile :: OsPath -> IO ()
removeFile :: OsPath -> IO ()
removeFile = Bool -> OsPath -> IO ()
removePathInternal Bool
False
renameDirectory :: OsPath -> OsPath -> IO ()
renameDirectory :: OsPath -> OsPath -> IO ()
renameDirectory OsPath
opath OsPath
npath =
   (IOError -> String -> IOError
`ioeAddLocation` String
"renameDirectory") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
     
     Bool
isDir <- OsPath -> IO Bool
pathIsDirectory OsPath
opath
     Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
isDir) (IO () -> IO ()) -> (IOError -> IO ()) -> IOError -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> IO ()
forall a. 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
"renameDirectory" Maybe Handle
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
       IOError -> String -> IOError
`ioeSetErrorString` String
"not a directory"
       IOError -> OsPath -> IOError
`ioeSetOsPath` OsPath
opath
     OsPath -> OsPath -> IO ()
renamePath OsPath
opath OsPath
npath
renameFile :: OsPath -> OsPath -> IO ()
renameFile :: OsPath -> OsPath -> IO ()
renameFile OsPath
opath OsPath
npath =
  (IOError -> String -> IOError
`ioeAddLocation` String
"renameFile") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    
    OsPath -> IO ()
checkNotDir OsPath
opath
    OsPath -> OsPath -> IO ()
renamePath OsPath
opath OsPath
npath
      
      
      
      
      
      
      IO () -> (IOError -> IO ()) -> IO ()
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` \ IOError
err -> do
        OsPath -> IO ()
checkNotDir OsPath
npath
        IOError -> IO ()
forall a. IOError -> IO a
ioError IOError
err
  where checkNotDir :: OsPath -> IO ()
checkNotDir OsPath
path = do
          Either IOError Metadata
m <- IO Metadata -> IO (Either IOError Metadata)
forall a. IO a -> IO (Either IOError a)
tryIOError (OsPath -> IO Metadata
getSymbolicLinkMetadata OsPath
path)
          case FileType -> Bool
fileTypeIsDirectory (FileType -> Bool) -> (Metadata -> FileType) -> Metadata -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> FileType
fileTypeFromMetadata (Metadata -> Bool)
-> Either IOError Metadata -> Either IOError Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either IOError Metadata
m of
            Right Bool
True ->
              IOError -> IO ()
forall a. 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 -> OsPath -> IOError
`ioeSetOsPath` OsPath
path
            Either IOError Bool
_          -> () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
renamePath :: OsPath                  
           -> OsPath                  
           -> IO ()
renamePath :: OsPath -> OsPath -> IO ()
renamePath OsPath
opath OsPath
npath =
  (IOError -> String -> IOError
`ioeAddLocation` String
"renamePath") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> OsPath -> IO ()
renamePathInternal OsPath
opath OsPath
npath
copyFile :: OsPath                    
         -> OsPath                    
         -> IO ()
copyFile :: OsPath -> OsPath -> IO ()
copyFile OsPath
fromFPath OsPath
toFPath =
  (IOError -> String -> IOError
`ioeAddLocation` String
"copyFile") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> OsPath -> (OsPath -> IO ()) -> IO ()
atomicCopyFileContents OsPath
fromFPath OsPath
toFPath
      (IO () -> IO ()
ignoreIOExceptions (IO () -> IO ()) -> (OsPath -> IO ()) -> OsPath -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath -> IO ()
copyPermissions OsPath
fromFPath)
copyFileToHandle :: OsPath              
                 -> Handle              
                 -> IO ()
copyFileToHandle :: OsPath -> Handle -> IO ()
copyFileToHandle OsPath
fromFPath Handle
hTo =
  (IOError -> String -> IOError
`ioeAddLocation` String
"copyFileToHandle") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    IO Handle -> (Handle -> IO ()) -> IO ()
forall r. IO Handle -> (Handle -> IO r) -> IO r
withBinaryHandle (OsPath -> IO Handle
openFileForRead OsPath
fromFPath) ((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 :: OsPath -> OsPath -> (OsPath -> IO ()) -> IO ()
atomicCopyFileContents OsPath
fromFPath OsPath
toFPath OsPath -> IO ()
postAction =
  (IOError -> String -> IOError
`ioeAddLocation` String
"atomicCopyFileContents") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> (OsPath -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a. OsPath -> (OsPath -> IO ()) -> (Handle -> IO a) -> IO a
withReplacementFile OsPath
toFPath OsPath -> IO ()
postAction ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Handle
hTo -> do
      OsPath -> Handle -> IO ()
copyFileToHandle OsPath
fromFPath Handle
hTo
withReplacementFile :: OsPath            
                    -> (OsPath -> IO ()) 
                    -> (Handle -> IO a)    
                    -> IO a
withReplacementFile :: forall a. OsPath -> (OsPath -> IO ()) -> (Handle -> IO a) -> IO a
withReplacementFile OsPath
path OsPath -> 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
      
      
      
      
      String
d <- OsPath -> IO String
decodeFS (OsPath -> OsPath
takeDirectory OsPath
path)
      (String
tmpFPath', Handle
hTmp) <- String -> String -> IO (String, Handle)
openBinaryTempFile String
d String
".copyFile.tmp"
      OsPath
tmpFPath <- String -> IO OsPath
encodeFS String
tmpFPath'
      (IO a -> IO () -> IO a
forall a b. IO a -> IO b -> IO a
`onException` IO () -> IO ()
ignoreIOExceptions (OsPath -> IO ()
removeFile OsPath
tmpFPath)) (IO a -> IO a) -> IO a -> IO a
forall a b. (a -> b) -> a -> b
$ do
        a
r <- (IO a -> IO () -> IO a
forall a b. IO a -> IO b -> IO a
`onException` IO () -> IO ()
ignoreIOExceptions (Handle -> IO ()
hClose Handle
hTmp)) (IO a -> IO a) -> IO a -> IO a
forall a b. (a -> b) -> a -> b
$ do
          IO a -> IO a
forall a. IO a -> IO a
restore (Handle -> IO a
action Handle
hTmp)
        Handle -> IO ()
hClose Handle
hTmp
        IO () -> IO ()
forall a. IO a -> IO a
restore (OsPath -> IO ()
postAction OsPath
tmpFPath)
        OsPath -> OsPath -> IO ()
renameFile OsPath
tmpFPath OsPath
path
        a -> IO a
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
r
copyFileWithMetadata :: OsPath        
                     -> OsPath        
                     -> IO ()
copyFileWithMetadata :: OsPath -> OsPath -> IO ()
copyFileWithMetadata OsPath
src OsPath
dst =
  (IOError -> String -> IOError
`ioeAddLocation` String
"copyFileWithMetadata") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError`
    (Metadata -> OsPath -> IO ())
-> (Metadata -> OsPath -> IO ()) -> OsPath -> OsPath -> IO ()
copyFileWithMetadataInternal Metadata -> OsPath -> IO ()
copyPermissionsFromMetadata
                                 Metadata -> OsPath -> IO ()
copyTimesFromMetadata
                                 OsPath
src
                                 OsPath
dst
copyTimesFromMetadata :: Metadata -> OsPath -> IO ()
copyTimesFromMetadata :: Metadata -> OsPath -> IO ()
copyTimesFromMetadata Metadata
st OsPath
dst = do
  let atime :: UTCTime
atime = Metadata -> UTCTime
accessTimeFromMetadata Metadata
st
  let mtime :: UTCTime
mtime = Metadata -> UTCTime
modificationTimeFromMetadata Metadata
st
  OsPath -> (Maybe UTCTime, Maybe UTCTime) -> IO ()
setFileTimes OsPath
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 :: OsPath -> IO OsPath
canonicalizePath = \ OsPath
path ->
  ((IOError -> String -> IOError
`ioeAddLocation` String
"canonicalizePath") (IOError -> IOError) -> (IOError -> IOError) -> IOError -> IOError
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
   (IOError -> OsPath -> IOError
`ioeSetOsPath` OsPath
path)) (IOError -> IOError) -> IO OsPath -> IO OsPath
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    
    OsPath -> OsPath
dropTrailingPathSeparator (OsPath -> OsPath) -> (OsPath -> OsPath) -> OsPath -> OsPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath
simplify (OsPath -> OsPath) -> IO OsPath -> IO OsPath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
      ((OsPath -> IO OsPath) -> OsPath -> IO OsPath
attemptRealpath OsPath -> IO OsPath
realPath (OsPath -> IO OsPath) -> IO OsPath -> IO OsPath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< OsPath -> IO OsPath
prependCurrentDirectory OsPath
path)
  where
    
    attemptRealpath :: (OsPath -> IO OsPath) -> OsPath -> IO OsPath
attemptRealpath OsPath -> IO OsPath
realpath =
      Int -> Maybe OsPath -> (OsPath -> IO OsPath) -> OsPath -> IO OsPath
forall {a}.
(Ord a, Num a) =>
a -> Maybe OsPath -> (OsPath -> IO OsPath) -> OsPath -> IO OsPath
attemptRealpathWith (Int
64 :: Int) Maybe OsPath
forall a. Maybe a
Nothing OsPath -> IO OsPath
realpath
      (OsPath -> IO OsPath)
-> (OsPath -> IO OsPath) -> OsPath -> IO OsPath
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< OsPath -> IO OsPath
canonicalizePathSimplify
    
    
    
    attemptRealpathWith :: a -> Maybe OsPath -> (OsPath -> IO OsPath) -> OsPath -> IO OsPath
attemptRealpathWith a
n Maybe OsPath
mFallback OsPath -> IO OsPath
realpath OsPath
path =
      case Maybe OsPath
mFallback of
        
        Just OsPath
fallback | a
n a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
0 -> OsPath -> IO OsPath
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OsPath
fallback
        
        
        Maybe OsPath
_ -> [(OsPath, OsPath)] -> IO OsPath
realpathPrefix ([(OsPath, OsPath)] -> [(OsPath, OsPath)]
forall a. [a] -> [a]
reverse ([OsPath] -> [OsPath] -> [(OsPath, OsPath)]
forall a b. [a] -> [b] -> [(a, b)]
zip [OsPath]
prefixes [OsPath]
suffixes))
      where
        segments :: [OsPath]
segments = OsPath -> [OsPath]
splitDirectories OsPath
path
        prefixes :: [OsPath]
prefixes = (OsPath -> OsPath -> OsPath) -> [OsPath] -> [OsPath]
forall a. (a -> a -> a) -> [a] -> [a]
scanl1 OsPath -> OsPath -> OsPath
(</>) [OsPath]
segments
        suffixes :: [OsPath]
suffixes = NonEmpty OsPath -> [OsPath]
forall a. NonEmpty a -> [a]
NE.tail ((OsPath -> OsPath -> OsPath)
-> OsPath -> [OsPath] -> NonEmpty OsPath
forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> f a -> NonEmpty b
NE.scanr OsPath -> OsPath -> OsPath
(</>) OsPath
forall a. Monoid a => a
mempty [OsPath]
segments)
        
        realpathPrefix :: [(OsPath, OsPath)] -> IO OsPath
realpathPrefix [(OsPath, OsPath)]
candidates =
          case [(OsPath, OsPath)]
candidates of
            [] -> OsPath -> IO OsPath
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OsPath
path
            (OsPath
prefix, OsPath
suffix) : [(OsPath, OsPath)]
rest -> do
              Bool
exist <- OsPath -> IO Bool
doesPathExist OsPath
prefix
              if Bool -> Bool
not Bool
exist
                
                
                
                then [(OsPath, OsPath)] -> IO OsPath
realpathPrefix [(OsPath, OsPath)]
rest
                else do
                  Either IOError OsPath
mp <- IO OsPath -> IO (Either IOError OsPath)
forall a. IO a -> IO (Either IOError a)
tryIOError (OsPath -> IO OsPath
realpath OsPath
prefix)
                  case Either IOError OsPath
mp of
                    
                    Left IOError
_ -> [(OsPath, OsPath)] -> IO OsPath
realpathPrefix [(OsPath, OsPath)]
rest
                    
                    Right OsPath
p -> OsPath -> OsPath -> OsPath -> IO OsPath
realpathFurther (OsPath
p OsPath -> OsPath -> OsPath
</> OsPath
suffix) OsPath
p OsPath
suffix
        
        
        
        
        realpathFurther :: OsPath -> OsPath -> OsPath -> IO OsPath
realpathFurther OsPath
fallback OsPath
p OsPath
suffix =
          case OsPath -> [OsPath]
splitDirectories OsPath
suffix of
            [] -> OsPath -> IO OsPath
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OsPath
fallback
            OsPath
next : [OsPath]
restSuffix -> do
              
              Either IOError OsPath
mTarget <- IO OsPath -> IO (Either IOError OsPath)
forall a. IO a -> IO (Either IOError a)
tryIOError (OsPath -> IO OsPath
getSymbolicLinkTarget (OsPath
p OsPath -> OsPath -> OsPath
</> OsPath
next))
              case Either IOError OsPath
mTarget of
                Left IOError
_ -> OsPath -> IO OsPath
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OsPath
fallback
                Right OsPath
target -> do
                  
                  let mFallback' :: Maybe OsPath
mFallback' = OsPath -> Maybe OsPath
forall a. a -> Maybe a
Just (OsPath -> Maybe OsPath -> OsPath
forall a. a -> Maybe a -> a
fromMaybe OsPath
fallback Maybe OsPath
mFallback)
                  OsPath
path' <- OsPath -> IO OsPath
canonicalizePathSimplify
                             (OsPath
p OsPath -> OsPath -> OsPath
</> OsPath
target OsPath -> OsPath -> OsPath
</> [OsPath] -> OsPath
joinPath [OsPath]
restSuffix)
                  a -> Maybe OsPath -> (OsPath -> IO OsPath) -> OsPath -> IO OsPath
attemptRealpathWith (a
n a -> a -> a
forall a. Num a => a -> a -> a
- a
1) Maybe OsPath
mFallback' OsPath -> IO OsPath
realpath OsPath
path'
makeAbsolute :: OsPath -> IO OsPath
makeAbsolute :: OsPath -> IO OsPath
makeAbsolute OsPath
path =
  ((IOError -> String -> IOError
`ioeAddLocation` String
"makeAbsolute") (IOError -> IOError) -> (IOError -> IOError) -> IOError -> IOError
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
   (IOError -> OsPath -> IOError
`ioeSetOsPath` OsPath
path)) (IOError -> IOError) -> IO OsPath -> IO OsPath
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> OsPath -> OsPath
matchTrailingSeparator OsPath
path (OsPath -> OsPath) -> (OsPath -> OsPath) -> OsPath -> OsPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath
simplify (OsPath -> OsPath) -> IO OsPath -> IO OsPath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsPath -> IO OsPath
prependCurrentDirectory OsPath
path
matchTrailingSeparator :: OsPath -> OsPath -> OsPath
matchTrailingSeparator :: OsPath -> OsPath -> OsPath
matchTrailingSeparator OsPath
path
  | OsPath -> Bool
hasTrailingPathSeparator OsPath
path = OsPath -> OsPath
addTrailingPathSeparator
  | Bool
otherwise                     = OsPath -> OsPath
dropTrailingPathSeparator
makeRelativeToCurrentDirectory :: OsPath -> IO OsPath
makeRelativeToCurrentDirectory :: OsPath -> IO OsPath
makeRelativeToCurrentDirectory OsPath
x = do
  (OsPath -> OsPath -> OsPath
`makeRelative` OsPath
x) (OsPath -> OsPath) -> IO OsPath -> IO OsPath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO OsPath
getCurrentDirectory
findExecutable :: OsString -> IO (Maybe OsPath)
findExecutable :: OsPath -> IO (Maybe OsPath)
findExecutable OsPath
binary =
  ListT IO OsPath -> IO (Maybe OsPath)
forall (m :: * -> *) a. Functor m => ListT m a -> m (Maybe a)
listTHead
    (([OsPath] -> OsPath -> ListT IO OsPath)
-> OsPath -> ListT IO OsPath
findExecutablesLazyInternal [OsPath] -> OsPath -> ListT IO OsPath
findExecutablesInDirectoriesLazy OsPath
binary)
findExecutables :: OsString -> IO [OsPath]
findExecutables :: OsPath -> IO [OsPath]
findExecutables OsPath
binary =
  ListT IO OsPath -> IO [OsPath]
forall (m :: * -> *) a. Monad m => ListT m a -> m [a]
listTToList
    (([OsPath] -> OsPath -> ListT IO OsPath)
-> OsPath -> ListT IO OsPath
findExecutablesLazyInternal [OsPath] -> OsPath -> ListT IO OsPath
findExecutablesInDirectoriesLazy OsPath
binary)
findExecutablesInDirectories :: [OsPath] -> OsString -> IO [OsPath]
findExecutablesInDirectories :: [OsPath] -> OsPath -> IO [OsPath]
findExecutablesInDirectories [OsPath]
path OsPath
binary =
  ListT IO OsPath -> IO [OsPath]
forall (m :: * -> *) a. Monad m => ListT m a -> m [a]
listTToList ([OsPath] -> OsPath -> ListT IO OsPath
findExecutablesInDirectoriesLazy [OsPath]
path OsPath
binary)
findExecutablesInDirectoriesLazy :: [OsPath] -> OsString -> ListT IO OsPath
findExecutablesInDirectoriesLazy :: [OsPath] -> OsPath -> ListT IO OsPath
findExecutablesInDirectoriesLazy [OsPath]
path OsPath
binary =
  (OsPath -> IO Bool) -> [OsPath] -> OsPath -> ListT IO OsPath
findFilesWithLazy OsPath -> IO Bool
isExecutable [OsPath]
path (OsPath
binary OsPath -> OsPath -> OsPath
<.> OsPath
exeExtension)
isExecutable :: OsPath -> IO Bool
isExecutable :: OsPath -> IO Bool
isExecutable OsPath
file = Permissions -> Bool
executable (Permissions -> Bool) -> IO Permissions -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsPath -> IO Permissions
getPermissions OsPath
file
findFile :: [OsPath] -> OsString -> IO (Maybe OsPath)
findFile :: [OsPath] -> OsPath -> IO (Maybe OsPath)
findFile = (OsPath -> IO Bool) -> [OsPath] -> OsPath -> IO (Maybe OsPath)
findFileWith (\ OsPath
_ -> 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 :: [OsPath] -> OsPath -> IO [OsPath]
findFiles = (OsPath -> IO Bool) -> [OsPath] -> OsPath -> IO [OsPath]
findFilesWith (\ OsPath
_ -> 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 :: (OsPath -> IO Bool) -> [OsPath] -> OsPath -> IO (Maybe OsPath)
findFileWith OsPath -> IO Bool
f [OsPath]
ds OsPath
name = ListT IO OsPath -> IO (Maybe OsPath)
forall (m :: * -> *) a. Functor m => ListT m a -> m (Maybe a)
listTHead ((OsPath -> IO Bool) -> [OsPath] -> OsPath -> ListT IO OsPath
findFilesWithLazy OsPath -> IO Bool
f [OsPath]
ds OsPath
name)
findFilesWith :: (OsPath -> IO Bool) -> [OsPath] -> OsString -> IO [OsPath]
findFilesWith :: (OsPath -> IO Bool) -> [OsPath] -> OsPath -> IO [OsPath]
findFilesWith OsPath -> IO Bool
f [OsPath]
ds OsPath
name = ListT IO OsPath -> IO [OsPath]
forall (m :: * -> *) a. Monad m => ListT m a -> m [a]
listTToList ((OsPath -> IO Bool) -> [OsPath] -> OsPath -> ListT IO OsPath
findFilesWithLazy OsPath -> IO Bool
f [OsPath]
ds OsPath
name)
findFilesWithLazy
  :: (OsPath -> IO Bool) -> [OsPath] -> OsString -> ListT IO OsPath
findFilesWithLazy :: (OsPath -> IO Bool) -> [OsPath] -> OsPath -> ListT IO OsPath
findFilesWithLazy OsPath -> IO Bool
f [OsPath]
dirs OsPath
path
  
  
  | OsPath -> Bool
isAbsolute OsPath
path = IO (Maybe (OsPath, ListT IO OsPath)) -> ListT IO OsPath
forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT ([OsPath] -> IO (Maybe (OsPath, ListT IO OsPath))
find [OsPath
forall a. Monoid a => a
mempty])
  | Bool
otherwise       = IO (Maybe (OsPath, ListT IO OsPath)) -> ListT IO OsPath
forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT ([OsPath] -> IO (Maybe (OsPath, ListT IO OsPath))
find [OsPath]
dirs)
  where
    find :: [OsPath] -> IO (Maybe (OsPath, ListT IO OsPath))
find []       = Maybe (OsPath, ListT IO OsPath)
-> IO (Maybe (OsPath, ListT IO OsPath))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (OsPath, ListT IO OsPath)
forall a. Maybe a
Nothing
    find (OsPath
d : [OsPath]
ds) = do
      let p :: OsPath
p = OsPath
d OsPath -> OsPath -> OsPath
</> OsPath
path
      Bool
found <- OsPath -> IO Bool
doesFileExist OsPath
p IO Bool -> IO Bool -> IO Bool
forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
`andM` OsPath -> IO Bool
f OsPath
p
      if Bool
found
        then Maybe (OsPath, ListT IO OsPath)
-> IO (Maybe (OsPath, ListT IO OsPath))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((OsPath, ListT IO OsPath) -> Maybe (OsPath, ListT IO OsPath)
forall a. a -> Maybe a
Just (OsPath
p, IO (Maybe (OsPath, ListT IO OsPath)) -> ListT IO OsPath
forall (m :: * -> *) a. m (Maybe (a, ListT m a)) -> ListT m a
ListT ([OsPath] -> IO (Maybe (OsPath, ListT IO OsPath))
find [OsPath]
ds)))
        else [OsPath] -> IO (Maybe (OsPath, ListT IO OsPath))
find [OsPath]
ds
exeExtension :: OsString
exeExtension :: OsPath
exeExtension = OsPath
exeExtensionInternal
getDirectoryContents :: OsPath -> IO [OsPath]
getDirectoryContents :: OsPath -> IO [OsPath]
getDirectoryContents OsPath
path =
  ((IOError -> OsPath -> IOError
`ioeSetOsPath` OsPath
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 [OsPath] -> IO [OsPath]
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> IO [OsPath]
getDirectoryContentsInternal OsPath
path
listDirectory :: OsPath -> IO [OsPath]
listDirectory :: OsPath -> IO [OsPath]
listDirectory OsPath
path = (OsPath -> Bool) -> [OsPath] -> [OsPath]
forall a. (a -> Bool) -> [a] -> [a]
filter OsPath -> Bool
f ([OsPath] -> [OsPath]) -> IO [OsPath] -> IO [OsPath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsPath -> IO [OsPath]
getDirectoryContents OsPath
path
  where f :: OsPath -> Bool
f OsPath
filename = OsPath
filename OsPath -> OsPath -> Bool
forall a. Eq a => a -> a -> Bool
/= String -> OsPath
os String
"." Bool -> Bool -> Bool
&& OsPath
filename OsPath -> OsPath -> Bool
forall a. Eq a => a -> a -> Bool
/= String -> OsPath
os String
".."
getCurrentDirectory :: IO OsPath
getCurrentDirectory :: IO OsPath
getCurrentDirectory =
  (IOError -> String -> IOError
`ioeAddLocation` String
"getCurrentDirectory") (IOError -> IOError) -> IO OsPath -> IO OsPath
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    String -> (IOError -> Bool) -> IO OsPath -> IO OsPath
forall a. String -> (IOError -> Bool) -> IO a -> IO a
specializeErrorString
      String
"Current working directory no longer exists"
      IOError -> Bool
isDoesNotExistError
      IO OsPath
getCurrentDirectoryInternal
setCurrentDirectory :: OsPath -> IO ()
setCurrentDirectory :: OsPath -> IO ()
setCurrentDirectory = OsPath -> IO ()
setCurrentDirectoryInternal
withCurrentDirectory :: OsPath    
                     -> IO a      
                     -> IO a
withCurrentDirectory :: forall a. OsPath -> IO a -> IO a
withCurrentDirectory OsPath
dir IO a
action =
  IO OsPath -> (OsPath -> IO ()) -> (OsPath -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO OsPath
getCurrentDirectory OsPath -> IO ()
setCurrentDirectory ((OsPath -> IO a) -> IO a) -> (OsPath -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \ OsPath
_ -> do
    OsPath -> IO ()
setCurrentDirectory OsPath
dir
    IO a
action
getFileSize :: OsPath -> IO Integer
getFileSize :: OsPath -> IO Integer
getFileSize OsPath
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
<$> OsPath -> IO Metadata
getFileMetadata OsPath
path
doesPathExist :: OsPath -> IO Bool
doesPathExist :: OsPath -> IO Bool
doesPathExist OsPath
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
<$ OsPath -> IO Metadata
getFileMetadata OsPath
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 :: OsPath -> IO Bool
doesDirectoryExist OsPath
path = do
  OsPath -> IO Bool
pathIsDirectory OsPath
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 :: OsPath -> IO Bool
doesFileExist OsPath
path = do
  (Bool -> Bool
not (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OsPath -> IO Bool
pathIsDirectory OsPath
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 :: OsPath -> IO Bool
pathIsDirectory OsPath
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
<$> OsPath -> IO Metadata
getFileMetadata OsPath
path
createFileLink
  :: OsPath                           
  -> OsPath                           
  -> IO ()
createFileLink :: OsPath -> OsPath -> IO ()
createFileLink OsPath
target OsPath
link =
  (IOError -> String -> IOError
`ioeAddLocation` String
"createFileLink") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    Bool -> OsPath -> OsPath -> IO ()
createSymbolicLink Bool
False OsPath
target OsPath
link
createDirectoryLink
  :: OsPath                           
  -> OsPath                           
  -> IO ()
createDirectoryLink :: OsPath -> OsPath -> IO ()
createDirectoryLink OsPath
target OsPath
link =
  (IOError -> String -> IOError
`ioeAddLocation` String
"createDirectoryLink") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    Bool -> OsPath -> OsPath -> IO ()
createSymbolicLink Bool
True OsPath
target OsPath
link
removeDirectoryLink :: OsPath -> IO ()
removeDirectoryLink :: OsPath -> IO ()
removeDirectoryLink OsPath
path =
  (IOError -> String -> IOError
`ioeAddLocation` String
"removeDirectoryLink") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    Bool -> OsPath -> IO ()
removePathInternal Bool
linkToDirectoryIsDirectory OsPath
path
pathIsSymbolicLink :: OsPath -> IO Bool
pathIsSymbolicLink :: OsPath -> IO Bool
pathIsSymbolicLink OsPath
path =
  ((IOError -> String -> IOError
`ioeAddLocation` String
"pathIsSymbolicLink") (IOError -> IOError) -> (IOError -> IOError) -> IOError -> IOError
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
   (IOError -> OsPath -> IOError
`ioeSetOsPath` OsPath
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
<$> OsPath -> IO Metadata
getSymbolicLinkMetadata OsPath
path
getSymbolicLinkTarget :: OsPath -> IO OsPath
getSymbolicLinkTarget :: OsPath -> IO OsPath
getSymbolicLinkTarget OsPath
path =
  (IOError -> String -> IOError
`ioeAddLocation` String
"getSymbolicLinkTarget") (IOError -> IOError) -> IO OsPath -> IO OsPath
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> IO OsPath
readSymbolicLink OsPath
path
getAccessTime :: OsPath -> IO UTCTime
getAccessTime :: OsPath -> IO UTCTime
getAccessTime OsPath
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
<$> OsPath -> IO Metadata
getFileMetadata (OsPath -> OsPath
emptyToCurDir OsPath
path)
getModificationTime :: OsPath -> IO UTCTime
getModificationTime :: OsPath -> IO UTCTime
getModificationTime OsPath
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
<$> OsPath -> IO Metadata
getFileMetadata (OsPath -> OsPath
emptyToCurDir OsPath
path)
setAccessTime :: OsPath -> UTCTime -> IO ()
setAccessTime :: OsPath -> UTCTime -> IO ()
setAccessTime OsPath
path UTCTime
atime =
  (IOError -> String -> IOError
`ioeAddLocation` String
"setAccessTime") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> (Maybe UTCTime, Maybe UTCTime) -> IO ()
setFileTimes OsPath
path (UTCTime -> Maybe UTCTime
forall a. a -> Maybe a
Just UTCTime
atime, Maybe UTCTime
forall a. Maybe a
Nothing)
setModificationTime :: OsPath -> UTCTime -> IO ()
setModificationTime :: OsPath -> UTCTime -> IO ()
setModificationTime OsPath
path UTCTime
mtime =
  (IOError -> String -> IOError
`ioeAddLocation` String
"setModificationTime") (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> (Maybe UTCTime, Maybe UTCTime) -> IO ()
setFileTimes OsPath
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 :: OsPath -> (Maybe UTCTime, Maybe UTCTime) -> IO ()
setFileTimes OsPath
_ (Maybe UTCTime
Nothing, Maybe UTCTime
Nothing) = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
setFileTimes OsPath
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 -> OsPath -> IOError
`ioeSetOsPath` OsPath
path)) (IOError -> IOError) -> IO () -> IO ()
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> (Maybe POSIXTime, Maybe POSIXTime) -> IO ()
setTimes (OsPath -> OsPath
emptyToCurDir OsPath
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 OsPath
getHomeDirectory =
  (IOError -> String -> IOError
`ioeAddLocation` String
"getHomeDirectory") (IOError -> IOError) -> IO OsPath -> IO OsPath
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    IO OsPath
getHomeDirectoryInternal
getXdgDirectory :: XdgDirectory         
                -> OsPath             
                                        
                                        
                -> IO OsPath
getXdgDirectory :: XdgDirectory -> OsPath -> IO OsPath
getXdgDirectory XdgDirectory
xdgDir OsPath
suffix =
  (IOError -> String -> IOError
`ioeAddLocation` String
"getXdgDirectory") (IOError -> IOError) -> IO OsPath -> IO OsPath
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> OsPath
simplify (OsPath -> OsPath) -> (OsPath -> OsPath) -> OsPath -> OsPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (OsPath -> OsPath -> OsPath
</> OsPath
suffix) (OsPath -> OsPath) -> IO OsPath -> IO OsPath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
      Maybe OsPath
env <- OsPath -> IO (Maybe OsPath)
lookupEnvOs (OsPath -> IO (Maybe OsPath))
-> (String -> OsPath) -> String -> IO (Maybe OsPath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> OsPath
os (String -> IO (Maybe OsPath)) -> String -> IO (Maybe OsPath)
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 Maybe OsPath
env of
        Just OsPath
path | OsPath -> Bool
isAbsolute OsPath
path -> OsPath -> IO OsPath
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OsPath
path
        Maybe OsPath
_                           -> IO OsPath -> XdgDirectory -> IO OsPath
getXdgDirectoryFallback IO OsPath
getHomeDirectory XdgDirectory
xdgDir
getXdgDirectoryList :: XdgDirectoryList 
                    -> IO [OsPath]
getXdgDirectoryList :: XdgDirectoryList -> IO [OsPath]
getXdgDirectoryList XdgDirectoryList
xdgDirs =
  (IOError -> String -> IOError
`ioeAddLocation` String
"getXdgDirectoryList") (IOError -> IOError) -> IO [OsPath] -> IO [OsPath]
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    Maybe OsPath
env <- OsPath -> IO (Maybe OsPath)
lookupEnvOs (OsPath -> IO (Maybe OsPath))
-> (String -> OsPath) -> String -> IO (Maybe OsPath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> OsPath
os (String -> IO (Maybe OsPath)) -> String -> IO (Maybe OsPath)
forall a b. (a -> b) -> a -> b
$ case XdgDirectoryList
xdgDirs of
      XdgDirectoryList
XdgDataDirs   -> String
"XDG_DATA_DIRS"
      XdgDirectoryList
XdgConfigDirs -> String
"XDG_CONFIG_DIRS"
    case Maybe OsPath
env of
      Maybe OsPath
Nothing    -> XdgDirectoryList -> IO [OsPath]
getXdgDirectoryListFallback XdgDirectoryList
xdgDirs
      Just OsPath
paths -> [OsPath] -> IO [OsPath]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (OsPath -> [OsPath]
splitSearchPath OsPath
paths)
getAppUserDataDirectory :: OsPath     
                                        
                        -> IO OsPath
getAppUserDataDirectory :: OsPath -> IO OsPath
getAppUserDataDirectory OsPath
appName = do
  (IOError -> String -> IOError
`ioeAddLocation` String
"getAppUserDataDirectory") (IOError -> IOError) -> IO OsPath -> IO OsPath
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    OsPath -> IO OsPath
getAppUserDataDirectoryInternal OsPath
appName
getUserDocumentsDirectory :: IO OsPath
getUserDocumentsDirectory :: IO OsPath
getUserDocumentsDirectory = do
  (IOError -> String -> IOError
`ioeAddLocation` String
"getUserDocumentsDirectory") (IOError -> IOError) -> IO OsPath -> IO OsPath
forall a. (IOError -> IOError) -> IO a -> IO a
`modifyIOError` do
    IO OsPath
getUserDocumentsDirectoryInternal
getTemporaryDirectory :: IO OsPath
getTemporaryDirectory :: IO OsPath
getTemporaryDirectory = IO OsPath
getTemporaryDirectoryInternal