-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | Platform-agnostic library for filesystem operations
--
-- This library provides a basic set of operations for manipulating files
-- and directories in a portable way.
@package directory
@version 1.3.9.0
-- | Internal modules are always subject to change from version to version.
-- The contents of this module are also platform-dependent, hence what is
-- shown in the Hackage documentation may differ from what is actually
-- available on your system.
module System.Directory.Internal
-- | A generator with side-effects.
newtype ListT m a
ListT :: m (Maybe (a, ListT m a)) -> ListT m a
[unListT] :: ListT m a -> m (Maybe (a, ListT m a))
-- | Special directories for storing user-specific application data,
-- configuration, and cache files, as specified by the XDG Base
-- Directory Specification.
--
-- Note: On Windows, XdgData and XdgConfig usually map to
-- the same directory.
data XdgDirectory
-- | For data files (e.g. images). It uses the XDG_DATA_HOME
-- environment variable. On non-Windows systems, the default is
-- ~/.local/share. On Windows, the default is %APPDATA%
-- (e.g. C:/Users/<user>/AppData/Roaming). Can be
-- considered as the user-specific equivalent of /usr/share.
XdgData :: XdgDirectory
-- | For configuration files. It uses the XDG_CONFIG_HOME
-- environment variable. On non-Windows systems, the default is
-- ~/.config. On Windows, the default is %APPDATA%
-- (e.g. C:/Users/<user>/AppData/Roaming). Can be
-- considered as the user-specific equivalent of /etc.
XdgConfig :: XdgDirectory
-- | For non-essential files (e.g. cache). It uses the
-- XDG_CACHE_HOME environment variable. On non-Windows systems,
-- the default is ~/.cache. On Windows, the default is
-- %LOCALAPPDATA% (e.g.
-- C:/Users/<user>/AppData/Local). Can be
-- considered as the user-specific equivalent of /var/cache.
XdgCache :: XdgDirectory
-- | For data that should persist between (application) restarts, but that
-- is not important or portable enough to the user that it should be
-- stored in XdgData. It uses the XDG_STATE_HOME
-- environment variable. On non-Windows sytems, the default is
-- ~/.local/state. On Windows, the default is
-- %LOCALAPPDATA% (e.g.
-- C:/Users/<user>/AppData/Local).
XdgState :: XdgDirectory
-- | Search paths for various application data, as specified by the XDG
-- Base Directory Specification.
--
-- The list of paths is split using searchPathSeparator, which on
-- Windows is a semicolon.
--
-- Note: On Windows, XdgDataDirs and XdgConfigDirs usually
-- yield the same result.
data XdgDirectoryList
-- | For data files (e.g. images). It uses the XDG_DATA_DIRS
-- environment variable. On non-Windows systems, the default is
-- /usr/local/share/ and /usr/share/. On Windows, the
-- default is %PROGRAMDATA% or %ALLUSERSPROFILE% (e.g.
-- C:/ProgramData).
XdgDataDirs :: XdgDirectoryList
-- | For configuration files. It uses the XDG_CONFIG_DIRS
-- environment variable. On non-Windows systems, the default is
-- /etc/xdg. On Windows, the default is %PROGRAMDATA%
-- or %ALLUSERSPROFILE% (e.g. C:/ProgramData).
XdgConfigDirs :: XdgDirectoryList
data Permissions
Permissions :: Bool -> Bool -> Bool -> Bool -> Permissions
[readable] :: Permissions -> Bool
[writable] :: Permissions -> Bool
[executable] :: Permissions -> Bool
[searchable] :: Permissions -> Bool
data WhetherFollow
NoFollow :: WhetherFollow
FollowLinks :: WhetherFollow
data FileType
File :: FileType
-- | POSIX: either file or directory link; Windows: file link
SymbolicLink :: FileType
Directory :: FileType
-- | Windows only: directory link
DirectoryLink :: FileType
withBinaryFile :: OsPath -> IOMode -> (Handle -> IO r) -> IO r
-- | Fallibly converts String to OsString. Only intended to be used on
-- literals.
os :: String -> OsString
emptyListT :: Applicative m => ListT m a
maybeToListT :: Applicative m => m (Maybe a) -> ListT m a
listToListT :: Applicative m => [a] -> ListT m a
liftJoinListT :: Monad m => m (ListT m a) -> ListT m a
listTHead :: Functor m => ListT m a -> m (Maybe a)
listTToList :: Monad m => ListT m a -> m [a]
andM :: Monad m => m Bool -> m Bool -> m Bool
sequenceWithIOErrors_ :: [IO ()] -> IO ()
-- | Similar to try but only catches a specify kind of
-- IOError as specified by the predicate.
tryIOErrorType :: (IOError -> Bool) -> IO a -> IO (Either IOError a)
-- | Attempt to perform the given action, silencing any IO exception thrown
-- by it.
ignoreIOExceptions :: IO () -> IO ()
specializeErrorString :: String -> (IOError -> Bool) -> IO a -> IO a
ioeAddLocation :: IOError -> String -> IOError
rightOrError :: Exception e => Either e a -> a
-- | Fallibly converts OsString to String. Only intended to be used on
-- literals.
so :: OsString -> String
ioeSetOsPath :: IOError -> OsPath -> IOError
dropSpecialDotDirs :: [OsPath] -> [OsPath]
-- | Given a list of path segments, expand . and ... The
-- path segments must not contain path separators.
expandDots :: [OsPath] -> [OsPath]
-- | Convert to the right kind of slashes.
normalisePathSeps :: OsPath -> OsPath
-- | Remove redundant trailing slashes and pick the right kind of slash.
normaliseTrailingSep :: OsPath -> OsPath
-- | Convert empty paths to the current directory, otherwise leave it
-- unchanged.
emptyToCurDir :: OsPath -> OsPath
-- | Similar to normalise but empty paths stay empty.
simplifyPosix :: OsPath -> OsPath
-- | Similar to normalise but:
--
--
-- - empty paths stay empty,
-- - parent dirs (..) are expanded, and
-- - paths starting with \\?\ are preserved.
--
--
-- The goal is to preserve the meaning of paths better than
-- normalise.
simplifyWindows :: OsPath -> OsPath
isNoFollow :: WhetherFollow -> Bool
-- | Check whether the given FileType is considered a directory by
-- the operating system. This affects the choice of certain functions
-- e.g. removeDirectory vs removeFile.
fileTypeIsDirectory :: FileType -> Bool
-- | Return whether the given FileType is a link.
fileTypeIsLink :: FileType -> Bool
-- | Copy data from one handle to another until end of file.
copyHandleData :: Handle -> Handle -> IO ()
-- | Type representing filenames/pathnames.
--
-- This type doesn't add any guarantees over OsString.
type OsPath = OsString
-- | Newtype representing short operating system specific strings.
--
-- Internally this is either WindowsString or PosixString,
-- depending on the platform. Both use unpinned ShortByteString
-- for efficiency.
--
-- The constructor is only exported via
-- System.OsString.Internal.Types, since dealing with the
-- internals isn't generally recommended, but supported in case you need
-- to write platform specific code.
data () => OsString
c_AT_FDCWD :: Fd
c_AT_SYMLINK_NOFOLLOW :: CInt
atWhetherFollow :: WhetherFollow -> CInt
defaultOpenFlags :: OpenFileFlags
type RawHandle = Fd
openRaw :: WhetherFollow -> Maybe RawHandle -> OsPath -> IO RawHandle
closeRaw :: RawHandle -> IO ()
createDirectoryInternal :: OsPath -> IO ()
c_unlinkat :: Fd -> CString -> CInt -> IO CInt
removePathAt :: FileType -> Maybe RawHandle -> OsPath -> IO ()
removePathInternal :: Bool -> OsPath -> IO ()
renamePathInternal :: OsPath -> OsPath -> IO ()
filesAlwaysRemovable :: Bool
-- | On POSIX, equivalent to simplifyPosix.
simplify :: OsPath -> OsPath
c_free :: Ptr a -> IO ()
c_PATH_MAX :: Maybe Int
c_realpath :: CString -> CString -> IO CString
withRealpath :: CString -> (CString -> IO a) -> IO a
realPath :: OsPath -> IO OsPath
canonicalizePathSimplify :: OsPath -> IO OsPath
findExecutablesLazyInternal :: ([OsPath] -> OsString -> ListT IO OsPath) -> OsString -> ListT IO OsPath
exeExtensionInternal :: OsString
openDirFromFd :: Fd -> IO DirStream
readDirStreamToEnd :: DirStream -> IO [OsPath]
readDirToEnd :: RawHandle -> IO [OsPath]
getDirectoryContentsInternal :: OsPath -> IO [OsPath]
getCurrentDirectoryInternal :: IO OsPath
-- | Convert a path into an absolute path. If the given path is relative,
-- the current directory is prepended and the path may or may not be
-- simplified. If the path is already absolute, the path is returned
-- unchanged. The function preserves the presence or absence of the
-- trailing path separator.
--
-- If the path is already absolute, the operation never fails. Otherwise,
-- the operation may throw exceptions.
--
-- Empty paths are treated as the current directory.
prependCurrentDirectory :: OsPath -> IO OsPath
setCurrentDirectoryInternal :: OsPath -> IO ()
linkToDirectoryIsDirectory :: Bool
createHardLink :: OsPath -> OsPath -> IO ()
createSymbolicLink :: Bool -> OsPath -> OsPath -> IO ()
readSymbolicLink :: OsPath -> IO OsPath
type Metadata = FileStatus
c_fstatat :: Fd -> CString -> Ptr CStat -> CInt -> IO CInt
getMetadataAt :: WhetherFollow -> Maybe RawHandle -> OsPath -> IO Metadata
getSymbolicLinkMetadata :: OsPath -> IO Metadata
getFileMetadata :: OsPath -> IO Metadata
fileTypeFromMetadata :: Metadata -> FileType
fileSizeFromMetadata :: Metadata -> Integer
accessTimeFromMetadata :: Metadata -> UTCTime
modificationTimeFromMetadata :: Metadata -> UTCTime
type Mode = FileMode
modeFromMetadata :: Metadata -> Mode
allWriteMode :: FileMode
hasWriteMode :: Mode -> Bool
setWriteMode :: Bool -> Mode -> Mode
setForceRemoveMode :: Mode -> Mode
c_fchmodat :: Fd -> CString -> FileMode -> CInt -> IO CInt
setModeAt :: WhetherFollow -> Maybe RawHandle -> OsPath -> Mode -> IO ()
setFileMode :: OsPath -> Mode -> IO ()
setFilePermissions :: OsPath -> Mode -> IO ()
getAccessPermissions :: OsPath -> IO Permissions
setAccessPermissions :: OsPath -> Permissions -> IO ()
copyOwnerFromStatus :: FileStatus -> OsPath -> IO ()
copyGroupFromStatus :: FileStatus -> OsPath -> IO ()
tryCopyOwnerAndGroupFromStatus :: FileStatus -> OsPath -> IO ()
-- | Truncate the destination file and then copy the contents of the source
-- file to the destination file. If the destination file already exists,
-- its attributes shall remain unchanged. Otherwise, its attributes are
-- reset to the defaults.
copyFileContents :: OsPath -> OsPath -> IO ()
copyFileWithMetadataInternal :: (Metadata -> OsPath -> IO ()) -> (Metadata -> OsPath -> IO ()) -> OsPath -> OsPath -> IO ()
setTimes :: OsPath -> (Maybe POSIXTime, Maybe POSIXTime) -> IO ()
lookupEnvOs :: OsString -> IO (Maybe OsString)
getEnvOs :: OsString -> IO OsString
-- | Get the contents of the PATH environment variable.
getPath :: IO [OsPath]
-- | $HOME is preferred, because the user has control over it. However,
-- POSIX doesn't define it as a mandatory variable, so fall back to
-- getpwuid_r.
getHomeDirectoryInternal :: IO OsPath
getXdgDirectoryFallback :: IO OsPath -> XdgDirectory -> IO OsPath
getXdgDirectoryListFallback :: XdgDirectoryList -> IO [OsPath]
getAppUserDataDirectoryInternal :: OsPath -> IO OsPath
getUserDocumentsDirectoryInternal :: IO OsPath
getTemporaryDirectoryInternal :: IO OsPath
-- | System-independent interface to directory manipulation.
module System.Directory.OsPath
-- | createDirectory dir creates a new directory
-- dir which is initially empty, or as near to empty as the
-- operating system allows.
--
-- The operation may fail with:
--
--
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EROFS, EACCES]
-- - isAlreadyExistsError The operand refers to a directory that
-- already exists. [EEXIST]
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument The operand is not a valid directory
-- name. [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError There is no path to the directory.
-- [ENOENT, ENOTDIR]
-- - isFullError Insufficient resources (virtual memory, process
-- file descriptors, physical disk space, etc.) are available to perform
-- the operation. [EDQUOT, ENOSPC, ENOMEM, EMLINK]
-- - InappropriateType The path refers to an existing
-- non-directory object. [EEXIST]
--
createDirectory :: OsPath -> IO ()
-- | createDirectoryIfMissing parents dir creates a new
-- directory dir if it doesn't exist. If the first argument is
-- True the function will also create all parent directories if
-- they are missing.
createDirectoryIfMissing :: Bool -> OsPath -> IO ()
-- | removeDirectory dir removes an existing directory
-- dir. The implementation may specify additional constraints
-- which must be satisfied before a directory can be removed (e.g. the
-- directory has to be empty, or may not be in use by other processes).
-- It is not legal for an implementation to partially remove a directory
-- unless the entire directory is removed. A conformant implementation
-- need not support directory removal in all situations (e.g. removal of
-- the root directory).
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument The operand is not a valid directory
-- name. [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The directory does not exist.
-- [ENOENT, ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EROFS, EACCES, EPERM]
-- - UnsatisfiedConstraints Implementation-dependent
-- constraints are not satisfied. [EBUSY, ENOTEMPTY,
-- EEXIST]
-- - UnsupportedOperation The implementation does not support
-- removal in this situation. [EINVAL]
-- - InappropriateType The operand refers to an existing
-- non-directory object. [ENOTDIR]
--
removeDirectory :: OsPath -> IO ()
-- | removeDirectoryRecursive dir removes an existing
-- directory dir together with its contents and subdirectories.
-- Within this directory, symbolic links are removed without affecting
-- their targets.
--
-- On Windows, the operation fails if dir is a directory symbolic
-- link.
--
-- This operation is reported to be flaky on Windows so retry logic may
-- be advisable. See:
-- https://github.com/haskell/directory/pull/108
removeDirectoryRecursive :: OsPath -> IO ()
-- | Removes a file or directory at path together with its contents
-- and subdirectories. Symbolic links are removed without affecting their
-- targets. If the path does not exist, nothing happens.
--
-- Unlike other removal functions, this function will also attempt to
-- delete files marked as read-only or otherwise made unremovable due to
-- permissions. As a result, if the removal is incomplete, the
-- permissions or attributes on the remaining files may be altered. If
-- there are hard links in the directory, then permissions on all related
-- hard links may be altered.
--
-- If an entry within the directory vanishes while
-- removePathForcibly is running, it is silently ignored.
--
-- If an exception occurs while removing an entry,
-- removePathForcibly will still try to remove as many entries
-- as it can before failing with an exception. The first exception that
-- it encountered is re-thrown.
removePathForcibly :: OsPath -> IO ()
-- | renameDirectory old new changes the name of an
-- existing directory from old to new. If the new
-- directory already exists, it is atomically replaced by the old
-- directory. If the new directory is neither the old
-- directory nor an alias of the old directory, it is removed as
-- if by removeDirectory. A conformant implementation need not
-- support renaming directories in all situations (e.g. renaming to an
-- existing directory, or across different physical devices), but the
-- constraints must be documented.
--
-- On Win32 platforms, renameDirectory fails if the new
-- directory already exists.
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument Either operand is not a valid directory
-- name. [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The original directory does not exist,
-- or there is no path to the target. [ENOENT, ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EROFS, EACCES, EPERM]
-- - isFullError Insufficient resources are available to perform
-- the operation. [EDQUOT, ENOSPC, ENOMEM, EMLINK]
-- - UnsatisfiedConstraints Implementation-dependent
-- constraints are not satisfied. [EBUSY, ENOTEMPTY,
-- EEXIST]
-- - UnsupportedOperation The implementation does not support
-- renaming in this situation. [EINVAL, EXDEV]
-- - InappropriateType Either path refers to an existing
-- non-directory object. [ENOTDIR, EISDIR]
--
renameDirectory :: OsPath -> OsPath -> IO ()
-- | listDirectory dir returns a list of all entries
-- in dir without the special entries (. and
-- ..).
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument The operand is not a valid directory
-- name. [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The directory does not exist.
-- [ENOENT, ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EACCES]
-- - isFullError Insufficient resources are available to perform
-- the operation. [EMFILE, ENFILE]
-- - InappropriateType The path refers to an existing
-- non-directory object. [ENOTDIR]
--
listDirectory :: OsPath -> IO [OsPath]
-- | Similar to listDirectory, but always includes the special
-- entries (. and ..). (This applies to Windows as
-- well.)
--
-- The operation may fail with the same exceptions as
-- listDirectory.
getDirectoryContents :: OsPath -> IO [OsPath]
-- | Obtain the current working directory as an absolute path.
--
-- In a multithreaded program, the current working directory is a global
-- state shared among all threads of the process. Therefore, when
-- performing filesystem operations from multiple threads, it is highly
-- recommended to use absolute rather than relative paths (see:
-- makeAbsolute).
--
-- Note that getCurrentDirectory is not guaranteed to return the
-- same path received by setCurrentDirectory. On POSIX systems,
-- the path returned will always be fully dereferenced (not contain any
-- symbolic links). For more information, refer to the documentation of
-- getcwd.
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - isDoesNotExistError There is no path referring to the
-- working directory. [EPERM, ENOENT, ESTALE...]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EACCES]
-- - isFullError Insufficient resources are available to perform
-- the operation.
-- - UnsupportedOperation The operating system has no notion
-- of current working directory.
--
getCurrentDirectory :: IO OsPath
-- | Change the working directory to the given path.
--
-- In a multithreaded program, the current working directory is a global
-- state shared among all threads of the process. Therefore, when
-- performing filesystem operations from multiple threads, it is highly
-- recommended to use absolute rather than relative paths (see:
-- makeAbsolute).
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument The operand is not a valid directory
-- name. [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The directory does not exist.
-- [ENOENT, ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EACCES]
-- - UnsupportedOperation The operating system has no notion
-- of current working directory, or the working directory cannot be
-- dynamically changed.
-- - InappropriateType The path refers to an existing
-- non-directory object. [ENOTDIR]
--
setCurrentDirectory :: OsPath -> IO ()
-- | Run an IO action with the given working directory and restore
-- the original working directory afterwards, even if the given action
-- fails due to an exception.
--
-- The operation may fail with the same exceptions as
-- getCurrentDirectory and setCurrentDirectory.
withCurrentDirectory :: OsPath -> IO a -> IO a
-- | Returns the current user's home directory.
--
-- The directory returned is expected to be writable by the current user,
-- but note that it isn't generally considered good practice to store
-- application-specific data here; use getXdgDirectory or
-- getAppUserDataDirectory instead.
--
-- On Unix, getHomeDirectory behaves as follows:
--
--
-- - Returns $HOME env variable if set (including to an empty
-- string).
-- - Otherwise uses home directory returned by getpwuid_r
-- using the UID of the current proccesses user. This basically reads the
-- etcpasswd file. An empty home directory field is considered
-- valid.
--
--
-- On Windows, the system is queried for a suitable path; a typical path
-- might be C:/Users/<user>.
--
-- The operation may fail with:
--
--
-- - UnsupportedOperation The operating system has no notion
-- of home directory.
-- - isDoesNotExistError The home directory for the current user
-- does not exist, or cannot be found.
--
getHomeDirectory :: IO OsPath
-- | Special directories for storing user-specific application data,
-- configuration, and cache files, as specified by the XDG Base
-- Directory Specification.
--
-- Note: On Windows, XdgData and XdgConfig usually map to
-- the same directory.
data XdgDirectory
-- | For data files (e.g. images). It uses the XDG_DATA_HOME
-- environment variable. On non-Windows systems, the default is
-- ~/.local/share. On Windows, the default is %APPDATA%
-- (e.g. C:/Users/<user>/AppData/Roaming). Can be
-- considered as the user-specific equivalent of /usr/share.
XdgData :: XdgDirectory
-- | For configuration files. It uses the XDG_CONFIG_HOME
-- environment variable. On non-Windows systems, the default is
-- ~/.config. On Windows, the default is %APPDATA%
-- (e.g. C:/Users/<user>/AppData/Roaming). Can be
-- considered as the user-specific equivalent of /etc.
XdgConfig :: XdgDirectory
-- | For non-essential files (e.g. cache). It uses the
-- XDG_CACHE_HOME environment variable. On non-Windows systems,
-- the default is ~/.cache. On Windows, the default is
-- %LOCALAPPDATA% (e.g.
-- C:/Users/<user>/AppData/Local). Can be
-- considered as the user-specific equivalent of /var/cache.
XdgCache :: XdgDirectory
-- | For data that should persist between (application) restarts, but that
-- is not important or portable enough to the user that it should be
-- stored in XdgData. It uses the XDG_STATE_HOME
-- environment variable. On non-Windows sytems, the default is
-- ~/.local/state. On Windows, the default is
-- %LOCALAPPDATA% (e.g.
-- C:/Users/<user>/AppData/Local).
XdgState :: XdgDirectory
-- | Obtain the paths to special directories for storing user-specific
-- application data, configuration, and cache files, conforming to the
-- XDG Base Directory Specification. Compared with
-- getAppUserDataDirectory, this function provides a more
-- fine-grained hierarchy as well as greater flexibility for the user.
--
-- On Windows, XdgData and XdgConfig usually map to the
-- same directory unless overridden.
--
-- Refer to the docs of XdgDirectory for more details.
--
-- The second argument is usually the name of the application. Since it
-- will be integrated into the path, it must consist of valid path
-- characters. Note: if the second argument is an absolute path, it will
-- just return the second argument.
--
-- Note: The directory may not actually exist, in which case you would
-- need to create it with file mode 700 (i.e. only accessible by
-- the owner).
--
-- As of 1.3.5.0, the environment variable is ignored if set to a
-- relative path, per revised XDG Base Directory Specification. See
-- #100.
getXdgDirectory :: XdgDirectory -> OsPath -> IO OsPath
-- | Search paths for various application data, as specified by the XDG
-- Base Directory Specification.
--
-- The list of paths is split using searchPathSeparator, which on
-- Windows is a semicolon.
--
-- Note: On Windows, XdgDataDirs and XdgConfigDirs usually
-- yield the same result.
data XdgDirectoryList
-- | For data files (e.g. images). It uses the XDG_DATA_DIRS
-- environment variable. On non-Windows systems, the default is
-- /usr/local/share/ and /usr/share/. On Windows, the
-- default is %PROGRAMDATA% or %ALLUSERSPROFILE% (e.g.
-- C:/ProgramData).
XdgDataDirs :: XdgDirectoryList
-- | For configuration files. It uses the XDG_CONFIG_DIRS
-- environment variable. On non-Windows systems, the default is
-- /etc/xdg. On Windows, the default is %PROGRAMDATA%
-- or %ALLUSERSPROFILE% (e.g. C:/ProgramData).
XdgConfigDirs :: XdgDirectoryList
-- | Similar to getXdgDirectory but retrieves the entire list of XDG
-- directories.
--
-- On Windows, XdgDataDirs and XdgConfigDirs usually map to
-- the same list of directories unless overridden.
--
-- Refer to the docs of XdgDirectoryList for more details.
getXdgDirectoryList :: XdgDirectoryList -> IO [OsPath]
-- | Obtain the path to a special directory for storing user-specific
-- application data (traditional Unix location). Newer applications may
-- prefer the the XDG-conformant location provided by
-- getXdgDirectory (migration guide).
--
-- The argument is usually the name of the application. Since it will be
-- integrated into the path, it must consist of valid path characters.
--
--
-- - On Unix-like systems, the path is
-- ~/.<app>.
-- - On Windows, the path is %APPDATA%/<app>
-- (e.g.
-- C:/Users/<user>/AppData/Roaming/<app>)
--
--
-- Note: the directory may not actually exist, in which case you would
-- need to create it. It is expected that the parent directory exists and
-- is writable.
--
-- The operation may fail with:
--
--
-- - UnsupportedOperation The operating system has no notion
-- of application-specific data directory.
-- - isDoesNotExistError The home directory for the current user
-- does not exist, or cannot be found.
--
getAppUserDataDirectory :: OsPath -> IO OsPath
-- | Returns the current user's document directory.
--
-- The directory returned is expected to be writable by the current user,
-- but note that it isn't generally considered good practice to store
-- application-specific data here; use getXdgDirectory or
-- getAppUserDataDirectory instead.
--
-- On Unix, getUserDocumentsDirectory returns the value of the
-- HOME environment variable. On Windows, the system is queried
-- for a suitable path; a typical path might be
-- C:/Users/<user>/Documents.
--
-- The operation may fail with:
--
--
-- - UnsupportedOperation The operating system has no notion
-- of document directory.
-- - isDoesNotExistError The document directory for the current
-- user does not exist, or cannot be found.
--
getUserDocumentsDirectory :: IO OsPath
-- | Returns the current directory for temporary files.
--
-- On Unix, getTemporaryDirectory returns the value of the
-- TMPDIR environment variable or "/tmp" if the variable isn't
-- defined. On Windows, the function checks for the existence of
-- environment variables in the following order and uses the first path
-- found:
--
--
-- - TMP environment variable.
-- - TEMP environment variable.
-- - USERPROFILE environment variable.
-- - The Windows directory
--
--
-- The operation may fail with:
--
--
-- - UnsupportedOperation The operating system has no notion
-- of temporary directory.
--
--
-- The function doesn't verify whether the path exists.
getTemporaryDirectory :: IO OsPath
-- | removeFile file removes the directory entry for an
-- existing file file, where file is not itself a
-- directory. The implementation may specify additional constraints which
-- must be satisfied before a file can be removed (e.g. the file may not
-- be in use by other processes).
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument The operand is not a valid file name.
-- [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The file does not exist. [ENOENT,
-- ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EROFS, EACCES, EPERM]
-- - UnsatisfiedConstraints Implementation-dependent
-- constraints are not satisfied. [EBUSY]
-- - InappropriateType The operand refers to an existing
-- directory. [EPERM, EINVAL]
--
removeFile :: OsPath -> IO ()
-- | renameFile old new changes the name of an existing
-- file system object from old to new. If the new
-- object already exists, it is replaced by the old object.
-- Neither path may refer to an existing directory.
--
-- A conformant implementation need not support renaming files in all
-- situations (e.g. renaming across different physical devices), but the
-- constraints must be documented. On Windows, this does not support
-- renaming across different physical devices; if you are looking to do
-- so, consider using copyFileWithMetadata and removeFile.
--
-- On Windows, this calls MoveFileEx with
-- MOVEFILE_REPLACE_EXISTING set, which is not guaranteed to be
-- atomic (https://github.com/haskell/directory/issues/109).
--
-- On other platforms, this operation is atomic.
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument Either operand is not a valid file name.
-- [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The original file does not exist, or
-- there is no path to the target. [ENOENT, ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EROFS, EACCES, EPERM]
-- - isFullError Insufficient resources are available to perform
-- the operation. [EDQUOT, ENOSPC, ENOMEM, EMLINK]
-- - UnsatisfiedConstraints Implementation-dependent
-- constraints are not satisfied. [EBUSY]
-- - UnsupportedOperation The implementation does not support
-- renaming in this situation. [EXDEV]
-- - InappropriateType Either path refers to an existing
-- directory. [ENOTDIR, EISDIR, EINVAL, EEXIST, ENOTEMPTY]
--
renameFile :: OsPath -> OsPath -> IO ()
-- | Rename a file or directory. If the destination path already exists, it
-- is replaced atomically. The destination path must not point to an
-- existing directory. A conformant implementation need not support
-- renaming files in all situations (e.g. renaming across different
-- physical devices), but the constraints must be documented.
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument Either operand is not a valid file name.
-- [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The original file does not exist, or
-- there is no path to the target. [ENOENT, ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EROFS, EACCES, EPERM]
-- - isFullError Insufficient resources are available to perform
-- the operation. [EDQUOT, ENOSPC, ENOMEM, EMLINK]
-- - UnsatisfiedConstraints Implementation-dependent
-- constraints are not satisfied. [EBUSY]
-- - UnsupportedOperation The implementation does not support
-- renaming in this situation. [EXDEV]
-- - InappropriateType Either the destination path refers to
-- an existing directory, or one of the parent segments in the
-- destination path is not a directory. [ENOTDIR, EISDIR, EINVAL,
-- EEXIST, ENOTEMPTY]
--
renamePath :: OsPath -> OsPath -> IO ()
-- | Copy a file with its permissions. If the destination file already
-- exists, it is replaced atomically. Neither path may refer to an
-- existing directory. No exceptions are thrown if the permissions could
-- not be copied.
copyFile :: OsPath -> OsPath -> IO ()
-- | Copy a file with its associated metadata. If the destination file
-- already exists, it is overwritten. There is no guarantee of atomicity
-- in the replacement of the destination file. Neither path may refer to
-- an existing directory. If the source and/or destination are symbolic
-- links, the copy is performed on the targets of the links.
--
-- On Windows, it behaves like the Win32 function CopyFile, which
-- copies various kinds of metadata including file attributes and
-- security resource properties.
--
-- On Unix-like systems, permissions, access time, and modification time
-- are preserved. If possible, the owner and group are also preserved.
-- Note that the very act of copying can change the access time of the
-- source file, hence the access times of the two files may differ after
-- the operation completes.
copyFileWithMetadata :: OsPath -> OsPath -> IO ()
-- | Obtain the size of a file in bytes.
getFileSize :: OsPath -> IO Integer
-- | Make a path absolute, normalize the path, and remove as many
-- indirections from it as possible. Any trailing path separators are
-- discarded via dropTrailingPathSeparator. Additionally, on
-- Windows the letter case of the path is canonicalized.
--
-- Note: This function is a very big hammer. If you only need an
-- absolute path, makeAbsolute is sufficient for removing
-- dependence on the current working directory.
--
-- Indirections include the two special directories . and
-- .., as well as any symbolic links (and junction points on
-- Windows). The input path need not point to an existing file or
-- directory. Canonicalization is performed on the longest prefix of the
-- path that points to an existing file or directory. The remaining
-- portion of the path that does not point to an existing file or
-- directory will still be normalized, but case canonicalization and
-- indirection removal are skipped as they are impossible to do on a
-- nonexistent path.
--
-- Most programs should not worry about the canonicity of a path. In
-- particular, despite the name, the function does not truly guarantee
-- canonicity of the returned path due to the presence of hard links,
-- mount points, etc.
--
-- If the path points to an existing file or directory, then the output
-- path shall also point to the same file or directory, subject to the
-- condition that the relevant parts of the file system do not change
-- while the function is still running. In other words, the function is
-- definitively not atomic. The results can be utterly wrong if the
-- portions of the path change while this function is running.
--
-- Since some indirections (symbolic links on all systems, .. on
-- non-Windows systems, and junction points on Windows) are dependent on
-- the state of the existing filesystem, the function can only make a
-- conservative attempt by removing such indirections from the longest
-- prefix of the path that still points to an existing file or directory.
--
-- Note that on Windows parent directories .. are always fully
-- expanded before the symbolic links, as consistent with the rest of the
-- Windows API (such as GetFullPathName). In contrast, on POSIX
-- systems parent directories .. are expanded alongside symbolic
-- links from left to right. To put this more concretely: if L
-- is a symbolic link for R/P, then on Windows L\..
-- refers to ., whereas on other operating systems L/..
-- refers to R.
--
-- Similar to normalise, passing an empty path is equivalent to
-- passing the current directory.
--
-- canonicalizePath can resolve at least 64 indirections in a
-- single path, more than what is supported by most operating systems.
-- Therefore, it may return the fully resolved path even though the
-- operating system itself would have long given up.
--
-- On Windows XP or earlier systems, junction expansion is not performed
-- due to their lack of GetFinalPathNameByHandle.
--
-- Changes since 1.2.3.0: The function has been altered to be more
-- robust and has the same exception behavior as makeAbsolute.
--
-- Changes since 1.3.0.0: The function no longer preserves the
-- trailing path separator. File symbolic links that appear in the middle
-- of a path are properly dereferenced. Case canonicalization and
-- symbolic link expansion are now performed on Windows.
canonicalizePath :: OsPath -> IO OsPath
-- | Convert a path into an absolute path. If the given path is relative,
-- the current directory is prepended and then the combined result is
-- normalized. If the path is already absolute, the path is simply
-- normalized. The function preserves the presence or absence of the
-- trailing path separator unless the path refers to the root directory
-- /.
--
-- If the path is already absolute, the operation never fails. Otherwise,
-- the operation may fail with the same exceptions as
-- getCurrentDirectory.
makeAbsolute :: OsPath -> IO OsPath
-- | Construct a path relative to the current directory, similar to
-- makeRelative.
--
-- The operation may fail with the same exceptions as
-- getCurrentDirectory.
makeRelativeToCurrentDirectory :: OsPath -> IO OsPath
-- | Test whether the given path points to an existing filesystem object.
-- If the user lacks necessary permissions to search the parent
-- directories, this function may return false even if the file does
-- actually exist. This operation traverses symbolic links, so it can
-- return either True or False for them.
doesPathExist :: OsPath -> IO Bool
-- | The operation doesFileExist returns True if the argument
-- file exists and is not a directory, and False otherwise. This
-- operation traverses symbolic links, so it can return either True or
-- False for them.
doesFileExist :: OsPath -> IO Bool
-- | The operation doesDirectoryExist returns True if the
-- argument file exists and is either a directory or a symbolic link to a
-- directory, and False otherwise. This operation traverses
-- symbolic links, so it can return either True or False for them.
doesDirectoryExist :: OsPath -> IO Bool
-- | Given the name or path of an executable file, findExecutable
-- searches for such a file in a list of system-defined locations, which
-- generally includes PATH and possibly more. The full path to
-- the executable is returned if found. For example, (findExecutable
-- "ghc") would normally give you the path to GHC.
--
-- The path returned by findExecutable name corresponds
-- to the program that would be executed by createProcess
-- when passed the same string (as a RawCommand, not a
-- ShellCommand), provided that name is not a relative
-- path with more than one segment.
--
-- On Windows, findExecutable calls the Win32 function
-- SearchPath, which may search other places before
-- checking the directories in the PATH environment variable.
-- Where it actually searches depends on registry settings, but notably
-- includes the directory containing the current executable.
--
-- On non-Windows platforms, the behavior is equivalent to
-- findFileWith using the search directories from the
-- PATH environment variable and testing each file for
-- executable permissions. Details can be found in the documentation of
-- findFileWith.
findExecutable :: OsString -> IO (Maybe OsPath)
-- | Search for executable files in a list of system-defined locations,
-- which generally includes PATH and possibly more.
--
-- On Windows, this only returns the first occurrence, if any. Its
-- behavior is therefore equivalent to findExecutable.
--
-- On non-Windows platforms, the behavior is equivalent to
-- findExecutablesInDirectories using the search directories from
-- the PATH environment variable. Details can be found in the
-- documentation of findExecutablesInDirectories.
findExecutables :: OsString -> IO [OsPath]
-- | Given a name or path, findExecutable appends the
-- exeExtension to the query and searches for executable files in
-- the list of given search directories and returns all occurrences.
--
-- The behavior is equivalent to findFileWith using the given
-- search directories and testing each file for executable permissions.
-- Details can be found in the documentation of findFileWith.
--
-- Unlike other similarly named functions,
-- findExecutablesInDirectories does not use SearchPath
-- from the Win32 API. The behavior of this function on Windows is
-- therefore equivalent to those on non-Windows platforms.
findExecutablesInDirectories :: [OsPath] -> OsString -> IO [OsPath]
-- | Search through the given list of directories for the given file.
--
-- The behavior is equivalent to findFileWith, returning only the
-- first occurrence. Details can be found in the documentation of
-- findFileWith.
findFile :: [OsPath] -> OsString -> IO (Maybe OsPath)
-- | Search through the given list of directories for the given file and
-- returns all paths where the given file exists.
--
-- The behavior is equivalent to findFilesWith. Details can be
-- found in the documentation of findFilesWith.
findFiles :: [OsPath] -> OsString -> IO [OsPath]
-- | Search through a given list of directories for a file that has the
-- given name and satisfies the given predicate and return the path of
-- the first occurrence. The directories are checked in a left-to-right
-- order.
--
-- This is essentially a more performant version of findFilesWith
-- that always returns the first result, if any. Details can be found in
-- the documentation of findFilesWith.
findFileWith :: (OsPath -> IO Bool) -> [OsPath] -> OsString -> IO (Maybe OsPath)
-- | findFilesWith predicate dirs name searches through the list
-- of directories (dirs) for files that have the given
-- name and satisfy the given predicate and returns the
-- paths of those files. The directories are checked in a left-to-right
-- order and the paths are returned in the same order.
--
-- If the name is a relative path, then for every search
-- directory dir, the function checks whether dir
-- </> name exists and satisfies the predicate. If so,
-- dir </> name is returned as one of the results.
-- In other words, the returned paths can be either relative or absolute
-- depending on the search directories were used. If there are no search
-- directories, no results are ever returned.
--
-- If the name is an absolute path, then the function will
-- return a single result if the file exists and satisfies the predicate
-- and no results otherwise. This is irrespective of what search
-- directories were given.
findFilesWith :: (OsPath -> IO Bool) -> [OsPath] -> OsString -> IO [OsPath]
-- | Filename extension for executable files (including the dot if any)
-- (usually "" on POSIX systems and ".exe" on Windows
-- or OS/2).
exeExtension :: OsString
-- | Create a file symbolic link. The target path can be either
-- absolute or relative and need not refer to an existing file. The order
-- of arguments follows the POSIX convention.
--
-- To remove an existing file symbolic link, use removeFile.
--
-- Although the distinction between file symbolic links and
-- directory symbolic links does not exist on POSIX systems, on
-- Windows this is an intrinsic property of every symbolic link and
-- cannot be changed without recreating the link. A file symbolic link
-- that actually points to a directory will fail to dereference and vice
-- versa. Moreover, creating symbolic links on Windows may require
-- privileges unavailable to users outside the Administrators group.
-- Portable programs that use symbolic links should take both into
-- consideration.
--
-- On Windows, the function is implemented using
-- CreateSymbolicLink. Since 1.3.3.0, the
-- SYMBOLIC_LINK_FLAG_ALLOW_UNPRIVILEGED_CREATE flag is included
-- if supported by the operating system. On POSIX, the function uses
-- symlink and is therefore atomic.
--
-- Windows-specific errors: This operation may fail with
-- permissionErrorType if the user lacks the privileges to create
-- symbolic links. It may also fail with illegalOperationErrorType
-- if the file system does not support symbolic links.
createFileLink :: OsPath -> OsPath -> IO ()
-- | Create a directory symbolic link. The target path can be either
-- absolute or relative and need not refer to an existing directory. The
-- order of arguments follows the POSIX convention.
--
-- To remove an existing directory symbolic link, use
-- removeDirectoryLink.
--
-- Although the distinction between file symbolic links and
-- directory symbolic links does not exist on POSIX systems, on
-- Windows this is an intrinsic property of every symbolic link and
-- cannot be changed without recreating the link. A file symbolic link
-- that actually points to a directory will fail to dereference and vice
-- versa. Moreover, creating symbolic links on Windows may require
-- privileges unavailable to users outside the Administrators group.
-- Portable programs that use symbolic links should take both into
-- consideration.
--
-- On Windows, the function is implemented using
-- CreateSymbolicLink with
-- SYMBOLIC_LINK_FLAG_DIRECTORY. Since 1.3.3.0, the
-- SYMBOLIC_LINK_FLAG_ALLOW_UNPRIVILEGED_CREATE flag is also
-- included if supported by the operating system. On POSIX, this is an
-- alias for createFileLink and is therefore atomic.
--
-- Windows-specific errors: This operation may fail with
-- permissionErrorType if the user lacks the privileges to create
-- symbolic links. It may also fail with illegalOperationErrorType
-- if the file system does not support symbolic links.
createDirectoryLink :: OsPath -> OsPath -> IO ()
-- | Remove an existing directory symbolic link.
--
-- On Windows, this is an alias for removeDirectory. On POSIX
-- systems, this is an alias for removeFile.
--
-- See also: removeFile, which can remove an existing file
-- symbolic link.
removeDirectoryLink :: OsPath -> IO ()
-- | Check whether an existing path is a symbolic link. If
-- path is a regular file or directory, False is
-- returned. If path does not exist or is otherwise
-- inaccessible, an exception is thrown (see below).
--
-- On Windows, this checks for FILE_ATTRIBUTE_REPARSE_POINT. In
-- addition to symbolic links, the function also returns true on junction
-- points. On POSIX systems, this checks for S_IFLNK.
--
-- The operation may fail with:
--
--
pathIsSymbolicLink :: OsPath -> IO Bool
-- | Retrieve the target path of either a file or directory symbolic link.
-- The returned path may not be absolute, may not exist, and may not even
-- be a valid path.
--
-- On Windows systems, this calls DeviceIoControl with
-- FSCTL_GET_REPARSE_POINT. In addition to symbolic links, the
-- function also works on junction points. On POSIX systems, this calls
-- readlink.
--
-- Windows-specific errors: This operation may fail with
-- illegalOperationErrorType if the file system does not support
-- symbolic links.
getSymbolicLinkTarget :: OsPath -> IO OsPath
data Permissions
emptyPermissions :: Permissions
readable :: Permissions -> Bool
writable :: Permissions -> Bool
executable :: Permissions -> Bool
searchable :: Permissions -> Bool
setOwnerReadable :: Bool -> Permissions -> Permissions
setOwnerWritable :: Bool -> Permissions -> Permissions
setOwnerExecutable :: Bool -> Permissions -> Permissions
setOwnerSearchable :: Bool -> Permissions -> Permissions
-- | Get the permissions of a file or directory.
--
-- On Windows, the writable permission corresponds to the
-- "read-only" attribute. The executable permission is set if the
-- file extension is of an executable file type. The readable
-- permission is always set.
--
-- On POSIX systems, this returns the result of access.
--
-- The operation may fail with:
--
--
getPermissions :: OsPath -> IO Permissions
-- | Set the permissions of a file or directory.
--
-- On Windows, this is only capable of changing the writable
-- permission, which corresponds to the "read-only" attribute. Changing
-- the other permissions has no effect.
--
-- On POSIX systems, this sets the owner permissions.
--
-- The operation may fail with:
--
--
setPermissions :: OsPath -> Permissions -> IO ()
-- | Copy the permissions of one file to another. This reproduces the
-- permissions more accurately than using getPermissions followed
-- by setPermissions.
--
-- On Windows, this copies only the read-only attribute.
--
-- On POSIX systems, this is equivalent to stat followed by
-- chmod.
copyPermissions :: OsPath -> OsPath -> IO ()
-- | Obtain the time at which the file or directory was last accessed.
--
-- The operation may fail with:
--
--
--
-- Caveat for POSIX systems: This function returns a timestamp with
-- sub-second resolution only if this package is compiled against
-- unix-2.6.0.0 or later and the underlying filesystem supports
-- them.
getAccessTime :: OsPath -> IO UTCTime
-- | Obtain the time at which the file or directory was last modified.
--
-- The operation may fail with:
--
--
--
-- Caveat for POSIX systems: This function returns a timestamp with
-- sub-second resolution only if this package is compiled against
-- unix-2.6.0.0 or later and the underlying filesystem supports
-- them.
getModificationTime :: OsPath -> IO UTCTime
-- | Change the time at which the file or directory was last accessed.
--
-- The operation may fail with:
--
--
--
-- Some caveats for POSIX systems:
--
--
-- - Not all systems support utimensat, in which case the
-- function can only emulate the behavior by reading the modification
-- time and then setting both the access and modification times together.
-- On systems where utimensat is supported, the access time is
-- set atomically with nanosecond precision.
-- - If compiled against a version of unix prior to
-- 2.7.0.0, the function would not be able to set timestamps
-- with sub-second resolution. In this case, there would also be loss of
-- precision in the modification time.
--
setAccessTime :: OsPath -> UTCTime -> IO ()
-- | Change the time at which the file or directory was last modified.
--
-- The operation may fail with:
--
--
--
-- Some caveats for POSIX systems:
--
--
-- - Not all systems support utimensat, in which case the
-- function can only emulate the behavior by reading the access time and
-- then setting both the access and modification times together. On
-- systems where utimensat is supported, the modification time
-- is set atomically with nanosecond precision.
-- - If compiled against a version of unix prior to
-- 2.7.0.0, the function would not be able to set timestamps
-- with sub-second resolution. In this case, there would also be loss of
-- precision in the access time.
--
setModificationTime :: OsPath -> UTCTime -> IO ()
-- | System-independent interface to directory manipulation (FilePath API).
module System.Directory
-- | createDirectory dir creates a new directory
-- dir which is initially empty, or as near to empty as the
-- operating system allows.
--
-- The operation may fail with:
--
--
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EROFS, EACCES]
-- - isAlreadyExistsError The operand refers to a directory that
-- already exists. [EEXIST]
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument The operand is not a valid directory
-- name. [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError There is no path to the directory.
-- [ENOENT, ENOTDIR]
-- - isFullError Insufficient resources (virtual memory, process
-- file descriptors, physical disk space, etc.) are available to perform
-- the operation. [EDQUOT, ENOSPC, ENOMEM, EMLINK]
-- - InappropriateType The path refers to an existing
-- non-directory object. [EEXIST]
--
createDirectory :: FilePath -> IO ()
-- | createDirectoryIfMissing parents dir creates a new
-- directory dir if it doesn't exist. If the first argument is
-- True the function will also create all parent directories if
-- they are missing.
createDirectoryIfMissing :: Bool -> FilePath -> IO ()
-- | removeDirectory dir removes an existing directory
-- dir. The implementation may specify additional constraints
-- which must be satisfied before a directory can be removed (e.g. the
-- directory has to be empty, or may not be in use by other processes).
-- It is not legal for an implementation to partially remove a directory
-- unless the entire directory is removed. A conformant implementation
-- need not support directory removal in all situations (e.g. removal of
-- the root directory).
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument The operand is not a valid directory
-- name. [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The directory does not exist.
-- [ENOENT, ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EROFS, EACCES, EPERM]
-- - UnsatisfiedConstraints Implementation-dependent
-- constraints are not satisfied. [EBUSY, ENOTEMPTY,
-- EEXIST]
-- - UnsupportedOperation The implementation does not support
-- removal in this situation. [EINVAL]
-- - InappropriateType The operand refers to an existing
-- non-directory object. [ENOTDIR]
--
removeDirectory :: FilePath -> IO ()
-- | removeDirectoryRecursive dir removes an existing
-- directory dir together with its contents and subdirectories.
-- Within this directory, symbolic links are removed without affecting
-- their targets.
--
-- On Windows, the operation fails if dir is a directory symbolic
-- link.
--
-- This operation is reported to be flaky on Windows so retry logic may
-- be advisable. See:
-- https://github.com/haskell/directory/pull/108
removeDirectoryRecursive :: FilePath -> IO ()
-- | Removes a file or directory at path together with its contents
-- and subdirectories. Symbolic links are removed without affecting their
-- targets. If the path does not exist, nothing happens.
--
-- Unlike other removal functions, this function will also attempt to
-- delete files marked as read-only or otherwise made unremovable due to
-- permissions. As a result, if the removal is incomplete, the
-- permissions or attributes on the remaining files may be altered. If
-- there are hard links in the directory, then permissions on all related
-- hard links may be altered.
--
-- If an entry within the directory vanishes while
-- removePathForcibly is running, it is silently ignored.
--
-- If an exception occurs while removing an entry,
-- removePathForcibly will still try to remove as many entries
-- as it can before failing with an exception. The first exception that
-- it encountered is re-thrown.
removePathForcibly :: FilePath -> IO ()
-- | renameDirectory old new changes the name of an
-- existing directory from old to new. If the new
-- directory already exists, it is atomically replaced by the old
-- directory. If the new directory is neither the old
-- directory nor an alias of the old directory, it is removed as
-- if by removeDirectory. A conformant implementation need not
-- support renaming directories in all situations (e.g. renaming to an
-- existing directory, or across different physical devices), but the
-- constraints must be documented.
--
-- On Win32 platforms, renameDirectory fails if the new
-- directory already exists.
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument Either operand is not a valid directory
-- name. [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The original directory does not exist,
-- or there is no path to the target. [ENOENT, ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EROFS, EACCES, EPERM]
-- - isFullError Insufficient resources are available to perform
-- the operation. [EDQUOT, ENOSPC, ENOMEM, EMLINK]
-- - UnsatisfiedConstraints Implementation-dependent
-- constraints are not satisfied. [EBUSY, ENOTEMPTY,
-- EEXIST]
-- - UnsupportedOperation The implementation does not support
-- renaming in this situation. [EINVAL, EXDEV]
-- - InappropriateType Either path refers to an existing
-- non-directory object. [ENOTDIR, EISDIR]
--
renameDirectory :: FilePath -> FilePath -> IO ()
-- | listDirectory dir returns a list of all entries
-- in dir without the special entries (. and
-- ..).
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument The operand is not a valid directory
-- name. [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The directory does not exist.
-- [ENOENT, ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EACCES]
-- - isFullError Insufficient resources are available to perform
-- the operation. [EMFILE, ENFILE]
-- - InappropriateType The path refers to an existing
-- non-directory object. [ENOTDIR]
--
listDirectory :: FilePath -> IO [FilePath]
-- | Similar to listDirectory, but always includes the special
-- entries (. and ..). (This applies to Windows as
-- well.)
--
-- The operation may fail with the same exceptions as
-- listDirectory.
getDirectoryContents :: FilePath -> IO [FilePath]
-- | Obtain the current working directory as an absolute path.
--
-- In a multithreaded program, the current working directory is a global
-- state shared among all threads of the process. Therefore, when
-- performing filesystem operations from multiple threads, it is highly
-- recommended to use absolute rather than relative paths (see:
-- makeAbsolute).
--
-- Note that getCurrentDirectory is not guaranteed to return the
-- same path received by setCurrentDirectory. On POSIX systems,
-- the path returned will always be fully dereferenced (not contain any
-- symbolic links). For more information, refer to the documentation of
-- getcwd.
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - isDoesNotExistError There is no path referring to the
-- working directory. [EPERM, ENOENT, ESTALE...]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EACCES]
-- - isFullError Insufficient resources are available to perform
-- the operation.
-- - UnsupportedOperation The operating system has no notion
-- of current working directory.
--
getCurrentDirectory :: IO FilePath
-- | Change the working directory to the given path.
--
-- In a multithreaded program, the current working directory is a global
-- state shared among all threads of the process. Therefore, when
-- performing filesystem operations from multiple threads, it is highly
-- recommended to use absolute rather than relative paths (see:
-- makeAbsolute).
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument The operand is not a valid directory
-- name. [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The directory does not exist.
-- [ENOENT, ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EACCES]
-- - UnsupportedOperation The operating system has no notion
-- of current working directory, or the working directory cannot be
-- dynamically changed.
-- - InappropriateType The path refers to an existing
-- non-directory object. [ENOTDIR]
--
setCurrentDirectory :: FilePath -> IO ()
-- | Run an IO action with the given working directory and restore
-- the original working directory afterwards, even if the given action
-- fails due to an exception.
--
-- The operation may fail with the same exceptions as
-- getCurrentDirectory and setCurrentDirectory.
withCurrentDirectory :: FilePath -> IO a -> IO a
-- | Returns the current user's home directory.
--
-- The directory returned is expected to be writable by the current user,
-- but note that it isn't generally considered good practice to store
-- application-specific data here; use getXdgDirectory or
-- getAppUserDataDirectory instead.
--
-- On Unix, getHomeDirectory behaves as follows:
--
--
-- - Returns $HOME env variable if set (including to an empty
-- string).
-- - Otherwise uses home directory returned by getpwuid_r
-- using the UID of the current proccesses user. This basically reads the
-- etcpasswd file. An empty home directory field is considered
-- valid.
--
--
-- On Windows, the system is queried for a suitable path; a typical path
-- might be C:/Users/<user>.
--
-- The operation may fail with:
--
--
-- - UnsupportedOperation The operating system has no notion
-- of home directory.
-- - isDoesNotExistError The home directory for the current user
-- does not exist, or cannot be found.
--
getHomeDirectory :: IO FilePath
-- | Special directories for storing user-specific application data,
-- configuration, and cache files, as specified by the XDG Base
-- Directory Specification.
--
-- Note: On Windows, XdgData and XdgConfig usually map to
-- the same directory.
data XdgDirectory
-- | For data files (e.g. images). It uses the XDG_DATA_HOME
-- environment variable. On non-Windows systems, the default is
-- ~/.local/share. On Windows, the default is %APPDATA%
-- (e.g. C:/Users/<user>/AppData/Roaming). Can be
-- considered as the user-specific equivalent of /usr/share.
XdgData :: XdgDirectory
-- | For configuration files. It uses the XDG_CONFIG_HOME
-- environment variable. On non-Windows systems, the default is
-- ~/.config. On Windows, the default is %APPDATA%
-- (e.g. C:/Users/<user>/AppData/Roaming). Can be
-- considered as the user-specific equivalent of /etc.
XdgConfig :: XdgDirectory
-- | For non-essential files (e.g. cache). It uses the
-- XDG_CACHE_HOME environment variable. On non-Windows systems,
-- the default is ~/.cache. On Windows, the default is
-- %LOCALAPPDATA% (e.g.
-- C:/Users/<user>/AppData/Local). Can be
-- considered as the user-specific equivalent of /var/cache.
XdgCache :: XdgDirectory
-- | For data that should persist between (application) restarts, but that
-- is not important or portable enough to the user that it should be
-- stored in XdgData. It uses the XDG_STATE_HOME
-- environment variable. On non-Windows sytems, the default is
-- ~/.local/state. On Windows, the default is
-- %LOCALAPPDATA% (e.g.
-- C:/Users/<user>/AppData/Local).
XdgState :: XdgDirectory
-- | Obtain the paths to special directories for storing user-specific
-- application data, configuration, and cache files, conforming to the
-- XDG Base Directory Specification. Compared with
-- getAppUserDataDirectory, this function provides a more
-- fine-grained hierarchy as well as greater flexibility for the user.
--
-- On Windows, XdgData and XdgConfig usually map to the
-- same directory unless overridden.
--
-- Refer to the docs of XdgDirectory for more details.
--
-- The second argument is usually the name of the application. Since it
-- will be integrated into the path, it must consist of valid path
-- characters. Note: if the second argument is an absolute path, it will
-- just return the second argument.
--
-- Note: The directory may not actually exist, in which case you would
-- need to create it with file mode 700 (i.e. only accessible by
-- the owner).
--
-- As of 1.3.5.0, the environment variable is ignored if set to a
-- relative path, per revised XDG Base Directory Specification. See
-- #100.
getXdgDirectory :: XdgDirectory -> FilePath -> IO FilePath
-- | Search paths for various application data, as specified by the XDG
-- Base Directory Specification.
--
-- The list of paths is split using searchPathSeparator, which on
-- Windows is a semicolon.
--
-- Note: On Windows, XdgDataDirs and XdgConfigDirs usually
-- yield the same result.
data XdgDirectoryList
-- | For data files (e.g. images). It uses the XDG_DATA_DIRS
-- environment variable. On non-Windows systems, the default is
-- /usr/local/share/ and /usr/share/. On Windows, the
-- default is %PROGRAMDATA% or %ALLUSERSPROFILE% (e.g.
-- C:/ProgramData).
XdgDataDirs :: XdgDirectoryList
-- | For configuration files. It uses the XDG_CONFIG_DIRS
-- environment variable. On non-Windows systems, the default is
-- /etc/xdg. On Windows, the default is %PROGRAMDATA%
-- or %ALLUSERSPROFILE% (e.g. C:/ProgramData).
XdgConfigDirs :: XdgDirectoryList
-- | Similar to getXdgDirectory but retrieves the entire list of XDG
-- directories.
--
-- On Windows, XdgDataDirs and XdgConfigDirs usually map to
-- the same list of directories unless overridden.
--
-- Refer to the docs of XdgDirectoryList for more details.
getXdgDirectoryList :: XdgDirectoryList -> IO [FilePath]
-- | Obtain the path to a special directory for storing user-specific
-- application data (traditional Unix location). Newer applications may
-- prefer the the XDG-conformant location provided by
-- getXdgDirectory (migration guide).
--
-- The argument is usually the name of the application. Since it will be
-- integrated into the path, it must consist of valid path characters.
--
--
-- - On Unix-like systems, the path is
-- ~/.<app>.
-- - On Windows, the path is %APPDATA%/<app>
-- (e.g.
-- C:/Users/<user>/AppData/Roaming/<app>)
--
--
-- Note: the directory may not actually exist, in which case you would
-- need to create it. It is expected that the parent directory exists and
-- is writable.
--
-- The operation may fail with:
--
--
-- - UnsupportedOperation The operating system has no notion
-- of application-specific data directory.
-- - isDoesNotExistError The home directory for the current user
-- does not exist, or cannot be found.
--
getAppUserDataDirectory :: FilePath -> IO FilePath
-- | Returns the current user's document directory.
--
-- The directory returned is expected to be writable by the current user,
-- but note that it isn't generally considered good practice to store
-- application-specific data here; use getXdgDirectory or
-- getAppUserDataDirectory instead.
--
-- On Unix, getUserDocumentsDirectory returns the value of the
-- HOME environment variable. On Windows, the system is queried
-- for a suitable path; a typical path might be
-- C:/Users/<user>/Documents.
--
-- The operation may fail with:
--
--
-- - UnsupportedOperation The operating system has no notion
-- of document directory.
-- - isDoesNotExistError The document directory for the current
-- user does not exist, or cannot be found.
--
getUserDocumentsDirectory :: IO FilePath
-- | Returns the current directory for temporary files.
--
-- On Unix, getTemporaryDirectory returns the value of the
-- TMPDIR environment variable or "/tmp" if the variable isn't
-- defined. On Windows, the function checks for the existence of
-- environment variables in the following order and uses the first path
-- found:
--
--
-- - TMP environment variable.
-- - TEMP environment variable.
-- - USERPROFILE environment variable.
-- - The Windows directory
--
--
-- The operation may fail with:
--
--
-- - UnsupportedOperation The operating system has no notion
-- of temporary directory.
--
--
-- The function doesn't verify whether the path exists.
getTemporaryDirectory :: IO FilePath
-- | removeFile file removes the directory entry for an
-- existing file file, where file is not itself a
-- directory. The implementation may specify additional constraints which
-- must be satisfied before a file can be removed (e.g. the file may not
-- be in use by other processes).
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument The operand is not a valid file name.
-- [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The file does not exist. [ENOENT,
-- ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EROFS, EACCES, EPERM]
-- - UnsatisfiedConstraints Implementation-dependent
-- constraints are not satisfied. [EBUSY]
-- - InappropriateType The operand refers to an existing
-- directory. [EPERM, EINVAL]
--
removeFile :: FilePath -> IO ()
-- | renameFile old new changes the name of an existing
-- file system object from old to new. If the new
-- object already exists, it is replaced by the old object.
-- Neither path may refer to an existing directory.
--
-- A conformant implementation need not support renaming files in all
-- situations (e.g. renaming across different physical devices), but the
-- constraints must be documented. On Windows, this does not support
-- renaming across different physical devices; if you are looking to do
-- so, consider using copyFileWithMetadata and removeFile.
--
-- On Windows, this calls MoveFileEx with
-- MOVEFILE_REPLACE_EXISTING set, which is not guaranteed to be
-- atomic (https://github.com/haskell/directory/issues/109).
--
-- On other platforms, this operation is atomic.
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument Either operand is not a valid file name.
-- [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The original file does not exist, or
-- there is no path to the target. [ENOENT, ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EROFS, EACCES, EPERM]
-- - isFullError Insufficient resources are available to perform
-- the operation. [EDQUOT, ENOSPC, ENOMEM, EMLINK]
-- - UnsatisfiedConstraints Implementation-dependent
-- constraints are not satisfied. [EBUSY]
-- - UnsupportedOperation The implementation does not support
-- renaming in this situation. [EXDEV]
-- - InappropriateType Either path refers to an existing
-- directory. [ENOTDIR, EISDIR, EINVAL, EEXIST, ENOTEMPTY]
--
renameFile :: FilePath -> FilePath -> IO ()
-- | Rename a file or directory. If the destination path already exists, it
-- is replaced atomically. The destination path must not point to an
-- existing directory. A conformant implementation need not support
-- renaming files in all situations (e.g. renaming across different
-- physical devices), but the constraints must be documented.
--
-- The operation may fail with:
--
--
-- - HardwareFault A physical I/O error has occurred.
-- [EIO]
-- - InvalidArgument Either operand is not a valid file name.
-- [ENAMETOOLONG, ELOOP]
-- - isDoesNotExistError The original file does not exist, or
-- there is no path to the target. [ENOENT, ENOTDIR]
-- - isPermissionError The process has insufficient privileges
-- to perform the operation. [EROFS, EACCES, EPERM]
-- - isFullError Insufficient resources are available to perform
-- the operation. [EDQUOT, ENOSPC, ENOMEM, EMLINK]
-- - UnsatisfiedConstraints Implementation-dependent
-- constraints are not satisfied. [EBUSY]
-- - UnsupportedOperation The implementation does not support
-- renaming in this situation. [EXDEV]
-- - InappropriateType Either the destination path refers to
-- an existing directory, or one of the parent segments in the
-- destination path is not a directory. [ENOTDIR, EISDIR, EINVAL,
-- EEXIST, ENOTEMPTY]
--
renamePath :: FilePath -> FilePath -> IO ()
-- | Copy a file with its permissions. If the destination file already
-- exists, it is replaced atomically. Neither path may refer to an
-- existing directory. No exceptions are thrown if the permissions could
-- not be copied.
copyFile :: FilePath -> FilePath -> IO ()
-- | Copy a file with its associated metadata. If the destination file
-- already exists, it is overwritten. There is no guarantee of atomicity
-- in the replacement of the destination file. Neither path may refer to
-- an existing directory. If the source and/or destination are symbolic
-- links, the copy is performed on the targets of the links.
--
-- On Windows, it behaves like the Win32 function CopyFile, which
-- copies various kinds of metadata including file attributes and
-- security resource properties.
--
-- On Unix-like systems, permissions, access time, and modification time
-- are preserved. If possible, the owner and group are also preserved.
-- Note that the very act of copying can change the access time of the
-- source file, hence the access times of the two files may differ after
-- the operation completes.
copyFileWithMetadata :: FilePath -> FilePath -> IO ()
-- | Obtain the size of a file in bytes.
getFileSize :: FilePath -> IO Integer
-- | Make a path absolute, normalize the path, and remove as many
-- indirections from it as possible. Any trailing path separators are
-- discarded via dropTrailingPathSeparator. Additionally, on
-- Windows the letter case of the path is canonicalized.
--
-- Note: This function is a very big hammer. If you only need an
-- absolute path, makeAbsolute is sufficient for removing
-- dependence on the current working directory.
--
-- Indirections include the two special directories . and
-- .., as well as any symbolic links (and junction points on
-- Windows). The input path need not point to an existing file or
-- directory. Canonicalization is performed on the longest prefix of the
-- path that points to an existing file or directory. The remaining
-- portion of the path that does not point to an existing file or
-- directory will still be normalized, but case canonicalization and
-- indirection removal are skipped as they are impossible to do on a
-- nonexistent path.
--
-- Most programs should not worry about the canonicity of a path. In
-- particular, despite the name, the function does not truly guarantee
-- canonicity of the returned path due to the presence of hard links,
-- mount points, etc.
--
-- If the path points to an existing file or directory, then the output
-- path shall also point to the same file or directory, subject to the
-- condition that the relevant parts of the file system do not change
-- while the function is still running. In other words, the function is
-- definitively not atomic. The results can be utterly wrong if the
-- portions of the path change while this function is running.
--
-- Since some indirections (symbolic links on all systems, .. on
-- non-Windows systems, and junction points on Windows) are dependent on
-- the state of the existing filesystem, the function can only make a
-- conservative attempt by removing such indirections from the longest
-- prefix of the path that still points to an existing file or directory.
--
-- Note that on Windows parent directories .. are always fully
-- expanded before the symbolic links, as consistent with the rest of the
-- Windows API (such as GetFullPathName). In contrast, on POSIX
-- systems parent directories .. are expanded alongside symbolic
-- links from left to right. To put this more concretely: if L
-- is a symbolic link for R/P, then on Windows L\..
-- refers to ., whereas on other operating systems L/..
-- refers to R.
--
-- Similar to normalise, passing an empty path is equivalent to
-- passing the current directory.
--
-- canonicalizePath can resolve at least 64 indirections in a
-- single path, more than what is supported by most operating systems.
-- Therefore, it may return the fully resolved path even though the
-- operating system itself would have long given up.
--
-- On Windows XP or earlier systems, junction expansion is not performed
-- due to their lack of GetFinalPathNameByHandle.
--
-- Changes since 1.2.3.0: The function has been altered to be more
-- robust and has the same exception behavior as makeAbsolute.
--
-- Changes since 1.3.0.0: The function no longer preserves the
-- trailing path separator. File symbolic links that appear in the middle
-- of a path are properly dereferenced. Case canonicalization and
-- symbolic link expansion are now performed on Windows.
canonicalizePath :: FilePath -> IO FilePath
-- | Convert a path into an absolute path. If the given path is relative,
-- the current directory is prepended and then the combined result is
-- normalized. If the path is already absolute, the path is simply
-- normalized. The function preserves the presence or absence of the
-- trailing path separator unless the path refers to the root directory
-- /.
--
-- If the path is already absolute, the operation never fails. Otherwise,
-- the operation may fail with the same exceptions as
-- getCurrentDirectory.
makeAbsolute :: FilePath -> IO FilePath
-- | Construct a path relative to the current directory, similar to
-- makeRelative.
--
-- The operation may fail with the same exceptions as
-- getCurrentDirectory.
makeRelativeToCurrentDirectory :: FilePath -> IO FilePath
-- | Test whether the given path points to an existing filesystem object.
-- If the user lacks necessary permissions to search the parent
-- directories, this function may return false even if the file does
-- actually exist.
doesPathExist :: FilePath -> IO Bool
-- | The operation doesFileExist returns True if the argument
-- file exists and is not a directory, and False otherwise.
doesFileExist :: FilePath -> IO Bool
-- | The operation doesDirectoryExist returns True if the
-- argument file exists and is either a directory or a symbolic link to a
-- directory, and False otherwise.
doesDirectoryExist :: FilePath -> IO Bool
-- | Given the name or path of an executable file, findExecutable
-- searches for such a file in a list of system-defined locations, which
-- generally includes PATH and possibly more. The full path to
-- the executable is returned if found. For example, (findExecutable
-- "ghc") would normally give you the path to GHC.
--
-- The path returned by findExecutable name corresponds
-- to the program that would be executed by createProcess
-- when passed the same string (as a RawCommand, not a
-- ShellCommand), provided that name is not a relative
-- path with more than one segment.
--
-- On Windows, findExecutable calls the Win32 function
-- SearchPath, which may search other places before
-- checking the directories in the PATH environment variable.
-- Where it actually searches depends on registry settings, but notably
-- includes the directory containing the current executable.
--
-- On non-Windows platforms, the behavior is equivalent to
-- findFileWith using the search directories from the
-- PATH environment variable and testing each file for
-- executable permissions. Details can be found in the documentation of
-- findFileWith.
findExecutable :: String -> IO (Maybe FilePath)
-- | Search for executable files in a list of system-defined locations,
-- which generally includes PATH and possibly more.
--
-- On Windows, this only returns the first occurrence, if any. Its
-- behavior is therefore equivalent to findExecutable.
--
-- On non-Windows platforms, the behavior is equivalent to
-- findExecutablesInDirectories using the search directories from
-- the PATH environment variable. Details can be found in the
-- documentation of findExecutablesInDirectories.
findExecutables :: String -> IO [FilePath]
-- | Given a name or path, findExecutable appends the
-- exeExtension to the query and searches for executable files in
-- the list of given search directories and returns all occurrences.
--
-- The behavior is equivalent to findFileWith using the given
-- search directories and testing each file for executable permissions.
-- Details can be found in the documentation of findFileWith.
--
-- Unlike other similarly named functions,
-- findExecutablesInDirectories does not use SearchPath
-- from the Win32 API. The behavior of this function on Windows is
-- therefore equivalent to those on non-Windows platforms.
findExecutablesInDirectories :: [FilePath] -> String -> IO [FilePath]
-- | Search through the given list of directories for the given file.
--
-- The behavior is equivalent to findFileWith, returning only the
-- first occurrence. Details can be found in the documentation of
-- findFileWith.
findFile :: [FilePath] -> String -> IO (Maybe FilePath)
-- | Search through the given list of directories for the given file and
-- returns all paths where the given file exists.
--
-- The behavior is equivalent to findFilesWith. Details can be
-- found in the documentation of findFilesWith.
findFiles :: [FilePath] -> String -> IO [FilePath]
-- | Search through a given list of directories for a file that has the
-- given name and satisfies the given predicate and return the path of
-- the first occurrence. The directories are checked in a left-to-right
-- order.
--
-- This is essentially a more performant version of findFilesWith
-- that always returns the first result, if any. Details can be found in
-- the documentation of findFilesWith.
findFileWith :: (FilePath -> IO Bool) -> [FilePath] -> String -> IO (Maybe FilePath)
-- | findFilesWith predicate dirs name searches through the list
-- of directories (dirs) for files that have the given
-- name and satisfy the given predicate and returns the
-- paths of those files. The directories are checked in a left-to-right
-- order and the paths are returned in the same order.
--
-- If the name is a relative path, then for every search
-- directory dir, the function checks whether dir
-- </> name exists and satisfies the predicate. If
-- so, dir </> name is returned as one of the
-- results. In other words, the returned paths can be either relative or
-- absolute depending on the search directories were used. If there are
-- no search directories, no results are ever returned.
--
-- If the name is an absolute path, then the function will
-- return a single result if the file exists and satisfies the predicate
-- and no results otherwise. This is irrespective of what search
-- directories were given.
findFilesWith :: (FilePath -> IO Bool) -> [FilePath] -> String -> IO [FilePath]
-- | Filename extension for executable files (including the dot if any)
-- (usually "" on POSIX systems and ".exe" on Windows
-- or OS/2).
exeExtension :: String
-- | Create a file symbolic link. The target path can be either
-- absolute or relative and need not refer to an existing file. The order
-- of arguments follows the POSIX convention.
--
-- To remove an existing file symbolic link, use removeFile.
--
-- Although the distinction between file symbolic links and
-- directory symbolic links does not exist on POSIX systems, on
-- Windows this is an intrinsic property of every symbolic link and
-- cannot be changed without recreating the link. A file symbolic link
-- that actually points to a directory will fail to dereference and vice
-- versa. Moreover, creating symbolic links on Windows may require
-- privileges unavailable to users outside the Administrators group.
-- Portable programs that use symbolic links should take both into
-- consideration.
--
-- On Windows, the function is implemented using
-- CreateSymbolicLink. Since 1.3.3.0, the
-- SYMBOLIC_LINK_FLAG_ALLOW_UNPRIVILEGED_CREATE flag is included
-- if supported by the operating system. On POSIX, the function uses
-- symlink and is therefore atomic.
--
-- Windows-specific errors: This operation may fail with
-- permissionErrorType if the user lacks the privileges to create
-- symbolic links. It may also fail with illegalOperationErrorType
-- if the file system does not support symbolic links.
createFileLink :: FilePath -> FilePath -> IO ()
-- | Create a directory symbolic link. The target path can be either
-- absolute or relative and need not refer to an existing directory. The
-- order of arguments follows the POSIX convention.
--
-- To remove an existing directory symbolic link, use
-- removeDirectoryLink.
--
-- Although the distinction between file symbolic links and
-- directory symbolic links does not exist on POSIX systems, on
-- Windows this is an intrinsic property of every symbolic link and
-- cannot be changed without recreating the link. A file symbolic link
-- that actually points to a directory will fail to dereference and vice
-- versa. Moreover, creating symbolic links on Windows may require
-- privileges unavailable to users outside the Administrators group.
-- Portable programs that use symbolic links should take both into
-- consideration.
--
-- On Windows, the function is implemented using
-- CreateSymbolicLink with
-- SYMBOLIC_LINK_FLAG_DIRECTORY. Since 1.3.3.0, the
-- SYMBOLIC_LINK_FLAG_ALLOW_UNPRIVILEGED_CREATE flag is also
-- included if supported by the operating system. On POSIX, this is an
-- alias for createFileLink and is therefore atomic.
--
-- Windows-specific errors: This operation may fail with
-- permissionErrorType if the user lacks the privileges to create
-- symbolic links. It may also fail with illegalOperationErrorType
-- if the file system does not support symbolic links.
createDirectoryLink :: FilePath -> FilePath -> IO ()
-- | Remove an existing directory symbolic link.
--
-- On Windows, this is an alias for removeDirectory. On POSIX
-- systems, this is an alias for removeFile.
--
-- See also: removeFile, which can remove an existing file
-- symbolic link.
removeDirectoryLink :: FilePath -> IO ()
-- | Check whether an existing path is a symbolic link. If
-- path is a regular file or directory, False is
-- returned. If path does not exist or is otherwise
-- inaccessible, an exception is thrown (see below).
--
-- On Windows, this checks for FILE_ATTRIBUTE_REPARSE_POINT. In
-- addition to symbolic links, the function also returns true on junction
-- points. On POSIX systems, this checks for S_IFLNK.
--
-- The operation may fail with:
--
--
pathIsSymbolicLink :: FilePath -> IO Bool
-- | Retrieve the target path of either a file or directory symbolic link.
-- The returned path may not be absolute, may not exist, and may not even
-- be a valid path.
--
-- On Windows systems, this calls DeviceIoControl with
-- FSCTL_GET_REPARSE_POINT. In addition to symbolic links, the
-- function also works on junction points. On POSIX systems, this calls
-- readlink.
--
-- Windows-specific errors: This operation may fail with
-- illegalOperationErrorType if the file system does not support
-- symbolic links.
getSymbolicLinkTarget :: FilePath -> IO FilePath
data Permissions
emptyPermissions :: Permissions
readable :: Permissions -> Bool
writable :: Permissions -> Bool
executable :: Permissions -> Bool
searchable :: Permissions -> Bool
setOwnerReadable :: Bool -> Permissions -> Permissions
setOwnerWritable :: Bool -> Permissions -> Permissions
setOwnerExecutable :: Bool -> Permissions -> Permissions
setOwnerSearchable :: Bool -> Permissions -> Permissions
-- | Get the permissions of a file or directory.
--
-- On Windows, the writable permission corresponds to the
-- "read-only" attribute. The executable permission is set if the
-- file extension is of an executable file type. The readable
-- permission is always set.
--
-- On POSIX systems, this returns the result of access.
--
-- The operation may fail with:
--
--
getPermissions :: FilePath -> IO Permissions
-- | Set the permissions of a file or directory.
--
-- On Windows, this is only capable of changing the writable
-- permission, which corresponds to the "read-only" attribute. Changing
-- the other permissions has no effect.
--
-- On POSIX systems, this sets the owner permissions.
--
-- The operation may fail with:
--
--
setPermissions :: FilePath -> Permissions -> IO ()
-- | Copy the permissions of one file to another. This reproduces the
-- permissions more accurately than using getPermissions followed
-- by setPermissions.
--
-- On Windows, this copies only the read-only attribute.
--
-- On POSIX systems, this is equivalent to stat followed by
-- chmod.
copyPermissions :: FilePath -> FilePath -> IO ()
-- | Obtain the time at which the file or directory was last accessed.
--
-- The operation may fail with:
--
--
--
-- Caveat for POSIX systems: This function returns a timestamp with
-- sub-second resolution only if this package is compiled against
-- unix-2.6.0.0 or later and the underlying filesystem supports
-- them.
getAccessTime :: FilePath -> IO UTCTime
-- | Obtain the time at which the file or directory was last modified.
--
-- The operation may fail with:
--
--
--
-- Caveat for POSIX systems: This function returns a timestamp with
-- sub-second resolution only if this package is compiled against
-- unix-2.6.0.0 or later and the underlying filesystem supports
-- them.
getModificationTime :: FilePath -> IO UTCTime
-- | Change the time at which the file or directory was last accessed.
--
-- The operation may fail with:
--
--
--
-- Some caveats for POSIX systems:
--
--
-- - Not all systems support utimensat, in which case the
-- function can only emulate the behavior by reading the modification
-- time and then setting both the access and modification times together.
-- On systems where utimensat is supported, the access time is
-- set atomically with nanosecond precision.
-- - If compiled against a version of unix prior to
-- 2.7.0.0, the function would not be able to set timestamps
-- with sub-second resolution. In this case, there would also be loss of
-- precision in the modification time.
--
setAccessTime :: FilePath -> UTCTime -> IO ()
-- | Change the time at which the file or directory was last modified.
--
-- The operation may fail with:
--
--
--
-- Some caveats for POSIX systems:
--
--
-- - Not all systems support utimensat, in which case the
-- function can only emulate the behavior by reading the access time and
-- then setting both the access and modification times together. On
-- systems where utimensat is supported, the modification time
-- is set atomically with nanosecond precision.
-- - If compiled against a version of unix prior to
-- 2.7.0.0, the function would not be able to set timestamps
-- with sub-second resolution. In this case, there would also be loss of
-- precision in the access time.
--
setModificationTime :: FilePath -> UTCTime -> IO ()
-- | Deprecated: Use pathIsSymbolicLink instead
isSymbolicLink :: FilePath -> IO Bool