View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2002-2023, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    9                              SWI-Prolog Solutions b.v.
   10    All rights reserved.
   11
   12    Redistribution and use in source and binary forms, with or without
   13    modification, are permitted provided that the following conditions
   14    are met:
   15
   16    1. Redistributions of source code must retain the above copyright
   17       notice, this list of conditions and the following disclaimer.
   18
   19    2. Redistributions in binary form must reproduce the above copyright
   20       notice, this list of conditions and the following disclaimer in
   21       the documentation and/or other materials provided with the
   22       distribution.
   23
   24    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   25    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   26    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   27    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   28    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   29    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   30    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   31    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   32    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   33    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   34    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   35    POSSIBILITY OF SUCH DAMAGE.
   36*/
   37
   38:- module(files_ex,
   39          [ set_time_file/3,            % +File, -OldTimes, +NewTimes
   40            link_file/3,                % +OldPath, +NewPath, +Type
   41            chmod/2,                    % +File, +Mode
   42            relative_file_name/3,       % ?AbsPath, +RelTo, ?RelPath
   43            directory_file_path/3,      % +Dir, +File, -Path
   44            directory_member/3,		% +Dir, -Member, +Options
   45            copy_file/2,                % +From, +To
   46            make_directory_path/1,      % +Directory
   47            ensure_directory/1,         % +Directory
   48            copy_directory/2,           % +Source, +Destination
   49            delete_directory_and_contents/1, % +Dir
   50            delete_directory_contents/1 % +Dir
   51          ]).   52:- autoload(library(apply), [maplist/2, maplist/3, foldl/4]).   53:- autoload(library(error),
   54            [ permission_error/3,
   55              must_be/2,
   56              domain_error/2,
   57              instantiation_error/1
   58            ]).   59:- autoload(library(lists), [member/2]).   60:- autoload(library(nb_set), [empty_nb_set/1, add_nb_set/3]).   61:- autoload(library(option), [dict_options/2]).

Extended operations on files

This module provides additional operations on files. This covers both more obscure and possible non-portable low-level operations and high-level utilities.

Using these Prolog primitives is typically to be preferred over using operating system primitives through shell/1 or process_create/3 because (1) there are no potential file name quoting issues, (2) there is no dependency on operating system commands and (3) using the implementations from this library is usually faster. */

   77:- predicate_options(directory_member/3, 3,
   78                     [ recursive(boolean),
   79                       follow_links(boolean),
   80                       file_type(atom),
   81                       extensions(list(atom)),
   82                       file_errors(oneof([fail,warning,error])),
   83                       access(oneof([read,write,execute])),
   84                       matches(text),
   85                       exclude(text),
   86                       exclude_directory(text),
   87                       hidden(boolean)
   88                     ]).   89
   90
   91:- use_foreign_library(foreign(files)).
 set_time_file(+File, -OldTimes, +NewTimes) is det
Query and set POSIX time attributes of a file. Both OldTimes and NewTimes are lists of option-terms. Times are represented in SWI-Prolog's standard floating point numbers. New times may be specified as now to indicate the current time. Defined options are:
access(Time)
Describes the time of last access of the file. This value can be read and written.
modified(Time)
Describes the time the contents of the file was last modified. This value can be read and written.
changed(Time)
Describes the time the file-structure itself was changed by adding (link()) or removing (unlink()) names.

Below are some example queries. The first retrieves the access-time, while the second sets the last-modified time to the current time.

?- set_time_file(foo, [access(Access)], []).
?- set_time_file(foo, [], [modified(now)]).
 link_file(+OldPath, +NewPath, +Type) is det
Create a link in the filesystem from NewPath to OldPath. Type defines the type of link and is one of hard or symbolic.

With some limitations, these functions also work on Windows. First of all, the underlying filesystem must support links. This requires NTFS. Second, symbolic links are only supported in Vista and later.

Errors
- domain_error(link_type, Type) if the requested link-type is unknown or not supported on the target OS.
 relative_file_name(+Path:atom, +RelToFile:atom, -RelPath:atom) is det
relative_file_name(-Path:atom, +RelToFile:atom, +RelPath:atom) is det
True when RelPath is Path, relative to the file RelToFile. Path and RelTo are first handed to absolute_file_name/2, which makes the absolute and canonical. Below are two examples:
?- relative_file_name('/home/janw/nice',
                      '/home/janw/deep/dir/file', Path).
Path = '../../nice'.

?- relative_file_name(Path, '/home/janw/deep/dir/file', '../../nice').
Path = '/home/janw/nice'.

Add a terminating / to get a path relative to a directory, e.g.

?- relative_file_name('/home/janw/deep/dir/file', './', Path).
Path = 'deep/dir/file'.
Arguments:
All- paths must be in canonical POSIX notation, i.e., using / to separate segments in the path. See prolog_to_os_filename/2.
bug
- It would probably have been cleaner to use a directory as second argument. We can not do such dynamically as this predicate is defined as a syntactical operation, which implies it may be used for non-existing paths and URLs.
  163relative_file_name(Path, RelTo, RelPath) :- % +,+,-
  164    nonvar(Path),
  165    !,
  166    absolute_file_name(Path, AbsPath),
  167    absolute_file_name(RelTo, AbsRelTo),
  168    atomic_list_concat(PL, /, AbsPath),
  169    atomic_list_concat(RL, /, AbsRelTo),
  170    delete_common_prefix(PL, RL, PL1, PL2),
  171    to_dot_dot(PL2, DotDot, PL1),
  172    (   DotDot == []
  173    ->  RelPath = '.'
  174    ;   atomic_list_concat(DotDot, /, RelPath)
  175    ).
  176relative_file_name(Path, RelTo, RelPath) :-
  177    (   is_absolute_file_name(RelPath)
  178    ->  Path = RelPath
  179    ;   file_directory_name(RelTo, RelToDir),
  180        directory_file_path(RelToDir, RelPath, Path0),
  181        absolute_file_name(Path0, Path)
  182    ).
  183
  184delete_common_prefix([H|T01], [H|T02], T1, T2) :-
  185    !,
  186    delete_common_prefix(T01, T02, T1, T2).
  187delete_common_prefix(T1, T2, T1, T2).
  188
  189to_dot_dot([], Tail, Tail).
  190to_dot_dot([_], Tail, Tail) :- !.
  191to_dot_dot([_|T0], ['..'|T], Tail) :-
  192    to_dot_dot(T0, T, Tail).
 directory_file_path(+Directory, +File, -Path) is det
directory_file_path(?Directory, ?File, +Path) is det
True when Path is the full path-name for File in Dir. This is comparable to atom_concat(Directory, File, Path), but it ensures there is exactly one / between the two parts. Notes:
  206directory_file_path(Dir, File, Path) :-
  207    nonvar(Dir), nonvar(File),
  208    !,
  209    (   (   is_absolute_file_name(File)
  210        ;   Dir == '.'
  211        ;   Dir == ''
  212        )
  213    ->  Path = File
  214    ;   sub_atom(Dir, _, _, 0, /)
  215    ->  atom_concat(Dir, File, Path)
  216    ;   atomic_list_concat([Dir, /, File], Path)
  217    ).
  218directory_file_path(Dir, File, Path) :-
  219    nonvar(Path),
  220    !,
  221    (   nonvar(Dir)
  222    ->  (   (   Dir == '.'
  223            ->  true
  224            ;   Dir == ''
  225            ),
  226            \+ is_absolute_file_name(Path)
  227        ->  File = Path
  228        ;   sub_atom(Dir, _, _, 0, /)
  229        ->  atom_concat(Dir, File, Path)
  230        ;   atom_concat(Dir, /, TheDir)
  231        ->  atom_concat(TheDir, File, Path)
  232        )
  233    ;   nonvar(File)
  234    ->  atom_concat(Dir0, File, Path),
  235        strip_trailing_slash(Dir0, Dir)
  236    ;   file_directory_name(Path, Dir),
  237        file_base_name(Path, File)
  238    ).
  239directory_file_path(Dir, _, _) :-
  240    instantiation_error(Dir).
  241
  242strip_trailing_slash(Dir0, Dir) :-
  243    (   atom_concat(D, /, Dir0),
  244        D \== ''
  245    ->  Dir = D
  246    ;   Dir = Dir0
  247    ).
 directory_member(+Directory, -Member, +Options) is nondet
True when Member is a path inside Directory. Options defined are:
recursive(+Boolean)
If true (default false), recurse into subdirectories
follow_links(+Boolean)
If true (default), follow symbolic links.
file_type(+Type)
See absolute_file_name/3.
extensions(+List)
Only return entries whose extension appears in List.
file_errors(+Errors)
How to handle errors. One of fail, warning or error. Default is warning. Errors notably happen if a directory is unreadable or a link points nowhere.
access(+Access)
Only return entries with Access
matches(+GlobPattern)
Only return files that match GlobPattern.
exclude(+GlobPattern)
Exclude files matching GlobPattern.
exclude_directory(+GlobPattern)
Do not recurse into directories matching GlobPattern.
hidden(+Boolean)
If true (default), also return hidden files.

This predicate is safe against cycles introduced by symbolic links to directories.

The idea for a non-deterministic file search predicate comes from Nicos Angelopoulos.

  283directory_member(Directory, Member, Options) :-
  284    dict_options(Dict, Options),
  285    (   Dict.get(recursive) == true,
  286        \+ Dict.get(follow_links) == false
  287    ->  empty_nb_set(Visited),
  288        DictOptions = Dict.put(visited, Visited)
  289    ;   DictOptions = Dict
  290    ),
  291    directory_member_dict(Directory, Member, DictOptions).
  292
  293directory_member_dict(Directory, Member, Dict) :-
  294    directory_files(Directory, Files, Dict),
  295    member(Entry, Files),
  296    \+ special(Entry),
  297    directory_file_path(Directory, Entry, AbsEntry),
  298    filter_link(AbsEntry, Dict),
  299    (   exists_directory(AbsEntry)
  300    ->  (   filter_dir_member(AbsEntry, Entry, Dict),
  301            Member = AbsEntry
  302        ;   filter_directory(Entry, Dict),
  303            Dict.get(recursive) == true,
  304            \+ hidden_file(Entry, Dict),
  305            no_link_cycle(AbsEntry, Dict),
  306            directory_member_dict(AbsEntry, Member, Dict)
  307        )
  308    ;   filter_dir_member(AbsEntry, Entry, Dict),
  309        Member = AbsEntry
  310    ).
  311
  312directory_files(Directory, Files, Dict) :-
  313    Errors = Dict.get(file_errors),
  314    !,
  315    errors_directory_files(Errors, Directory, Files).
  316directory_files(Directory, Files, _Dict) :-
  317    errors_directory_files(warning, Directory, Files).
  318
  319errors_directory_files(fail, Directory, Files) :-
  320    catch(directory_files(Directory, Files), _, fail).
  321errors_directory_files(warning, Directory, Files) :-
  322    catch(directory_files(Directory, Files), E,
  323          (   print_message(warning, E),
  324              fail)).
  325errors_directory_files(error, Directory, Files) :-
  326    directory_files(Directory, Files).
  327
  328
  329filter_link(File, Dict) :-
  330    \+ ( Dict.get(follow_links) == false,
  331         read_link(File, _, _)
  332       ).
  333
  334no_link_cycle(Directory, Dict) :-
  335    Visited = Dict.get(visited),
  336    !,
  337    absolute_file_name(Directory, Canonical,
  338                       [ file_type(directory)
  339                       ]),
  340    add_nb_set(Canonical, Visited, true).
  341no_link_cycle(_, _).
  342
  343hidden_file(Entry, Dict) :-
  344    false == Dict.get(hidden),
  345    sub_atom(Entry, 0, _, _, '.').
 filter_dir_member(+Absolute, +BaseName, +Options)
True when the given file satisfies the filter expressions.
  351filter_dir_member(_AbsEntry, Entry, Dict) :-
  352    Exclude = Dict.get(exclude),
  353    wildcard_match(Exclude, Entry),
  354    !, fail.
  355filter_dir_member(_AbsEntry, Entry, Dict) :-
  356    Include = Dict.get(matches),
  357    \+ wildcard_match(Include, Entry),
  358    !, fail.
  359filter_dir_member(AbsEntry, _Entry, Dict) :-
  360    Type = Dict.get(file_type),
  361    \+ matches_type(Type, AbsEntry),
  362    !, fail.
  363filter_dir_member(_AbsEntry, Entry, Dict) :-
  364    ExtList = Dict.get(extensions),
  365    file_name_extension(_, Ext, Entry),
  366    \+ memberchk(Ext, ExtList),
  367    !, fail.
  368filter_dir_member(AbsEntry, _Entry, Dict) :-
  369    Access = Dict.get(access),
  370    \+ access_file(AbsEntry, Access),
  371    !, fail.
  372filter_dir_member(_AbsEntry, Entry, Dict) :-
  373    hidden_file(Entry, Dict),
  374    !, fail.
  375filter_dir_member(_, _, _).
  376
  377matches_type(directory, Entry) :-
  378    !,
  379    exists_directory(Entry).
  380matches_type(regular, Entry) :-
  381    !,
  382    exists_file(Entry).
  383matches_type(Type, Entry) :-
  384    \+ exists_directory(Entry),
  385    user:prolog_file_type(Ext, Type),
  386    file_name_extension(_, Ext, Entry).
 filter_directory(+Entry, +Dict) is semidet
Implement the exclude_directory(+GlobPattern) option.
  393filter_directory(Entry, Dict) :-
  394    Exclude = Dict.get(exclude_directory),
  395    wildcard_match(Exclude, Entry),
  396    !, fail.
  397filter_directory(_, _).
 copy_file(+From, +To) is det
Copy a file into a new file or directory. The data is copied as binary data.
  405copy_file(From, To) :-
  406    destination_file(To, From, Dest),
  407    setup_call_cleanup(
  408        open(Dest, write, Out, [type(binary)]),
  409        copy_from(From, Out),
  410        close(Out)).
  411
  412copy_from(File, Stream) :-
  413    setup_call_cleanup(
  414        open(File, read, In, [type(binary)]),
  415        copy_stream_data(In, Stream),
  416        close(In)).
  417
  418destination_file(Dir, File, Dest) :-
  419    exists_directory(Dir),
  420    !,
  421    file_base_name(File, Base),
  422    directory_file_path(Dir, Base, Dest).
  423destination_file(Dest, _, Dest).
 make_directory_path(+Dir) is det
Create Dir and all required components (like mkdir -p). Can raise various file-specific exceptions.
  431make_directory_path(Dir) :-
  432    make_directory_path_2(Dir),
  433    !.
  434make_directory_path(Dir) :-
  435    permission_error(create, directory, Dir).
  436
  437make_directory_path_2(Dir) :-
  438    exists_directory(Dir),
  439    !.
  440make_directory_path_2(Dir) :-
  441    atom_concat(RealDir, '/', Dir),
  442    RealDir \== '',
  443    !,
  444    make_directory_path_2(RealDir).
  445make_directory_path_2(Dir) :-
  446    Dir \== (/),
  447    !,
  448    file_directory_name(Dir, Parent),
  449    make_directory_path_2(Parent),
  450    ensure_directory_(Dir).
 ensure_directory(+Dir) is det
Ensure the directory Dir exists. Similar to make_directory_path/1, but creates at most one new directory, i.e., the directory or its direct parent must exist.
  458ensure_directory(Dir) :-
  459    exists_directory(Dir),
  460    !.
  461ensure_directory(Dir) :-
  462    atom_concat(RealDir, '/', Dir),
  463    RealDir \== '',
  464    !,
  465    ensure_directory(RealDir).
  466ensure_directory(Dir) :-
  467    ensure_directory_(Dir).
  468
  469ensure_directory_(Dir) :-
  470    E = error(existence_error(directory, _), _),
  471    catch(make_directory(Dir), E,
  472          (   exists_directory(Dir)
  473          ->  true
  474          ;   throw(E)
  475          )).
 copy_directory(+From, +To) is det
Copy the contents of the directory From to To (recursively). If To is the name of an existing directory, the contents of From are copied into To. I.e., no subdirectory using the basename of From is created.
  485copy_directory(From, To) :-
  486    (   exists_directory(To)
  487    ->  true
  488    ;   make_directory(To)
  489    ),
  490    directory_files(From, Entries),
  491    maplist(copy_directory_content(From, To), Entries).
  492
  493copy_directory_content(_From, _To, Special) :-
  494    special(Special),
  495    !.
  496copy_directory_content(From, To, Entry) :-
  497    directory_file_path(From, Entry, Source),
  498    directory_file_path(To, Entry, Dest),
  499    (   exists_directory(Source)
  500    ->  copy_directory(Source, Dest)
  501    ;   copy_file(Source, Dest)
  502    ).
  503
  504special(.).
  505special(..).
 delete_directory_and_contents(+Dir) is det
Recursively remove the directory Dir and its contents. If Dir is a symbolic link or symbolic links inside Dir are encountered, the links are removed rather than their content. Use with care!
  513delete_directory_and_contents(Dir) :-
  514    read_link(Dir, _, _),
  515    !,
  516    delete_file(Dir).
  517delete_directory_and_contents(Dir) :-
  518    directory_files(Dir, Files),
  519    maplist(delete_directory_contents(Dir), Files),
  520    E = error(existence_error(directory, _), _),
  521    catch(delete_directory(Dir), E,
  522          (   \+ exists_directory(Dir)
  523          ->  true
  524          ;   throw(E)
  525          )).
  526
  527delete_directory_contents(_, Entry) :-
  528    special(Entry),
  529    !.
  530delete_directory_contents(Dir, Entry) :-
  531    directory_file_path(Dir, Entry, Delete),
  532    (   exists_directory(Delete)
  533    ->  delete_directory_and_contents(Delete)
  534    ;   E = error(existence_error(file, _), _),
  535        catch(delete_file(Delete), E,
  536              (   \+ exists_file(Delete)
  537              ->  true
  538              ;   throw(E)))
  539    ).
 delete_directory_contents(+Dir) is det
Remove all content from directory Dir, without removing Dir itself. Similar to delete_directory_and_contents/2, if symbolic links are encountered in Dir, the links are removed rather than their content.
  548delete_directory_contents(Dir) :-
  549    directory_files(Dir, Files),
  550    maplist(delete_directory_contents(Dir), Files).
 chmod(+File, +Spec) is det
Set the mode of the target file. Spec is one of +Mode, -Mode or a plain Mode, which adds new permissions, revokes permissions or sets the exact permissions. Mode itself is an integer, a POSIX mode name or a list of POSIX mode names. Defines names are suid, sgid, svtx and all names defined by the regular expression [ugo]*[rwx]*. Specifying none of "ugo" is the same as specifying all of them. For example, to make a file executable for the owner (user) and group, we can use:
?- chmod(myfile, +ugx).
  568chmod(File, +Spec) :-
  569    must_be(ground, Spec),
  570    !,
  571    mode_bits(Spec, Bits),
  572    file_mode_(File, Mode0),
  573    Mode is Mode0 \/ Bits,
  574    chmod_(File, Mode).
  575chmod(File, -Spec) :-
  576    must_be(ground, Spec),
  577    !,
  578    mode_bits(Spec, Bits),
  579    file_mode_(File, Mode0),
  580    Mode is Mode0 /\ \Bits,
  581    chmod_(File, Mode).
  582chmod(File, Spec) :-
  583    must_be(ground, Spec),
  584    !,
  585    mode_bits(Spec, Bits),
  586    chmod_(File, Bits).
  587
  588mode_bits(Spec, Spec) :-
  589    integer(Spec),
  590    !.
  591mode_bits(Name, Bits) :-
  592    atom(Name),
  593    !,
  594    (   file_mode(Name, Bits)
  595    ->  true
  596    ;   domain_error(posix_file_mode, Name)
  597    ).
  598mode_bits(Spec, Bits) :-
  599    must_be(list(atom), Spec),
  600    phrase(mode_bits(0, Bits), Spec).
  601
  602mode_bits(Bits0, Bits) -->
  603    [Spec], !,
  604    (   { file_mode(Spec, B), Bits1 is Bits0\/B }
  605    ->  mode_bits(Bits1, Bits)
  606    ;   { domain_error(posix_file_mode, Spec) }
  607    ).
  608mode_bits(Bits, Bits) -->
  609    [].
  610
  611file_mode(suid, 0o4000).
  612file_mode(sgid, 0o2000).
  613file_mode(svtx, 0o1000).
  614file_mode(Name, Bits) :-
  615    atom_chars(Name, Chars),
  616    phrase(who_mask(0, WMask0), Chars, Rest),
  617    (   WMask0 =:= 0
  618    ->  WMask = 0o0777
  619    ;   WMask = WMask0
  620    ),
  621    maplist(mode_char, Rest, MBits),
  622    foldl(or, MBits, 0, Mask),
  623    Bits is Mask /\ WMask.
  624
  625who_mask(M0, M) -->
  626    [C],
  627    { who_mask(C,M1), !,
  628      M2 is M0\/M1
  629    },
  630    who_mask(M2,M).
  631who_mask(M, M) -->
  632    [].
  633
  634who_mask(o, 0o0007).
  635who_mask(g, 0o0070).
  636who_mask(u, 0o0700).
  637
  638mode_char(r, 0o0444).
  639mode_char(w, 0o0222).
  640mode_char(x, 0o0111).
  641
  642or(B1, B2, B) :-
  643    B is B1\/B2