read
, write
, append
, execute
,
search
, exist
, or none
. Fails
silently otherwise.
File may also be the name of a directory.
access_file(File, none)
simply succeeds without testing
anything.
If Mode is write
or append
, this
predicate also succeeds if the file does not exist and the user has
write access to the directory of the specified location.
The mode execute
is only intended for use with regular
files and the mode search
only with directories. However,
the two modes are currently equivalent and both can be used with either
files or directories. This may change in the future, so the results of
checking execute
access on directories or search
access on regular files should not be relied on.
The behaviour is backed up by the POSIX access() API. The Windows replacement (_waccess()) returns incorrect results because it does not consider ACLs (Access Control Lists). The Prolog flag win_file_access_check may be used to control the level of checking performed by Prolog. Please note that checking access never provides a guarantee that a subsequent open succeeds without errors due to inherent concurrency in file operations. It is generally more robust to try and open the file and handle possible exceptions. See open/4 and catch/3.
/*[^/]*/*$
. If
the result is empty it binds Directory to /
if the first character of File is /
and .
otherwise. The behaviour is consistent
with the POSIX dirname program.150Before
SWI-Prolog 7.7.13 trailing /
where not
removed, translation /a/b/
into /a/b
. Volker
Wysk pointed at this incorrect behaviour.
See also directory_file_path/3
from library(filesex)
. The system ensures that for every
valid Path using the Prolog (POSIX) directory separators,
following is true on systems with a sound implementation of
same_file/2.151On
some systems, Path and Path2 refer to the same
entry in the file system, but same_file/2
may fail. See also prolog_to_os_filename/2.
..., file_directory_name(Path, Dir), file_base_name(Path, File), directory_file_path(Dir, File, Path2), same_file(Path, Path2).
/*([^/]*)/*$
, now capturing the non-/
segment. If the segment is empty it unifies File with /
if Path starts with /
and the empty
atom (''
) otherwise. The behaviour is consistent with the
POSIX basename program.152Before
SWI-Prolog 7.7.13, if argPath ended with a /
File
was unified with the empty atom.st_dev
and st_inode
, same_file/2
is implemented by comparing the device and inode identifiers. On
Windows,
same_file/2
compares the strings returned by the GetFullPathName() system call..
, ..
and
repeated directory separators (/
) are deleted.
This predicate ensures that expanding a filename returns the same
absolute path regardless of how the file is addressed. Notably, if a
file appears in multiple directories due to symbolic or hard links absolute_file_name/2
returns the same absolute filename. SWI-Prolog uses absolute filenames
to register source files independent of the current working directory.
This predicate has a different history than absolute_file_name/3 and should primarily be used to get an absolute canonical name from a relative name. If File is a term Alias(Relative) is behaviour is defined as below, i.e., if an accessible file can be found using the provided search path this is returned. Otherwise it returns the the expansion of the alias path.153The SICStus implementation behaves as absolute_file_name/3 with an empty option list. Users are advised to use absolute_file_name/3 with appropriate options for resolving an Alias(Relative) term.
absolute_file_name(Spec, AbsFile) :- absolute_file_name(Spec, File, [access(read), file_errors(fail)]), !, AbsFile = File. absolute_file_name(Spec, AbsFile) :- absolute_file_name(Spec, AbsFile, []).
See also absolute_file_name/3, file_search_path/2, and expand_file_name/2.
(library(lists)
), a
relative filename or an absolute filename. The primary intention of this
predicate is to resolve files specified as Alias(Relative), which use
file_search_path/2
to look up the possibilities for Alias. This predicate only returns
non-directories, unless the option
file_type(directory)
is specified or the requested access
is none
. Supported Options are:
.ext
or
plain ext
.read
, write
, append
, execute
,
search
, exist
or none
. See also access_file/2.
The default is none
which, if file_type
is not
specified as directory
or regular
, returns
absolute file names that result from expanding aliases without
inspecting the actual file system.txt
implies ['']
,
prolog
implies ['.pl',’’]
, executable
implies
['.so',’’]
and qlf
implies ['.qlf',’’]
.
The
Type directory
implies ['']
and
causes this predicate to generate (only) directories. The Type regular
is the opposite of directory
and is the default if no file
type is specified and the effective access mode is none
.
The file type source
is an alias for prolog
for compatibility with SICStus Prolog. See also prolog_file_type/2.
error
(default), throw an existence_error
exception if the file cannot be found. If fail
, stay
silent.154Silent operation was the
default up to version 3.2.6.first
(default), the predicate leaves no choice point.
Otherwise a choice point will be left and backtracking may yield more
solutions.true
(default is false
) and Spec
is atomic, call expand_file_name/2
followed by member/2
on Spec before proceeding. This is a SWI-Prolog extension
intended to minimise porting effort after SWI-Prolog stopped expanding
environment variables and the ~
by default.
This option should be considered deprecated. In particular the use of wildcard
patterns such as *
should be avoided.
The Prolog flag verbose_file_search
can be set to true
to help debugging Prolog's search for
files. See also file_search_path/2.
This predicate is derived from Quintus Prolog. In Quintus Prolog, the
argument order was absolute_file_name(+Spec, +Options, -Path)
.
The argument order has been changed for compatibility with ISO and
SICStus. The Quintus argument order is still accepted.
<letter>:
.
This predicate is intended to provide platform-independent checking for
absolute paths. See also absolute_file_name/2
and prolog_to_os_filename/2..
).
If an Extension is generated, it will not have a leading dot..
and
..
. See also expand_file_name/2.155This
predicate should be considered a misnomer because it returns entries
rather than files. We stick to this name for compatibility with, e.g.,
SICStus, Ciao and YAP.?
’,‘*
’,‘[
... ]
’and‘{...}
’are recognised.
The interpretation of‘{...}
’is slightly
different from the C shell (csh(1)). The comma-separated argument can be
arbitrary patterns, including‘{...}
’patterns.
The empty pattern is legal as well:‘{.pl,}
’matches
either‘.pl
’or the empty string.
If the pattern contains wildcard characters, only existing files and directories are returned. Expanding a‘pattern' without wildcard characters returns the argument, regardless of whether or not it exists.
Before expanding wildcards, the construct $\arg{var}
is
expanded to the value of the environment variable var, and a
possible leading ~
character is expanded to the user's home
directory.156On Windows, the home
directory is determined as follows: if the environment variable HOME
exists, this is used. If the variables HOMEDRIVE
and HOMEPATH
exist (Windows-NT), these are used. At initialisation, the system will
set the environment variable HOME
to point to the
SWI-Prolog home directory if neither HOME
nor HOMEPATH
and HOMEDRIVE
are defined.
\
into /
.Because it is possible to guess the generated filename, attackers may create the filesystem entry as a link and possibly create a security issue. New code should use tmp_file_stream/3.
O_EXCL
, which guarantees that
the file did not exist before this call. The following options are
processed:
binary
opens the file in binary mode.
This predicate is a safe replacement of tmp_file/2. Note that in those cases where the temporary file is needed to store output from an external command, the file must be closed first. E.g., the following downloads a file from a URL to a temporary file and opens the file for reading (on Unix systems you can delete the file for cleanup after opening it for reading):
open_url(URL, In) :- tmp_file_stream(text, File, Stream), close(Stream), process_create(curl, ['-o', File, URL], []), open(File, read, In), delete_file(File). % Unix-only
Temporary files created using this call are removed if the Prolog process terminates gracefully. Calling delete_file/1 using FileName removes the file and removes the entry from the administration of files-to-be-deleted.
working_directory(CWD, CWD)
to get the current directory.
See also absolute_file_name/2
and chdir/1.bugSome
of the file I/O predicates use local filenames. Changing directory while
file-bound streams are open causes wrong results on telling/1, seeing/1
and current_stream/3.
Note that the working directory is shared between all threads.