1:- module( os_lib, [ 
    2              % name manipulators
    3              os_base/2,                 % +Os, -Bname
    4              os_ext/2,                  % ?Ext, +Os
    5              os_ext/3,                  % ?Ext, ?Stem, ?Os
    6              os_ext/4,                  % ?Ext, ?NewExt, +Os, -NewOs
    7              os_dir_stem_ext/2,         % -Os, +Opts
    8              os_dir_stem_ext/4,         % ?Dir, ?Stem, ?Ext, ?Os
    9              os_stem/3,                 % ?Stem, -Os, +Opts
   10              os_postfix/2,              % -PsfxS, +Posted
   11              os_postfix/3,              % +PsfxS, ?Fname, ?Posted
   12              os_postfix/4,              % +PsfxS, ?Fname, ?Posted, +Opts
   13              os_abs/2, os_abs/3,        % +Os, -Abs[, +Opts]
   14              os_path/2,                 % ?Parts, ?Path
   15              os_path/3,                 % +-Dir, +-File, -+Path
   16              os_slashify/2,             % +-Path, -+Slashed
   17              os_parts/2,                % +-Parts, -+Stem
   18              os_parts/3,                % +-Parts, -+Stem, +Opts
   19              os_unique/2,               % +Tkn, -Os
   20              os_unique/3,               % +Tkn, -Os, +Opts
   21
   22              % commands
   23              os_mv/2,                   % +From, +To
   24              os_cp/2,                   % +From, +To
   25              os_ln_s/2,                 % +From, +To
   26              os_rm/1, os_rm/2,          % see os_remove/1,2
   27              os_remove/1,               % +Os
   28              os_remove/2,               % +Os, +Opts
   29              os_make_path/1,            % +Os
   30              os_make_path/2,            % +Os, +Opts
   31              os_repoint/2,              % +Os, +Opts 
   32              os_mill/4,                 % +Os, +Goal, ?Milled, +Opts
   33              os_un_zip/3,               % +Os, ?Stem, +Opts
   34
   35              % helpers
   36              os_sep/1,                  % -Sep
   37              os_sep/2,                  % -Sep, +Opts
   38              os_sel/3,                  % +Oses, +Pattern, -Selected
   39              os_sel/4,                  % +Oses, +Pattern, -Selected, +Opts
   40              os_term/2,                 % +-Atom, -+SlashTerm
   41              os_name/2,                 % +Os, -Type
   42
   43              % types and casting
   44              % os_type_entity/3,         % +Os, +Type, -Typed
   45              os_cast/2,                 % +Os, -Typed
   46              os_cast/3,                 % +Type, +Os, -Typed
   47              os_tmp_dir/1,              % -Os
   48              os_type_base/2,            % ?Type, ?Base
   49              os_version/2,              % -Vers, -Date
   50
   51              % logical
   52              os_exists/1, os_exists/2,  % +Os[, +Opts]
   53              os_file/1, os_file/2,      % ?Os[, +Opts]
   54              os_files/1, os_files/2,    % -Os[, +Opts]
   55              os_dir/1, os_dir/2,        % ?Os[, +Opts]
   56              os_dirs/1, os_dirs/2,      % ?Os[, +Opts]
   57
   58              % operators
   59              op( 400, fx, / )
   60            ] ).

Operating system interaction predicates.

This library collects a number of predicates useful for OS interactions. The emphasis here is on operations on files and directories rather than on calling OS commands. Unlike the system predicates of SWI/Yap here we adhere to the <lib>_ convention prefix that allows for more succinct predicate names. The assumption is that by using prefix "os", there will be a main argument that is an OS entity, so the predicate name does not have to explicitly refer to all the arguments. For instance

Highlights

polymorphic
4 ways to name OS objects
casting
and particulalry output variable casting via variable decoration
os_exists(Os, Opts)
works on files and dirs by default, and can be specialised via Opts
os_postfix(Psfx, Os, Posted)
os_postfix/3 add a bit on a OS name to produce a new one
os_ext(Ext, Stem, Os)
os_ext/3 is a renamed file_name_extension/3 with few extra bits
os_unique(Token, Os, Opts)
constructs unique filenames either based ondate (and possible time stamp) or on versioning
os_dir_stem_ext(Dir, Stem, Ext, Os)
os_dir_stem_ext/4 construct and de-construct OS names from/to its main parts
os_dir_stem_ext(Os, Opts)
construct
os_mill(File, Goal, Milled, Opts)
os_mill/4 allows construction of evolving pipelines
os_file(File)
os_file/1 backtrack over all files in current directory

In addition, the library is polymorphic in naming OS objects by supporting 4 different os term structures:

Currently the emphasis is on file name manipulations but command (eg copy_file) are likely to be included in new versions. Main reason why they are not yes, is that we use pack(by_unix).

Installation

To install

?- pack_install( os_lib ).

to load

?- use_module( library(os) ).

or

?- use_module( library(os_lib) ).

Opts

The library attempts to keep a consistent set of options that are on occasions funnelled through to either other interface or commonly used private predicates.

Common options:

dir(Dir=(.))
directory for input and output
idir(Idir=(.))
directory for input (overrides Dir)
odir(Odir=(.))
directory for output (overrides Dir)
ext(Ext=)
extension for file
stem(Stem)
stem to be used for constructing os names
sub(Sub)
apply operation recursive to sub directories

Variable name conventions

var(Os)
An os entity

Casts

(os_cast/3,os_cast/2)

\ Os
casts to /-terms
+ Os
casts to atoms
&(Os)
casts to strings
@ Os
casts to alias (input must be an alias to start with)

Nonmeclature

Predicates

The library predicates can be split to 4 groups.

  1. Predicates for manipulating and constructing OS entity names
  2. Commands
  3. Logical
  4. Helpers

Info

author
- nicos angelopoulos
version
- 0.0.1 2015/4/30
- 0.0.2 2015/4/30 added module documentation
- 0.0.3 2015/12/10 redone the typing and added better alias support, started custom errors
- 0.1.0 2016/2/24 first publisc release
- 0.6.0 2017/3/10 works with pack(lib)
- 1.0.0 2018/3/18
- 1.2.0 2018/8/5 added os_files/1,2 and os_dirs/1,2 (with options) and removed os_dir_files/2 and os_dir_dirs/2.
- 1.3 2018/10/1 cleaner error handling via throw, new opt dots(D), os_cast/3 arguments switch
- 1.4 2019/4/22 option sub(Sub); cp_rec.pl script; list of postfixes, etc
- 1.5 2019/4/22 os_path/2, fixes and new options to os_mill/4 ; os_exists/2 (return type) & os_sel/4
See also
- http://www.stoics.org.uk/~nicos/sware/os
- http://www.stoics.org.uk/~nicos/sware/os/html/os_lib.html
- doc/Releases.txt
To be done
- os_pwd/1 (working_directory + casting)
- use os_path/3 as a template to convert all lib predicates to castable outputs.
- there might a bit of dead code around

*/

  240:- use_module(library(lists)).      % select/3,...
  241:- use_module(library(apply)).      % maplist/3,...
  242:- use_module(library(debug)).      % /1,3.  -> switch to debuc/1,3
  243:- use_module(library(filesex)).    % link_file/3, make_directory_path/1.
  244
  245:- use_module(library(lib)).  246:- lib(source(os_lib), homonyms(true)).  247
  248:- lib(options).  249:- lib(pack_errors).  250
  251:- lib(os_dir_stem_ext/4).  252:- lib(os_dir_stem_ext/2).  253:- lib(os_stem/3).  254:- lib(os_ext/3).  255:- lib(os_remove/2).  256:- lib(os_make_path/2).  257:- lib(os_mill/4).  258:- lib(os_un_zip/3).  259:- lib(os_parts/3).  260:- lib(os_path/3).  261:- lib(os_postfix/3).  262:- lib(os_repoint/2).  263:- lib(os_slashify/2).  264:- lib(os_term/2).  265:- lib(os_tmp_dir/1).  266:- lib(os_name/2).  267:- lib(os_unique/2).  268:- lib(os_base/2).  269:- lib(os_cast/3).  270:- lib(os_errors/0).  271:- lib(os_abs/2).  272:- lib(os_abs/3).  273:- lib(os_file/1).  274:- lib(os_dir/1).  275:- lib(os_exists/1).  276:- lib(os_sep/1).  277:- lib(os_make_path/1).  278:- lib(os_sel/4).  279:- lib(os_mv/2).  280:- lib(os_cp/2).  281:- lib(os_ln_s/2).  282:- lib(os_type_base/2).  283
  284:- lib(stoics_lib:at_con/3).  285:- lib(stoics_lib:holds/2).  286:- lib(stoics_lib:compound/3).  287
  288:- lib(end(os_lib)).
 os_version(-Version, -Date)
Current version and release date for the library.
?- os_version( V, D ) :-
    V = 1:5:0,
    D = date(2020,9,18)

*/

  301os_version( 1:5:0, date(2020,9,18) )