Copyright | © 2016–present Mark Karpov |
---|---|
License | BSD 3 clause |
Maintainer | Mark Karpov <markkarpov92@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module provides an interface to System.Directory for users of the Path module. It also implements some extra functionality like recursive scanning and copying of directories, working with temporary files/directories, etc.
Synopsis
- createDir :: MonadIO m => Path b Dir -> m ()
- createDirIfMissing :: MonadIO m => Bool -> Path b Dir -> m ()
- ensureDir :: MonadIO m => Path b Dir -> m ()
- removeDir :: MonadIO m => Path b Dir -> m ()
- removeDirRecur :: MonadIO m => Path b Dir -> m ()
- removePathForcibly :: MonadIO m => Path b t -> m ()
- renameDir :: MonadIO m => Path b0 Dir -> Path b1 Dir -> m ()
- renamePath :: MonadIO m => Path b0 t -> Path b1 t -> m ()
- listDir :: MonadIO m => Path b Dir -> m ([Path Abs Dir], [Path Abs File])
- listDirRel :: MonadIO m => Path b Dir -> m ([Path Rel Dir], [Path Rel File])
- listDirRecur :: MonadIO m => Path b Dir -> m ([Path Abs Dir], [Path Abs File])
- listDirRecurRel :: MonadIO m => Path b Dir -> m ([Path Rel Dir], [Path Rel File])
- copyDirRecur :: (MonadIO m, MonadCatch m) => Path b0 Dir -> Path b1 Dir -> m ()
- copyDirRecur' :: (MonadIO m, MonadCatch m) => Path b0 Dir -> Path b1 Dir -> m ()
- data WalkAction b
- = WalkFinish
- | WalkExclude [Path b Dir]
- walkDir :: MonadIO m => (Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs)) -> Path b Dir -> m ()
- walkDirRel :: MonadIO m => (Path Rel Dir -> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel)) -> Path b Dir -> m ()
- walkDirAccum :: (MonadIO m, Monoid o) => Maybe (Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs)) -> (Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m o) -> Path b Dir -> m o
- walkDirAccumRel :: (MonadIO m, Monoid o) => Maybe (Path Rel Dir -> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel)) -> (Path Rel Dir -> [Path Rel Dir] -> [Path Rel File] -> m o) -> Path b Dir -> m o
- getCurrentDir :: MonadIO m => m (Path Abs Dir)
- setCurrentDir :: MonadIO m => Path b Dir -> m ()
- withCurrentDir :: (MonadIO m, MonadMask m) => Path b Dir -> m a -> m a
- getHomeDir :: MonadIO m => m (Path Abs Dir)
- getAppUserDataDir :: MonadIO m => String -> m (Path Abs Dir)
- getUserDocsDir :: MonadIO m => m (Path Abs Dir)
- getTempDir :: MonadIO m => m (Path Abs Dir)
- data XdgDirectory
- getXdgDir :: MonadIO m => XdgDirectory -> Maybe (Path Rel Dir) -> m (Path Abs Dir)
- data XdgDirectoryList
- getXdgDirList :: MonadIO m => XdgDirectoryList -> m [Path Abs Dir]
- class AnyPath path where
- type AbsPath path :: Type
- type RelPath path :: Type
- canonicalizePath :: MonadIO m => path -> m (AbsPath path)
- makeAbsolute :: MonadIO m => path -> m (AbsPath path)
- makeRelative :: MonadThrow m => Path Abs Dir -> path -> m (RelPath path)
- makeRelativeToCurrentDir :: MonadIO m => path -> m (RelPath path)
- resolveFile :: MonadIO m => Path Abs Dir -> FilePath -> m (Path Abs File)
- resolveFile' :: MonadIO m => FilePath -> m (Path Abs File)
- resolveDir :: MonadIO m => Path Abs Dir -> FilePath -> m (Path Abs Dir)
- resolveDir' :: MonadIO m => FilePath -> m (Path Abs Dir)
- removeFile :: MonadIO m => Path b File -> m ()
- renameFile :: MonadIO m => Path b0 File -> Path b1 File -> m ()
- copyFile :: MonadIO m => Path b0 File -> Path b1 File -> m ()
- getFileSize :: MonadIO m => Path b File -> m Integer
- findExecutable :: MonadIO m => Path Rel File -> m (Maybe (Path Abs File))
- findFile :: MonadIO m => [Path b Dir] -> Path Rel File -> m (Maybe (Path Abs File))
- findFiles :: MonadIO m => [Path b Dir] -> Path Rel File -> m [Path Abs File]
- findFilesWith :: MonadIO m => (Path Abs File -> m Bool) -> [Path b Dir] -> Path Rel File -> m [Path Abs File]
- createFileLink :: MonadIO m => Path b0 File -> Path b1 File -> m ()
- createDirLink :: MonadIO m => Path b0 Dir -> Path b1 Dir -> m ()
- removeDirLink :: MonadIO m => Path b Dir -> m ()
- getSymlinkTarget :: MonadIO m => Path b t -> m FilePath
- isSymlink :: MonadIO m => Path b t -> m Bool
- withTempFile :: (MonadIO m, MonadMask m) => Path b Dir -> String -> (Path Abs File -> Handle -> m a) -> m a
- withTempDir :: (MonadIO m, MonadMask m) => Path b Dir -> String -> (Path Abs Dir -> m a) -> m a
- withSystemTempFile :: (MonadIO m, MonadMask m) => String -> (Path Abs File -> Handle -> m a) -> m a
- withSystemTempDir :: (MonadIO m, MonadMask m) => String -> (Path Abs Dir -> m a) -> m a
- openTempFile :: MonadIO m => Path b Dir -> String -> m (Path Abs File, Handle)
- openBinaryTempFile :: MonadIO m => Path b Dir -> String -> m (Path Abs File, Handle)
- createTempDir :: MonadIO m => Path b Dir -> String -> m (Path Abs Dir)
- doesPathExist :: MonadIO m => Path b t -> m Bool
- doesFileExist :: MonadIO m => Path b File -> m Bool
- doesDirExist :: MonadIO m => Path b Dir -> m Bool
- isLocationOccupied :: MonadIO m => Path b t -> m Bool
- forgivingAbsence :: (MonadIO m, MonadCatch m) => m a -> m (Maybe a)
- ignoringAbsence :: (MonadIO m, MonadCatch m) => m a -> m ()
- 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
- getPermissions :: MonadIO m => Path b t -> m Permissions
- setPermissions :: MonadIO m => Path b t -> Permissions -> m ()
- copyPermissions :: MonadIO m => Path b0 t0 -> Path b1 t1 -> m ()
- getAccessTime :: MonadIO m => Path b t -> m UTCTime
- setAccessTime :: MonadIO m => Path b t -> UTCTime -> m ()
- setModificationTime :: MonadIO m => Path b t -> UTCTime -> m ()
- getModificationTime :: MonadIO m => Path b t -> m UTCTime
Actions on directories
createDir :: MonadIO m => Path b Dir -> m () Source #
creates a new directory createDir
dirdir
which is initially
empty, or as near to empty as the operating system allows.
The operation may fail with:
isPermissionError
/PermissionDenied
The process has insufficient privileges to perform the operation.[EROFS, EACCES]
isAlreadyExistsError
/AlreadyExists
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]
NoSuchThing
There is no path to the directory.[ENOENT, ENOTDIR]
ResourceExhausted
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]
:: MonadIO m | |
=> Bool | Create its parents too? |
-> Path b Dir | The path to the directory you want to make |
-> m () |
creates a new directory createDirIfMissing
parents dirdir
if it
doesn't exist. If the first argument is True
the function will also
create all parent directories if they are missing.
ensureDir :: MonadIO m => Path b Dir -> m () Source #
Ensure that a directory exists creating it and its parent directories if necessary. This is just a handy shortcut:
ensureDir = createDirIfMissing True
Since: 0.3.1
removeDir :: MonadIO m => Path b Dir -> m () Source #
removes an existing directory removeDir
dirdir
. 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
/NoSuchThing
The directory does not exist.[ENOENT, ENOTDIR]
isPermissionError
/PermissionDenied
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]
removeDirRecur :: MonadIO m => Path b Dir -> m () Source #
removes an existing directory removeDirRecur
dirdir
together
with its contents and sub-directories. Within this directory, symbolic
links are removed without affecting their targets.
removePathForcibly :: MonadIO m => Path b t -> m () Source #
Remove 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.
Since: 1.7.0
changes the name of an existing directory from
renameDir
old newold
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 removeDir
. 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, renameDir
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
/NoSuchThing
The original directory does not exist, or there is no path to the target.[ENOENT, ENOTDIR]
isPermissionError
/PermissionDenied
The process has insufficient privileges to perform the operation.[EROFS, EACCES, EPERM]
ResourceExhausted
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]
renamePath :: MonadIO m => Path b0 t -> Path b1 t -> m () Source #
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]
Since: 1.7.0
:: MonadIO m | |
=> Path b Dir | Directory to list |
-> m ([Path Abs Dir], [Path Abs File]) | Sub-directories and files |
returns a list of all entries in listDir
dirdir
without the
special entries (.
and ..
). Entries are not sorted.
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
/NoSuchThing
The directory does not exist.[ENOENT, ENOTDIR]
isPermissionError
/PermissionDenied
The process has insufficient privileges to perform the operation.[EACCES]
ResourceExhausted
Insufficient resources are available to perform the operation.[EMFILE, ENFILE]
InappropriateType
The path refers to an existing non-directory object.[ENOTDIR]
:: MonadIO m | |
=> Path b Dir | Directory to list |
-> m ([Path Rel Dir], [Path Rel File]) | Sub-directories and files |
The same as listDir
but returns relative paths.
Since: 1.4.0
:: MonadIO m | |
=> Path b Dir | Directory to list |
-> m ([Path Rel Dir], [Path Rel File]) | Sub-directories and files |
The same as listDirRecur
but returns paths that are relative to the
given directory.
Since: 1.4.2
Copies a directory recursively. It does not follow symbolic links and preserves permissions when possible. If the destination directory already exists, new files and sub-directories complement its structure, possibly overwriting old files if they happen to have the same name as the new ones.
Note: before version 1.3.0, this function followed symlinks.
Note: before version 1.6.0, the function created empty directories
in the destination directory when the source directory contained
directory symlinks. The symlinked directories were not recursively
traversed. It also copied symlinked files creating normal regular files
in the target directory as the result. This was fixed in the version
1.6.0 so that the function now behaves much like the cp
utility, not
traversing symlinked directories, but recreating symlinks in the target
directory according to their targets in the source directory.
The same as copyDirRecur
, but it does not preserve directory
permissions. This may be useful, for example, if the directory you want
to copy is “read-only”, but you want your copy to be editable.
Note: before version 1.3.0, this function followed symlinks.
Note: before version 1.6.0, the function created empty directories
in the destination directory when the source directory contained
directory symlinks. The symlinked directories were not recursively
traversed. It also copied symlinked files creating normal regular files
in the target directory as the result. This was fixed in the version
1.6.0 so that the function now behaves much like the cp
utility, not
traversing symlinked directories, but recreating symlinks in the target
directory according to their targets in the source directory.
Since: 1.1.0
Walking directory trees
data WalkAction b Source #
Action returned by the traversal handler function. The action controls how the traversal will proceed.
Note: in version 1.4.0 the type was adjusted to have the b
type
parameter.
Since: 1.2.0
WalkFinish | Finish the entire walk altogether |
WalkExclude [Path b Dir] | List of sub-directories to exclude from descending |
Instances
Show (WalkAction b) Source # | |
Defined in Path.IO showsPrec :: Int -> WalkAction b -> ShowS # show :: WalkAction b -> String # showList :: [WalkAction b] -> ShowS # | |
Eq (WalkAction b) Source # | |
Defined in Path.IO (==) :: WalkAction b -> WalkAction b -> Bool # (/=) :: WalkAction b -> WalkAction b -> Bool # |
:: MonadIO m | |
=> (Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs)) | Handler ( |
-> Path b Dir | Directory where traversal begins |
-> m () |
Traverse a directory tree using depth first pre-order traversal, calling a handler function at each directory node traversed. The absolute paths of the parent directory, sub-directories and the files in the directory are provided as arguments to the handler.
The function is capable of detecting and avoiding traversal loops in the directory tree. Note that the traversal follows symlinks by default, an appropriate traversal handler can be used to avoid that when necessary.
Since: 1.2.0
:: MonadIO m | |
=> (Path Rel Dir -> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel)) | Handler ( |
-> Path b Dir | Directory where traversal begins |
-> m () |
The same as walkDir
but uses relative paths. The handler is given
dir
, directory relative to the directory where traversal begins.
Sub-directories and files are relative to dir
.
Since: 1.4.2
:: (MonadIO m, Monoid o) | |
=> Maybe (Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m (WalkAction Abs)) | Descend handler ( |
-> (Path Abs Dir -> [Path Abs Dir] -> [Path Abs File] -> m o) | Output writer ( |
-> Path b Dir | Directory where traversal begins |
-> m o | Accumulation of outputs generated by the output writer invocations |
Similar to walkDir
but accepts a Monoid
-returning output writer as
well. Values returned by the output writer invocations are accumulated
and returned.
Both, the descend handler as well as the output writer can be used for side effects but keep in mind that the output writer runs before the descend handler.
Since: 1.2.0
:: (MonadIO m, Monoid o) | |
=> Maybe (Path Rel Dir -> [Path Rel Dir] -> [Path Rel File] -> m (WalkAction Rel)) | Descend handler ( |
-> (Path Rel Dir -> [Path Rel Dir] -> [Path Rel File] -> m o) | Output writer ( |
-> Path b Dir | Directory where traversal begins |
-> m o | Accumulation of outputs generated by the output writer invocations |
The same as walkDirAccum
but uses relative paths. The handler and
writer are given dir
, directory relative to the directory where
traversal begins. Sub-directories and files are relative to dir
.
Since: 1.4.2
Current working directory
getCurrentDir :: MonadIO m => m (Path Abs Dir) Source #
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
).
The operation may fail with:
HardwareFault
A physical I/O error has occurred.[EIO]
isDoesNotExistError
orNoSuchThing
There is no path referring to the working directory.[EPERM, ENOENT, ESTALE...]
isPermissionError
orPermissionDenied
The process has insufficient privileges to perform the operation.[EACCES]
ResourceExhausted
Insufficient resources are available to perform the operation.UnsupportedOperation
The operating system has no notion of current working directory.
setCurrentDir :: MonadIO m => Path b Dir -> m () Source #
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
orNoSuchThing
The directory does not exist.[ENOENT, ENOTDIR]
isPermissionError
orPermissionDenied
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]
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 getCurrentDir
and
setCurrentDir
.
Pre-defined directories
getHomeDir :: MonadIO m => m (Path Abs Dir) Source #
Return 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 getAppUserDataDir
instead.
On Unix, getHomeDir
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>
.
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.
Obtain the path to a special directory for storing user-specific application data (traditional Unix location).
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.
getUserDocsDir :: MonadIO m => m (Path Abs Dir) Source #
Return 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 getAppUserDataDir
instead.
On Unix, getUserDocsDir
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.
getTempDir :: MonadIO m => m (Path Abs Dir) Source #
Return the current directory for temporary files.
On Unix, getTempDir
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.
data XdgDirectory #
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.
Since: directory-1.2.3.0
XdgData | For data files (e.g. images).
It uses the |
XdgConfig | For configuration files.
It uses the |
XdgCache | For non-essential files (e.g. cache).
It uses the |
Instances
:: MonadIO m | |
=> XdgDirectory | Which special directory |
-> Maybe (Path Rel Dir) | A relative path that is appended to the path; if |
-> m (Path Abs Dir) |
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 getAppUserDataDir
, this function provides a more
fine-grained hierarchy as well as greater flexibility for the user.
It also works on Windows, although in that case XdgData
and
XdgConfig
will map to the same directory.
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).
Note also: this is a piece of conditional API, only available if
directory-1.2.3.0
or later is used.
Since: 1.2.1
data XdgDirectoryList #
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.
Since: directory-1.3.2.0
XdgDataDirs | For data files (e.g. images).
It uses the |
XdgConfigDirs | For configuration files.
It uses the |
Instances
:: MonadIO m | |
=> XdgDirectoryList | Which special directory list |
-> m [Path Abs Dir] |
Similar to getXdgDir
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.
Since: 1.5.0
Path transformation
class AnyPath path where Source #
Class of things (Path
s) that can be canonicalized, made absolute, and
made relative to a some base directory.
type AbsPath path :: Type Source #
Type of absolute version of the given path
.
type RelPath path :: Type Source #
Type of relative version of the given path
.
canonicalizePath :: MonadIO m => path -> m (AbsPath path) Source #
Make a path absolute and remove as many indirections from it as
possible. Indirections include the two special directories .
and
..
, as well as any symbolic links. The input path need not point to
an existing file or directory.
Note: if you require only an absolute path, use makeAbsolute
instead. Most programs need not care about whether a path contains
symbolic links.
Due to the fact that symbolic links are dependent on the state of the existing filesystem, the function can only make a conservative, best-effort attempt. Nevertheless, if the input path points to an existing file or directory, then the output path shall also point to the same file or directory.
Formally, symbolic links are removed from the longest prefix of the path that still points to an existing file. The function is not atomic, therefore concurrent changes in the filesystem may lead to incorrect results.
(Despite the name, the function does not guarantee canonicity of the returned path due to the presence of hard links, mount points, etc.)
Known bug(s): on Windows, the function does not resolve symbolic links.
Please note that before version 1.2.3.0 of the directory
package,
this function had unpredictable behavior on non-existent paths.
makeAbsolute :: MonadIO m => path -> m (AbsPath path) Source #
Make a path absolute by prepending the current directory (if it isn't
already absolute) and applying normalise
to the result.
If the path is already absolute, the operation never fails. Otherwise,
the operation may fail with the same exceptions as getCurrentDir
.
:: MonadThrow m | |
=> Path Abs Dir | Base directory |
-> path | Path that will be made relative to base directory |
-> m (RelPath path) |
Make a path relative to a given directory.
Since: 0.3.0
makeRelativeToCurrentDir :: MonadIO m => path -> m (RelPath path) Source #
Make a path relative to current working directory.
Since: 0.3.0
Instances
Append stringly-typed path to an absolute path and then canonicalize it.
Since: 0.3.0
The same as resolveFile
, but uses current working directory.
Since: 0.3.0
The same as resolveFile
, but for directories.
Since: 0.3.0
The same as resolveDir
, but uses current working directory.
Since: 0.3.0
Actions on files
removeFile :: MonadIO m => Path b File -> m () Source #
removes the directory entry for an existing file
removeFile
filefile
, 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
/NoSuchThing
The file does not exist.[ENOENT, ENOTDIR]
isPermissionError
/PermissionDenied
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]
changes the name of an existing file system
object from old to new. If the new object already exists, it is
atomically 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.renameFile
old new
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
/NoSuchThing
The original file does not exist, or there is no path to the target.[ENOENT, ENOTDIR]
isPermissionError
/PermissionDenied
The process has insufficient privileges to perform the operation.[EROFS, EACCES, EPERM]
ResourceExhausted
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]
copies the existing file from copyFile
old newold
to new
. If
the new
file already exists, it is atomically replaced by the old
file. Neither path may refer to an existing directory. The permissions of
old
are copied to new
, if possible.
getFileSize :: MonadIO m => Path b File -> m Integer Source #
Obtain the size of a file in bytes.
Since: 1.7.0
:: MonadIO m | |
=> Path Rel File | Executable file name |
-> m (Maybe (Path Abs File)) | Path to found executable |
Given an executable file name, search for such file in the directories
listed in system PATH
. The returned value is the path to the found
executable or Nothing
if an executable with the given name was not
found. For example (findExecutable
"ghc") gives you the path to GHC.
The path returned by findExecutable
corresponds to the program that
would be executed by createProcess
when passed the same
string (as a RawCommand, not a ShellCommand).
On Windows, findExecutable
calls the Win32 function SearchPath
, which
may search other places before checking the directories in PATH
. Where
it actually searches depends on registry settings, but notably includes
the directory containing the current executable. See
http://msdn.microsoft.com/en-us/library/aa365527.aspx for more details.
:: MonadIO m | |
=> [Path b Dir] | Set of directories to search in |
-> Path Rel File | Filename of interest |
-> m (Maybe (Path Abs File)) | Absolute path to file (if found) |
Search through the given set of directories for the given file.
:: MonadIO m | |
=> [Path b Dir] | Set of directories to search in |
-> Path Rel File | Filename of interest |
-> m [Path Abs File] | Absolute paths to all found files |
Search through the given set of directories for the given file and return a list of paths where the given file exists.
:: MonadIO m | |
=> (Path Abs File -> m Bool) | How to test the files |
-> [Path b Dir] | Set of directories to search in |
-> Path Rel File | Filename of interest |
-> m [Path Abs File] | Absolute paths to all found files |
Search through the given set of directories for the given file and with the given property (usually permissions) and return a list of paths where the given file exists and has the property.
Symbolic links
:: MonadIO m | |
=> Path b0 File | Path to the target file |
-> Path b1 File | Path to the link to be created |
-> m () |
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.
Since: 1.5.0
:: MonadIO m | |
=> Path b0 Dir | Path to the target directory |
-> Path b1 Dir | Path to the link to be created |
-> m () |
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 removeDirLink
.
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.
Since: 1.5.0
Remove an existing directory symbolic link.
On Windows, this is an alias for removeDir
. On POSIX systems, this is
an alias for removeFile
.
See also: removeFile
, which can remove an existing file symbolic link.
Since: 1.5.0
Retrieve the target path of either a file or directory symbolic link. The returned path 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.
Since: 1.5.0
isSymlink :: MonadIO m => Path b t -> m Bool Source #
Check whether the path refers to a symbolic link. An exception is thrown if the path does not exist or is inaccessible.
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
.
Check if the given path is a symbolic link.
Since: 1.3.0
Temporary files and directories
:: (MonadIO m, MonadMask m) | |
=> Path b Dir | Directory to create the file in |
-> String | File name template, see |
-> (Path Abs File -> Handle -> m a) | Callback that can use the file |
-> m a |
Use a temporary file that doesn't already exist.
Creates a new temporary file inside the given directory, making use of the template. The temporary file is deleted after use.
Since: 0.2.0
:: (MonadIO m, MonadMask m) | |
=> Path b Dir | Directory to create the file in |
-> String | Directory name template, see |
-> (Path Abs Dir -> m a) | Callback that can use the directory |
-> m a |
Create and use a temporary directory.
Creates a new temporary directory inside the given directory, making use of the template. The temporary directory is deleted after use.
Since: 0.2.0
:: (MonadIO m, MonadMask m) | |
=> String | File name template, see |
-> (Path Abs File -> Handle -> m a) | Callback that can use the file |
-> m a |
Create and use a temporary file in the system standard temporary directory.
Behaves exactly the same as withTempFile
, except that the parent
temporary directory will be that returned by getTempDir
.
Since: 0.2.0
:: (MonadIO m, MonadMask m) | |
=> String | Directory name template, see |
-> (Path Abs Dir -> m a) | Callback that can use the directory |
-> m a |
Create and use a temporary directory in the system standard temporary directory.
Behaves exactly the same as withTempDir
, except that the parent
temporary directory will be that returned by getTempDir
.
Since: 0.2.0
:: MonadIO m | |
=> Path b Dir | Directory to create file in |
-> String | File name template; if the template is "foo.ext" then the created
file will be |
-> m (Path Abs File, Handle) | Name of created file and its |
The function creates a temporary file in rw
mode. The created file
isn't deleted automatically, so you need to delete it manually.
The file is created with permissions such that only the current user can read/write it.
With some exceptions (see below), the file will be created securely in
the sense that an attacker should not be able to cause openTempFile to
overwrite another file on the filesystem using your credentials, by
putting symbolic links (on Unix) in the place where the temporary file is
to be created. On Unix the O_CREAT
and O_EXCL
flags are used to
prevent this attack, but note that O_EXCL
is sometimes not supported on
NFS filesystems, so if you rely on this behaviour it is best to use local
filesystems only.
Since: 0.2.0
:: MonadIO m | |
=> Path b Dir | Directory to create file in |
-> String | File name template, see |
-> m (Path Abs File, Handle) | Name of created file and its |
Like openTempFile
, but opens the file in binary mode. On Windows,
reading a file in text mode (which is the default) will translate CRLF
to LF
, and writing will translate LF
to CRLF
. This is usually what
you want with text files. With binary files this is undesirable; also, as
usual under Microsoft operating systems, text mode treats control-Z as
EOF. Binary mode turns off all special treatment of end-of-line and
end-of-file characters.
Since: 0.2.0
:: MonadIO m | |
=> Path b Dir | Directory to create file in |
-> String | Directory name template, see |
-> m (Path Abs Dir) | Name of created temporary directory |
Create a temporary directory. The created directory isn't deleted automatically, so you need to delete it manually.
The directory is created with permissions such that only the current user can read/write it.
Since: 0.2.0
Existence tests
doesPathExist :: MonadIO m => Path b t -> m Bool Source #
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.
Since: 1.7.0
doesFileExist :: MonadIO m => Path b File -> m Bool Source #
The operation doesFileExist
returns True
if the argument file
exists and is not a directory, and False
otherwise.
doesDirExist :: MonadIO m => Path b Dir -> m Bool Source #
The operation doesDirExist
returns True
if the argument file exists
and is either a directory or a symbolic link to a directory, and False
otherwise.
isLocationOccupied :: MonadIO m => Path b t -> m Bool Source #
Check if there is a file or directory on specified path.
forgivingAbsence :: (MonadIO m, MonadCatch m) => m a -> m (Maybe a) Source #
If argument of the function throws a
doesNotExistErrorType
, Nothing
is returned (other
exceptions propagate). Otherwise the result is returned inside a Just
.
Since: 0.3.0
ignoringAbsence :: (MonadIO m, MonadCatch m) => m a -> m () Source #
The same as forgivingAbsence
, but ignores result.
Since: 0.3.1
Permissions
data Permissions #
Instances
Read Permissions | |
Defined in System.Directory.Internal.Common readsPrec :: Int -> ReadS Permissions # readList :: ReadS [Permissions] # readPrec :: ReadPrec Permissions # readListPrec :: ReadPrec [Permissions] # | |
Show Permissions | |
Defined in System.Directory.Internal.Common showsPrec :: Int -> Permissions -> ShowS # show :: Permissions -> String # showList :: [Permissions] -> ShowS # | |
Eq Permissions | |
Defined in System.Directory.Internal.Common (==) :: Permissions -> Permissions -> Bool # (/=) :: Permissions -> Permissions -> Bool # | |
Ord Permissions | |
Defined in System.Directory.Internal.Common compare :: Permissions -> Permissions -> Ordering # (<) :: Permissions -> Permissions -> Bool # (<=) :: Permissions -> Permissions -> Bool # (>) :: Permissions -> Permissions -> Bool # (>=) :: Permissions -> Permissions -> Bool # max :: Permissions -> Permissions -> Permissions # min :: Permissions -> Permissions -> 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 #
getPermissions :: MonadIO m => Path b t -> m Permissions Source #
The getPermissions
operation returns the permissions for the file or
directory.
The operation may fail with:
isPermissionError
if the user is not permitted to access the permissions; orisDoesNotExistError
if the file or directory does not exist.
setPermissions :: MonadIO m => Path b t -> Permissions -> m () Source #
The setPermissions
operation sets the permissions for the file or
directory.
The operation may fail with:
isPermissionError
if the user is not permitted to set the permissions; orisDoesNotExistError
if the file or directory does not exist.
Set permissions for the object found on second given path so they match permissions of the object on the first path.
Timestamps
getAccessTime :: MonadIO m => Path b t -> m UTCTime Source #
Obtain the time at which the file or directory was last accessed.
The operation may fail with:
isPermissionError
if the user is not permitted to read the access time; orisDoesNotExistError
if the file or directory does not exist.
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.
Note: this is a piece of conditional API, only available if
directory-1.2.3.0
or later is used.
setAccessTime :: MonadIO m => Path b t -> UTCTime -> m () Source #
Change the time at which the file or directory was last accessed.
The operation may fail with:
isPermissionError
if the user is not permitted to alter the access time; orisDoesNotExistError
if the file or directory does not exist.
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 whereutimensat
is supported, the access time is set atomically with nanosecond precision. - If compiled against a version of
unix
prior to2.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.
Note: this is a piece of conditional API, only available if
directory-1.2.3.0
or later is used.
setModificationTime :: MonadIO m => Path b t -> UTCTime -> m () Source #
Change the time at which the file or directory was last modified.
The operation may fail with:
isPermissionError
if the user is not permitted to alter the modification time; orisDoesNotExistError
if the file or directory does not exist.
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 whereutimensat
is supported, the modification time is set atomically with nanosecond precision. - If compiled against a version of
unix
prior to2.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.
Note: this is a piece of conditional API, only available if
directory-1.2.3.0
or later is used.
getModificationTime :: MonadIO m => Path b t -> m UTCTime Source #
Obtain the time at which the file or directory was last modified.
The operation may fail with:
isPermissionError
if the user is not permitted to read the modification time; orisDoesNotExistError
if the file or directory does not exist.
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.