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:
- /-terms,
 
- atoms,
 
- strings, and
 
- aliased terms.
 
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
- /-(term)
Pronounced slash-term. Is an Os entity expressed as a term starting or separated by / for example abc/foo.bar instead of 'abc/foo.bar'
 
atomic(+os)
is an atom referring to an OS object 
- string(&os)
is a stringreferring to an OS object
 
- alias(@term)
is an Os entity expressed with alias compound, for example
abc(data/foo.bar) where abc is a known path alias 
- (16.6.24) i think the common adjective fo dir, link and fiel should be os-name
 
Predicates
The library predicates can be split to 4 groups.
- Predicates for manipulating and constructing OS entity names
 
- Commands
 
- Logical
 
- 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
 
-  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)
 
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
-  os_base(Arg1, Arg2)
 
-  os_ext(Arg1, Arg2)
 
-  os_ext(Arg1, Arg2, Arg3)
 
-  os_ext(Arg1, Arg2, Arg3, Arg4)
 
-  os_dir_stem_ext(Arg1, Arg2)
 
-  os_dir_stem_ext(Arg1, Arg2, Arg3, Arg4)
 
-  os_stem(Arg1, Arg2, Arg3)
 
-  os_postfix(Arg1, Arg2)
 
-  os_postfix(Arg1, Arg2, Arg3)
 
-  os_postfix(Arg1, Arg2, Arg3, Arg4)
 
-  os_abs(Arg1, Arg2)
 
-  os_abs(Arg1, Arg2, Arg3)
 
-  os_path(Arg1, Arg2)
 
-  os_path(Arg1, Arg2, Arg3)
 
-  os_slashify(Arg1, Arg2)
 
-  os_parts(Arg1, Arg2)
 
-  os_parts(Arg1, Arg2, Arg3)
 
-  os_unique(Arg1, Arg2)
 
-  os_unique(Arg1, Arg2, Arg3)
 
-  os_mv(Arg1, Arg2)
 
-  os_cp(Arg1, Arg2)
 
-  os_ln_s(Arg1, Arg2)
 
-  os_rm(Arg1)
 
-  os_rm(Arg1, Arg2)
 
-  os_remove(Arg1)
 
-  os_remove(Arg1, Arg2)
 
-  os_make_path(Arg1)
 
-  os_make_path(Arg1, Arg2)
 
-  os_repoint(Arg1, Arg2)
 
-  os_mill(Arg1, Arg2, Arg3, Arg4)
 
-  os_un_zip(Arg1, Arg2, Arg3)
 
-  os_sep(Arg1)
 
-  os_sep(Arg1, Arg2)
 
-  os_sel(Arg1, Arg2, Arg3)
 
-  os_sel(Arg1, Arg2, Arg3, Arg4)
 
-  os_term(Arg1, Arg2)
 
-  os_name(Arg1, Arg2)
 
-  os_cast(Arg1, Arg2)
 
-  os_cast(Arg1, Arg2, Arg3)
 
-  os_tmp_dir(Arg1)
 
-  os_type_base(Arg1, Arg2)
 
-  os_exists(Arg1)
 
-  os_exists(Arg1, Arg2)
 
-  os_file(Arg1)
 
-  os_file(Arg1, Arg2)
 
-  os_files(Arg1)
 
-  os_files(Arg1, Arg2)
 
-  os_dir(Arg1)
 
-  os_dir(Arg1, Arg2)
 
-  os_dirs(Arg1)
 
-  os_dirs(Arg1, Arg2)