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
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)
.
To install
?- pack_install( os_lib ).
to load
?- use_module( library(os) ).
or
?- use_module( library(os_lib) ).
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:
Variable name conventions
atomic(+os)
is an atom referring to an OS objectabc(data/foo.bar)
where abc is a known path aliasThe library predicates can be split to 4 groups.
Opts
?- os_dir_stem_ext( Os, [stem(file),ext(csv)] ). Os = file.csv. ?- os_dir_stem_ext( Os, [stem(some_dir),ext(csv),type(dir)] ). Os = some_dir.
?- os_dir_stem_ext( data/what, file, csv, File ). File = data/what/file.csv. ?- os_dir_stem_ext( 'data/what', file, csv, File ). File = 'data/what/file.csv'. ?- os_dir_stem_ext( library(os), file, csv, File ). File = library('os/file.csv'). ?- os_dir_stem_ext( Dir, Stem, Ext, library('os/file.csv') ). Dir = '/usr/local/users/nicos/local/git/lib/swipl-7.3.16/library/os', Stem = file, Ext = csv. ?- os_dir_stem_ext( dir, stem, ext, /Os ). dir/stem.ext. ?- os_dir_stem_ext( "data/what", file, csv, File ). File = "data/what/file.csv". ?- os_dir_stem_ext( "data/what", file, csv, +File ). File = 'data/what/file.csv'.
Note: there is no quarantee the path to the file or the file itself exist.
Also File, might a relative or absolute reference depending on Dir's disposition.
Opts
postfix()
)?- os_stem( abc, File, dir(sub) ). File = 'sub/abc'. ?- os_stem( abc, File, [dir(sub),ext(csv)] ). File = 'sub/abc.csv'. ?- os_stem( Var, File, [from(abc/foo.bar),postfix(ps)] ). Var = File, File = abc/foo_ps. ?- os_stem( Stem, File, [from(abc/foo.bar),postfix(ps),dir(doc)] ). Stem = abc/foo_ps, File = doc/foo_ps. ?- os_stem( Stem, File, [from(abc/foo.bar),postfix(ps),dir(doc),use_from_dir(true)] ). Stem = File, File = abc/foo_ps. ?- os_stem( Stem, +(File), [from(abc/foo.bar),postfix(ps),dir(doc)] ). Stem = abc/foo_ps, File = 'doc/foo_ps'. ?- os_stem( "abc", File, dir(sub) ). File = 'sub/abc'. ?- os_stem( "abc", File, dir("sub") ). File = "sub/abc". ?- os_stem( abc, File, dir("sub") ).
New is a replacement of Ext in File that produces NewFile. Contrary to file_name_extension/3, os_ext/3 allows dots in Ext.
Currently Opts is only used to provide a trail of who has called this predicate for error reporting purposes:
?- os_ext( _, _, _, os_mill/4 ). ERROR: os:os_ext/4: Ground arguments expected in some of the positions: [[1,2],3], but found:[_172,_178,_184] ERROR: Trail: [os_mill/4] ?- os_ext( _, _, _, [os_mill/4,hrsv_fda/1] ). ERROR: os:os_ext/4: Ground arguments expected in some of the positions: [[1,2],3], but found:[_2126,_2132,_2138] ERROR: Trail: [os_mill/4,hrsv_fda/1]
Examples:
?- file_name_extension( X, tar.gz, abc.tar.gz ). false. ?- os_ext( tar.gz, Stem, dir/abc.tar.gz ). Stem = dir/abc ?- include( os_ext(pl), ['what.pl',none], Pls ). Pls = ['what.pl']. ?- maplist( os_ext(xls,csv), [abc.xls,def.xls], New ). New = [abc.csv, def.csv]. ?- os_ext( Ext, library(abc.txt) ). Ext = txt. ?- os_ext( csv, file.csv, File ). File = file.csv. ?- os_ext( csv, a.file.csv, File ). File = a.file.csv. ?- os_ext( X, S, a.file.csv ). X = csv, S = a.file. ?- os_ext( Old, new, afile.csv, Afile ). Old = csv, Afile = afile.new. ?- os_ext( Old, new, library(afile.csv), Afile ). Old = csv, Afile = library(afile.new). ?- os_ext( csv, abc/def, Os ). Os = abc/def.csv. ?- os_ext( csv, library(def), Os ). Os = library(def.csv). ?- os_ext( csv, /def, Os ). Os = /def.csv. ?- os_ext( csv, abc/def, Os ). Os = abc/def.csv. ?- os_ext( csv, "abc/def", Os ). Os = "abc/def.csv". ?- os_ext( csv, "abc/def", +Os ). Os = 'abc/def.csv'. ?- os_ext( Ext, Stem, "afile.csv" ). Ext = "csv", Stem = "afile". ?- os_ext( srt, 'a.file', 'a.file.srt' ). true. ?- os_ext( Old, srt, 'a.file', Afile ). Old = file, Afile = a.srt. ?- os_ext( txt, Csv, old.txt, New ). ERROR: os:os_ext/4: Ground argument expected at position: 2, (found: _7644) ?- os_ext( txt, Csv, New ). ERROR: os:os_ext/3: Ground arguments expected in some of the positions: [[1,2],3], but found:[txt,_8390,_8396]
Opts
on_exit(E)
message(M)
?- os_remove( sk, true ). Warning: os:os_rm/2: OS file: sk, does not exist false. ?- @touch(sk). true. ?- os_remove( sk, debug(true) ). % Deleting existing file: sk true. ?- os_remove( sk, err(test) ). false. ?- os_remove( sk, err(error) ). ERROR: os:os_rm/2: OS file: sk, does not exist ?- os_remove( sk, [on_exit(error),message(warning)] ). Warning: os:os_rm/2: OS file: sk, does not exist ?- os_remove( sk, [on_exit(false),message(informational)] ). % os:os_rm/2: OS file: sk, does not exist false. ?- os_remove( sk, [on_exit(fail),message(warning)] ). Warning: os:os_rm/2: OS file: sk, does not exist false.
Opts
debug(os_make_path)
,
instead it uses options_debug/3.false
?- os_make_path( '/tmp/what', debug(true) ). % Creating path: '/tmp/what' true. ?- os_make_path( '/tmp/what', debug(false) ). true. ?- os_make_path( '/tmp/what', debug(true) ). true. ?- os_make_path( '/tmp/what', debug_exists(true) ). true. ?- os_make_path( '/tmp/what', [debug_exists(true),debug(true)] ). % Path existed: '/tmp/what' true. ?- os_make_path( '/tmp/what1', debug(false) ). true. ?- os_make_path( '/tmp/what2' ). true. ?- os_make_path( "/tmp/what4" ). true. ?- os_make_path( /tmp/what5 ). true. ?- os_make_path( library(tmp) ). ?- os_make_path( Path, odir('/tmp/what3') ). Path = '/tmp/what3'. ?- ls('/tmp/what3'). true. ?- os_make_path( Path, true ). ERROR: Domain error: `Path, first argument in os_path_make/2 ground, or options containing dir/1 or odir/2' expected, found `'Opts'=['$restore'(os_make_path,debug,false),true,debug(false),afresh(false),debug_exists(false)]' ?- os_make_path( '/tmp/new1', [make_path(false),debug(true)] ). % Skipping creation of path: '/tmp/new1' true.
call(Callable,Obj)
is called to establish the location of OsObj which is used in place of FromOs.
As of 0.3, when Type=dir
and OutsTo
is a filename, Milled is created
as to house the file. Goal, should be aware of this- as it might be attempting to
create it too.
The Goal is called as call( Goal, RelFromOs, Milled, Co )
.
Opts
call(OnX,Milled)
, if OnX has a module, then it is used as is, else Mod is : prepended.Type=dir
OutsTo is assumed to be a file within (Milled, is created in this case).OutsTty=true
makes the file a tty output (stream_property/2).The predicate uses os_dir_stem_ext/2 to construct OS, so its options can be used in addition to the above.
The default postfix (P) is taken to be the predicate name of Goal, minus a possible 'file_' prefix.
?- assert( (true(A,B,C) :- write(args(A,B,C)), nl) ). ?- os_mill( abc.txt, true, Outf, [] ). args(abc.txt,abc_true.txt,[]) ERROR: os:os_mill/4: OS milled: abc_true.txt was not created (source was: abc.txt) ?- os_mill( abc.txt, true, Outf, not_created(fail) ). args(abc.txt,abc_true.txt,[]) false. ?- use_module(library(debug)). true. ?- [user]. |: go_from_here_to_there( Here, There, HTopts ) :- |: debug( testo, 'Here: ~w', [Here] ), |: debug( testo, 'There: ~w', [There] ), |: debug( testo, 'TheOpts: ~w', [HTopts] ). |: ^D% user://1 compiled 0.01 sec, 1 clauses true. ?- debug(testo). true. ?- Milts = [outputs_to('debug_outs.txt'),type(dir),debug(true)], os_mill( here, go_from_here_to_there, ex_os_milled, Milts ), write( milled(ex_os_milled) ), nl. % Creating non-existing mill entity: ex_os_milled, from: here % Calling os_mill: user:go_from_here_to_there/0 % Opened:'ex_os_milled/debug_outs.txt', at:<stream>(0x558dbb1d98c0) % Changing channels to: io_streams(user_input,<stream>(0x558dbb1d98c0),<stream>(0x558dbb1d98c0)) % Closing: <stream>(0x558dbb1d98c0) % Run output at: 'ex_os_milled/debug_outs.txt' milled(ex_os_milled) Milts = [outputs_to('debug_outs.txt'), type(dir), debug(true)]. ?- shell( 'cat ex_os_milled/debug_outs.txt'). % Calling: call(user:go_from_here_to_there,here,ex_os_milled,[]) % Here: here % There: ex_os_milled % TheOpts: [] % Caught: exit % Reverting streams to: io_streams(<stream>(0x7f4311820780),<stream>(0x7f4311820880),<stream>(0x7f4311820980)) true. ?-
Opts
?- tell( ex.txt ), maplist( writeln, [1,2,3,4,5] ), told, shell( 'gzip ex.txt' ), ls. ?- os_un_zip( ex.txt.gz, Stem1, keep(true) ). ?- os_un_zip( ex.txt.gz, Stem2, on_exists(error) ).
Second time should be an error as the gunzipped file already exists.
?- tell( ex2.txt ), maplist( writeln, [1,2,3,4,5] ), told, shell( 'gzip ex2.txt' ), ls. ?- os_un_zip( ex2.txt.gz, Stem, [keep(true),debug(true)] ). % Sending: gunzip(-k,-d,ex2.txt.gz) Stem = ex2.txt. % Stem: ex.txt exists, so skipping un_zipping of file: ex.txt.gz Stem = ex.txt.
Second time the debug message is different.
Opts
separator()
?- os_parts( Parts, abc_def ). Parts = [abc, def]. ?- os_parts( Parts, 'abc_def-xyz', sep(-) ). Parts = [abc_def, xyz].
?- os_path( D, F, '/abc/def/' ). D = '/abc', F = def. ?- os_path( D, F, "/abc/def/" ). D = "/abc", F = "def". ?- os_path( D, F, /abc/def/ ). ERROR: Syntax error: Unbalanced operator ERROR: os_path( D, F, /abc/def/ ERROR: ** here ** ERROR: ) . ?- os_path( D, F, /abc/def ). D = /abc, F = def. ?- os_path( abc/def, ghi.txt, Path ). Path = abc/def/ghi.txt. ?- os_path( /abc/def, ghi.txt, Path ). Path = /abc/def/ghi.txt. ?- os_path( '', abc, Abc ). Abc = abc. ?- directory_file_path( '', abc, Abc ). Abc = '/abc'. ?- os_path( Dir, Base, '/abc' ). Dir = '', Base = abc. ?- directory_file_path( Dir, Base, '/abc' ). Dir = (/), Base = abc. ?- os_path( hmrn(library(what)), abc, Abc ). ERROR: pack(os): Nested aliases are not supported yet. Found: hmrn(library(what)) at position: 1 for predicate: os_path/3 ?- file_search_path( hmrn, Hmrn ). Hmrn = '/home/nicos/ac/14mg/cohorts/hmrn'. ?- os_path( hmrn(what), if, Abc ). Abc = hmrn('what/if'). ?- os_path( hmrn(what/if), not, Abc ). Abc = hmrn(what/if/not). ?- os_path( hmrn(what/if), not, +Abc ). Abc = '/home/nicos/ac/14mg/cohorts/hmrn/what/if/not'. ?- os_path( hmrn(what/if), not, \Abc ). Abc = /home/nicos/ac/'14mg'/hmrn/what/if/not. ?- os_path( hmrn(what/if), not, @Abc ). Abc = hmrn(what/if/not). ?- os_path( "what/if", foo.txt, Abc ). Abc = "what/if/foo.txt". ?- os_path( Parts, 'a/b/c.txt' ), os_path( Parts, Rel ). Parts = [a, b, c.txt], Rel = 'a/b/c.txt'. ?- os_path( Parts, '/a/b/c.txt' ), os_path( Parts, Rel ). Parts = ['', a, b, c.txt], Rel = '/a/b/c.txt'.
Second argument is allowed to be the options (recognised as such when input is a list) so that it can be used in meta-calls.
Opts
with_ext()
for setting alternative extensions.ext(Ext)
above)sep(Sep)
- canonical is sep(Sep)
separator()
separator for stem-file parts (see os_sep/2)?- os_postfix( abc, library(x.txt), T ). T = library(x_abc.txt). ?- os_postfix( abc, library(x.txt), T, [separator(-)] ). T = library('x-abc.txt'). ?- os_postfix( abc, x.txt, T, sep(.) ). T = x.abc.txt. ?- os_postfix( v1, graph_layout.csv, T, [ignore_post(layout)] ). T = graph_v1_layout.csv. ?- os_postfix( v1, graph_lay_out.csv, T, [ignore_post(layout)] ). T = graph_lay_out_v1.csv. ?- os_postfix( v1, graph_lay_out.csv, T, ignore_post([lay,out]) ). T = graph_v1_lay_out.csv. ?- os_postfix( v1, graph_lay_out.csv, T, [ignore_post([out]),replace(true)] ). T = graph_v1_out.csv ?- maplist( os_postfix(v1,[sep(-)]),[a.csv,b.csv], AB ). AB = ['a-v1.csv', 'b-v1.csv']. ?- os_postfix( _, library(x.txt), T, postfix(abc) ). T = library(x_abc.txt). ?- os_postfix( _, "x.txt", T, postfix(abc) ). T = "x_abc.txt". ?- os_postfix( Psf, abc_def.txt ). Psf = def. ?- os_postfix( bit, by.csv, ByBit, with_ext(txt) ). ByBit = by_bit.txt. ?- os_postfix( [by,bit], bit.csv, ByBit, with_ext(txt) ). ByBit = bit_by_bit.txt.
debug(os_repoint)
aware.
?- debug( os_repoint ). ?- shell( 'touch atzoumbalos' ). ?- shell( 'ln -s atzoumbalos shortos' ). ?- shell( 'touch atzoukos ). ?- os_repoint( shortos, atzoukos ). % Warning, repointing link did not exist. Creating: shortos % Linked to: '/home/nicos/pl/packs/private/os/atzoukos' ?- os_repoint( shortolos, atzoumbalos ). % Repointing existing link: shortolos % Old target was: '/home/nicos/pl/packs/private/os/atzoukos' % Linked to: '/home/nicos/pl/packs/private/os/atzoumbalos' ?- os_repoint( danglink, atzou ). % Warning, repointing link did not exist. Creating: danglink % Linked to: '/home/nicos/pl/packs/private/os/atzou' ?- exists_file( danglink ). false. ?- os_exists( danglink ). false. ?- os_exists( danglink, type(flink) ). false. ?- os_exists( danglink, type(link) ). true.
0.2@2011/10/28, '' now goes to '', not to '/' 0.3@2013/10/06, now also goes -Path +Slashed 0.4@2014/10/06, changed predicate name from slashify/2
?- os_slashify( a, A ). A = 'a/'. ?- os_slashify( "a", A ). A = "a/". ?- os_slashify( A, 'a/' ). A = a. ?- os_slashify( A, 'a' ). A = a. ?- os_slashify( library(csv), Sla ). Sla = '/home/nicos/pl/lib/src/csv/'. ?- os_slashify( /tmp/abc, &(Sla) ). Sla = "/tmp/abc/". ?- os_slashify( /tmp/abc, Atom ). Atom = '/tmp/abc/'. ?- os_slashify( /tmp/abc, \(Term) ). Term = /tmp/abc.
?- os_term( Atom, './abc/edf.g' ). Atom = './abc/edf.g/'. ?- os_term( Atom, '.'/abc/edf.g ). Atom = './abc/edf.g/'. ?- os_term( 'abc/edf.g', Term ), Term = B / C. Term = abc/edf.g, B = abc, C = edf.g. ?- os_term( Abc, /abc/def.txt ). Abc = '/abc/def.txt'. ?- os_term( Abc, abc/def.txt ). Abc = 'abc/def.txt'. % Can be used to ensure a dir is in atom form: ?- os_term( Atom, 'abc/def' ). Atom = 'abc/def'. ?- os_term( '/abc/edf.g', Term ), Term = /A/B . ? Term = /abc/edf.g, A = abc, B = edf.g. ?- os_term( './abc/edf.g', Term ). Term = ('.')/abc/edf.g.
v0.2 added
Contrary to system tmp_file_stream/3 this predicate does not remove the directory at halt. The directory is placed in /tmp/ so it wouldn't survive a reboot.
When Os matches +(_), \(_) , &(_) or @(_) then the corresponding type is atom, slash string and alias, respectively. In this case, then first argument is not inspected.
Types
?- os_name(_,Type). Type = atom. ?- os_name(abc,Type). Type = atom. ?- os_name('abc/def',Type). Type = atom. ?- os_name("abc/def",Type). Type = string. ?- os_name(abc/def,Type). Type = slash. ?- os_name(+(_),Type). Type = atom. ?- os_name(\(_),Type). Type = slash. ?- os_name(&(_),Type). Type = string.
TokenS can be an atomic Token, or a list of Tokens in which case the Separator option will also apply within the token parts.
The predicate does not only provide the name of Os, it also, by default, creates it.
Opts:
version(Pfx,Compon,Type,Whc)
(version/0 is short for version(v,'',1,int,1)
).false
, do not make uniqueness check. A false
value makes this predicate a misnomer, however
is useful for geting the Os value in say results directory. See examples.Id and DP can be a free variables in which case they match everything.
When using dates for By and call this twice within a single second there is all the chance it will fail.
?- os_unique( res, Dname ). Dname = 'res-14.05.22'. ?- os_unique( res, Dname, [] ). Dname = 'res-14.05.22.10.40'. ?- os_unique( res, Dname, [] ). Dname = 'res-14.05.22.10.40.46'. ?- os_unique( res, Dname, [] ). Dname = 'res-14.05.22.10.40.57'. ?- os_unique( res, Dname, dir('/tmp') ). Dname = 'res-21.02.15/' % note: dir is created in /tmp ?- os_unique( res, Dname, [min_length(_,3)] ). Dname = 'res-014.005.022'. ?- os_unique( res, Dname, [token_sep('+'),sep_sub(':'),place_token(after),type(file)] ). Fname = '14:05:22+res.csv'. ?- os_unique( res, Dname, [token_sep('+'),sep_sub(':'),place_token(after),type(file)] ). Dname = '14:05:22:11:03+res.csv'. ?- os_unique( tkn, &(Bname), [type(file),ext(tsv)] ). Bname = "tkn-16.02.23.tsv". ?- os_unique( tkn, &(Bname), [type(file),ext(tsv)] ). Bname = "tkn-16.02.23.16.15.tsv". ?- os_unique( res, Dname, [ext(png),by(version),create(false),type(file)] ). Dname = 'res-v01.png'. ?- os_unique( res, Dname, [ext(png),by(version),create(false),type(file)] ). Dname = 'res-v01.png'. ?- os_unique( res, Dname, [ext(png),by(version),create(false),type(file)] ). Dname = 'res-v01.png'. ?- os_unique( res, Dname, by(version) ). Dname = 'res-v01'. ?- os_unique( res, Dname, by(version) ). Dname = 'res-v02'. ?- os_unique( res, Dname, by(version) ). Dname = 'res-v03'. ?- os_unique( res, Dname, [by(version),create(false)] ). Dname = 'res-v04'. ?- os_unique( res, Dname, [by(version),create(false)] ). Dname = 'res-v04'.
To force a restriction of say uniqueness at the date level:
?- os_unique( res, Here, by(date([ye,mo,da])) ). Here = 'res-23.06.01'. ?- os_unique( res, Here, by(date([ye,mo,da])) ). fail.
As of version 0.6, you can instead do the above with an error
?- os_unique( res1, Here, check(false) ). ?- ls. bigs.pl data/ res1-23.06.01/ ?- os_unique( res1, Here, check(false) ). ERROR: directory `'res1-23.06.01'' does not exist (File exists) ...
Used to be unique_entry_by_date/n, then unique_by_date/n.
?- os_base( abc/foo.txt, Base ). Base = foo.txt. ?- os_base( Var, Base ). ERROR: pack(os): Ground argument expected at position: 1 for predicate: os_base/2, but, _G1156 was found ?- os_base( abc(foo.bar), Base ). ERROR: pack(os): OS entity: abc(foo.bar), looks like aliased but alias does not exist. ?- os_base( library(foo.bar), Base ). Base = foo.bar. ?- os_base( "abc/foo.txt", Base ). Base = "foo.txt". ?- os_base( "abc/foo.txt", +Base ). Base = foo.txt.
atom
.
?- os_cast( abc/edf.txt, +Var ). Var = 'abc/edf.txt'. ?- os_cast( abc/edf.txt, \Var ). Var = abc/edf.txt. ?- os_cast( abc/edf.txt, @Var ). Var = abc/edf.txt. ?- os_cast( abc/edf.txt, &(Var) ). Var = "abc/edf.txt". ?- os_cast( abc/edf.txt, Var ). Var = 'abc/edf.txt'. ?- os_cast( atom, abc/edf.txt, Var ). Var = 'abc/edf.txt'.
Termplates
+(V) converts to atom (atom)
\(V) converts to /-term (slash)
@(V)
leave Os as is, assumes it is an alias-term
it is harder to convert arbitrary terms to aliased ones, (alias)
&(V) converts to string (string)
Opts
true
if dot starting files are required.true
, return the target of links rather than the links (via read_link/3).Stem==abs
.findall
for returning a list of all solutions.true
.?- cd(pack('os_lib/examples/testo')). ?- os_file(File). File = file1 ; ?- os_file( & File ). File = "file1". ?- os_file(File, sub(true)). File = 'dir1/file2' ; File = 'dir1/link2' ; File = file1. ?- os_file(File, dots(true)). File = '.dotty1' ; File = file1. :- absolute_file_name( pack(os_lib), OsDir ), working_directory( Old, OsDir ). OsDir = '/usr/local/users/nicos/local/git/lib/swipl-7.7.19/pack/os_lib', Old = '/home/nicos/.unison/canonical/sware/nicos/git/github/stoics.infra/'. File = pack.pl ; false. ?- os_file( File, solutions(findall) ). File = [pack.pl]. ?- os_file( File, [solutions(findall),sub(true)] ). File = ['doc/Releases.txt', 'doc/html/h1-bg.png', 'doc/html/h2-bg.png', 'doc/html/multi-bg.png', 'doc/html/os.html', 'doc/html/pldoc.css', 'doc/html/priv-bg.png', 'doc/html/pub-bg.png', 'examples/testo/dir1/file2'|...]. ?- os_file( File, [solutions(single),sub(true)] ). File = 'doc/Releases.txt' ; File = 'doc/html/h1-bg.png' ; File = 'doc/html/h2-bg.png' ; File = 'doc/html/multi-bg.png'...
os_file(File)
or os_file(File,Opts)
succeed.?- absolute_file_name( pack(os_lib/src), Abs ), os_files( Files, dir(Abs) ). Abs = '/usr/local/users/nicos/local/git/lib/swipl-7.7.18/pack/os_lib/src', Files = [os_abs.pl, os_base.pl, os_cast.pl, os_cp.pl, os_dir.pl, os_dir_stem_ext.pl, os_errors.pl, os_exists.pl, os_ext.pl|...].
Opts
?- cd( pack(os_lib) ). true. ?- ls. % doc/ pack.pl prolog/ src/ true. ?- os_dir(Dir), write( Dir ), nl, fail. doc prolog src false. ?- os_dir(& Dir). Dir = "doc" ; Dir = "prolog" ; Dir = "src" ; false. ?- os_dir(Os,sub(true)), write(Os), nl, fail. doc doc/html prolog src src/lib false. ?- os_dir(Os,[stem(abs),sub(true)]), write(Os), nl, fail. /usr/local/users/nicos/local/git/lib/swipl-7.7.18/pack/os_lib/doc/doc /usr/local/users/nicos/local/git/lib/swipl-7.7.18/pack/os_lib/doc/html/html /usr/local/users/nicos/local/git/lib/swipl-7.7.18/pack/os_lib/prolog/prolog /usr/local/users/nicos/local/git/lib/swipl-7.7.18/pack/os_lib/src/src /usr/local/users/nicos/local/git/lib/swipl-7.7.18/pack/os_lib/src/lib/lib false. ?- cd(pack('os_lib/examples/testo')). ?- os_dir( Dir ). Dir = dir1 ; false. ?- os_dir( Dir, dots(true) ). Dir = '.dodi1' Unknown action: ' (h for help) Action? ; Dir = dir1 ; false. ?- absolute_file_name( pack(os_lib), OsDir ), working_directory( _, OsDir ). OsDir = '.../lib/swipl-7.7.19/pack/os_lib', ?- ls. % doc/ examples/ pack.pl prolog/ src/ true. ?- os_dir( Dir ). Dir = doc ; Dir = examples ; Dir = prolog ; Dir = src ; false. ?- os_dir( Dir, solutions(findall) ). Dir = [doc, examples, prolog, src].
os_dir(Dir)
succeeds.?- cd( pack(os_lib) ). ?- os_dirs( Dirs ). Dirs = [doc,prolog, src, doc].
access_file(Os,execute)
. See option WinsFileExec.
The predicate tries to stay compatible with system predicates, but it does introduces two new file types: flink and dlink, for file point link or file, and directory pointing link or directory.
Opts
err(E)
, on_exit(O)
and message(M)
in throw/2)base(BaseType)
streamline type to either file or dir (see os_type_base/2).?- os_exists( pack(os_lib/src) ). true. ?- os_exists( pack(os_lib/src), type(link) ). false. ?- set_prolog_flag( allow_dot_in_atom, true ). ?- os_exists( pack(os_lib/prolog/os.pl), type(file) ). true. ?- cd( pack('os_lib/examples/testo') ). ?- os_exists(file1). true. ?- os_exists( "file1" ). true ?- os_exists( file2 ). false. ?- os_exists( file2, err(error) ). ERROR: os:os_exists/2: OS entity: file2, does not exist ?- os_exists( file2, err(exists) ). Warning: os:os_exists/2: OS entity: file2, does not exist false. ?- os_exists( file2, [on_exit(fail),message(warning)] ). Warning: os:os_exists/2: OS entity: file2, does not exist false. ?- os_exists( file2, [on_exit(error),message(informational)] ), writeln(later). % os:os_exists/2: OS entity: file2, does not exist ?- os_exists( file2, not(true) ). true. ?- os_exists( file1, [not(true),err(error)] ). ERROR: os:os_exists/2: OS entity: file1, already exists ?- os_exists( file1, type(dir) ). false. ?- os_exists( file1, [type(dir),err(error)] ). ERROR: os:os_exists/2: OS entity: file1, not of requested type: dir, but has type: file ?- os_exists( file1, type(flink) ). true. ?- os_exists( file1, type(link) ). false. ?- os_exists( dir1/link2, type(link) ). true. ?- os_exists( dir1/link2, type(base(Base)) ). Base = file.
Opts
sep(Sep)
- canonical is sep(Sep)
separator()
. Sep is the separator for stem-file parts?- os_sep( Sep ). Sep = '_'. ?- os_sep( Sep, true ). Sep = '_'. ?- os_sep( Sep, separator(x) ). Sep = x. ?- os_sep( Sep, [separator(x),sep(y)] ). Sep = y.
PatternS, a list of, or one of:
Opts
% mkdir /tmp/os_sel; cd /tmp/os_sel; touch a.pl b.txt c.pl abc.txt; mkdir abc_sub ?- os_sel( os_files, ext(pl), Sel, true ). Sel = [a.pl, c.pl]. ?- os_sel( os_files, ext(txt), Sel, true ). Sel = [b.txt, abc.txt]. ?- os_sel( os_all, sub(abc), Sel, true ). Sel = [abc.txt, abc_sub]. ?- working_directory( Old, '..' ), os_sel( os_dirs, os_, Sel, true ), working_directory( _, Old ). Old = '/tmp/os_sel/', Sel = [os_sel]. ?- os_sel( os_files, ext(txt), Files, stem(abs) ). Files = ['/homes/nicos/email.txt'].
% mkdir testo_D; touch testo_D/testo1; touch at_root ?- os_mv( testo_D/testo1, testo_D/example1 ). true ?- os_mv( at_root, testo_D ). ?- ls( testo_D ). % at_root example1 true. ?- % halt άμπελος;src/os% rm testo_D/example1; rm testo_D/at_root άμπελος;src/os% rmdir testo_D/;
% mkdir testo_D; touch testo_D/testo1; touch at_root ?- os_cp( testo_D/testo1, testo_D/example1 ). true ?- os_cp( at_root, testo_D ). ?- ls( testo_D ). % at_root example1 testo1 true. ?- % halt άμπελος;src/os% rm testo_D/testo1; rm testo_D/example1; rm testo_D/at_root; rm at_root άμπελος;src/os% rmdir testo_D
file,flink,link,any
map to file
and dir,dlink,link,any
to dir
.
Predicate is deterministic and in the -,- mode it generates file
for both any,link
.
?- os_type_base( flink, Base ). Base = file. ?- os_type_base( file, Base ). Base = file. ?- cd( pack('os_lib/examples/testo') ). ?- os_exists( dir1/link2, type(base(Base)) ). Base = file.
?- os_version( V, D ). V = 1:7:0, D = date(2024,1,7)