YAP 7.1.0
system.yap
Go to the documentation of this file.
1/*************************************************************************
2* *
3* YAP Prolog *
4* *
5* Yap Prolog was developed at NCCUP - Universidade do Porto *
6* *
7 * Copyright L.Damas, V.S.Costa and Universidade do Porto 1985-1997 *
8* *
9**************************************************************************
10* *
11* File: system.yap *
12* Last rev: *
13* mods: *
14* comments: Operating System Access built-ins *
15* *
16*************************************************************************/
17
18/**
19 * @file system.yap
20 * @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
21 * @date Wed Nov 18 01:23:45 2015
22 *
23 *
24*/
25
26
27
28:- module(operating_system_support,
29 [
30 datime/1,
31 %delete_file/1,
36 exec/3,
37 file_exists/2,
41 kill/1,
42 md5/3,
43 pid/1,
45% make_directory/1,
46 popen/3,
49 shell/0,
50 shell/1,
51 shell/2,
52 system/0,
58 tmpdir/1,
59 wait/2,
61 ]).
62
63
64
65/** @defgroup operating_system_support Operating System Functionality
66 * @brief Portable Interaction with the OS, be it Unix, Linux, OSX, or Windows.
67 *
68@ingroup YAPLibrary
69@{
70
71YAP provides a library of system utilities compatible with the
72SICStus Prolog system library. This library extends and to some point
73complements the functionality of Operating System access routines. The
74library includes Unix/Linux and Win32 `C` code. They
75are available through the `use_module(library(system))` command.
76
77*/
78
79
80/** @pred file_property(+ _File_,? _Property_)
81
82
83The atom _File_ corresponds to an existing file, and _Property_
84will be unified with a property of this file. The properties are of the
85form `type( _Type_)`, which gives whether the file is a regular
86file, a directory, a fifo file, or of unknown type;
87`size( _Size_)`, with gives the size for a file, and
88`mod_time( _Time_)`, which gives the last time a file was
89modified according to some Operating System dependent
90timestamp; `mode( _mode_)`, gives the permission flags for the
91file, and `linkto( _FileName_)`, gives the file pointed to by a
92symbolic link. Properties can be obtained through backtracking:
93
94```
95 ?- file_property('Makefile',P).
96
97P = type(regular) ? ;
98
99P = size(2375) ? ;
100
101P = mod_time(990826911) ? ;
102
103no
104```
105
106
107*/
108/** @pred host_id(- _Id_)
109
110
1117
112Unify _Id_ with an identifier of the current host. YAP uses the
113`hostid` function when available,
114
115
116*/
117/** @pred host_name(- _Name_)
118
119
120
121Unify _Name_ with a name for the current host. YAP uses the
122`hostname` function in Unix systems when available, and the
123`GetComputerName` function in WIN32 systems.
124
125
126*/
127/** @pred mktemp( _Spec_,- _File_)
128
129
130
131Direct interface to `mktemp`: given a _Spec_, that is a file
132name with six _X_ to it, create a file name _File_. Use
133tmpnam/1 instead.
134
135
136*/
137/** @pred mktime(+_Datime_, - _Seconds_)
138
139The `mktime/2` procedure receives a term of the form _datime(+ _Year_,
140+ _Month_, + _DayOfTheMonth_, + _Hour_, + _Minute_, + _Second_)_ and
141 returns the number of _Seconds_ elapsed since 00:00:00 on January 1,
1421970, Coordinated Universal Time (UTC). The user provides information
143on _Year_, _Month_, _DayOfTheMonth_, _Hour_, _Minute_, and
144_Second_. The _Hour_ is given on local time. This function uses the
145WIN32 `GetLocalTime` function or the Unix `mktime` function.
146
147```
148 ?- mktime(datime(2001,5,28,15,29,46),X).
149
150X = 991081786 ? ;
151```
152
153
154*/
155/** @pred pid(- _Id_)
156
157
158
159Unify _Id_ with the process identifier for the current
160process. An interface to the <tt>getpid</tt> function.
161
162
163*/
164
165/** @pred read_link(+ SymbolicLink, -Link, -NewPath)
166
167
168Follow a _SymbolicLink_, and obtain the actual _Link_ and the target _newPath_). This predicate uses the
169`C` built-in function `readlink` and is not yet operational in WIN32.
170
171
172*/
173/** @pred shell
174
175
176Start a new shell and leave YAP in background until the shell
177completes. YAP uses the shell given by the environment variable
178`SHELL`. In WIN32 environment YAP will use `COMSPEC` if
179`SHELL` is undefined.
180
181
182*/
183/** @pred shell(+ _Command_)
184
185Execute command _Command_ under a new shell. YAP will be in
186background until the command completes. In Unix environments YAP uses
187the shell given by the environment variable `SHELL` with the option
188`" -c "`. In WIN32 environment YAP will use `COMSPEC` if
189`SHELL` is undefined, in this case with the option `" /c "`.
190
191
192*/
193/** @pred shell(+ _Command_,- _Status_)
194
195Execute command _Command_ under a new shell and unify _Status_
196with the exit for the command. YAP will be in background until the
197command completes. In Unix environments YAP uses the shell given by the
198environment variable `SHELL` with the option `" -c "`. In
199WIN32 environment YAP will use `COMSPEC` if `SHELL` is
200undefined, in this case with the option `" /c "`.
201
202
203*/
204/** @pred system
205
206Start a new default shell and leave YAP in background until the shell
207completes. YAP uses `/bin/sh` in Unix systems and `COMSPEC` in
208WIN32.
209
210
211*/
212/** @pred tmp_file(+_Base_, - _File_)
213
214Create a name for a temporary file. _Base_ is an user provided
215identifier for the category of file. The _TmpName_ is guaranteed to
216be unique. If the system halts, it will automatically remove all created
217temporary files.
218
219
220*/
221/** @pred tmpnam(- _File_)
2227
223
224
225Interface with _tmpnam_: obtain a new, unique file name _File_.
226
227
228*/
229
230:- append/3use_module(library(lists), []).
231
232:- load_foreign_files([sys], [], init_sys).
233
234:- dynamic tmp_file_sequence_counter/1.
235
236% time builtins
237
238/**
239
240 @pred datime(datime(- _Year_, - _Month_, - _DayOfTheMonth_, - _Hour_, - _Minute_, - _Second_)
241
242The datime/1 procedure returns the current date and time, with
243information on _Year_, _Month_, _DayOfTheMonth_,
244 _Hour_, _Minute_, and _Second_. The _Hour_ is returned
245on local time. This function uses the WIN32
246`GetLocalTime` function or the Unix `localtime` function.
247
248```
249 ?- datime(X).
250
251X = datime(2001,5,28,15,29,46) ?
252```
253
254
255*/
256datime(X) :-
257 datime(X, Error),
258 handle_system_internal(Error, off, datime(X)).
259
260mktime(V, A) :- var(V), var,
261 throw(error(instantiation_error,mktime(V,A))).
262mktime(In,Out) :-
263 check_mktime_inp(In, mktime(In,Out)),
264 In = datime(Y,Mo,D,H,Mi,S),
265 mktime(Y, Mo, D, H, Mi, S, Out, Error),
266 handle_system_internal(Error, off, mktime(In,Out)).
267
268check_mktime_inp(V, Inp) :- var(V), var,
269 throw(error(instantiation_error,Inp)).
270check_mktime_inp(datime(Y,Mo,D,H,Mi,S), Inp) :- check_mktime_inp,
271 check_int(Y, Inp),
272 check_int(Mo, Inp),
273 check_int(D, Inp),
274 check_int(H, Inp),
275 check_int(Mi, Inp),
276 check_int(S, Inp).
277check_mktime_inp(T, Inp) :-
278 throw(error(domain_error(mktime,T),Inp)).
279
280check_int(I, _) :- integer(I), integer.
281check_int(I, Inp) :- var(I),
282 throw(error(instantiation_error,Inp)).
283check_int(I, Inp) :-
284 throw(error(type_error(integer,I),Inp)).
285
286% file operations
287% file operations
288
289/** @pred delete_file(+ _File_,+ _Opts_)
290
291The `delete_file/2` procedure removes file _File_ according to
292options _Opts_. These options are `directory` if one should
293remove directories, `recursive` if one should remove directories
294recursively, and `ignore` if errors are not to be reported.
295
296This example is equivalent to using the delete_file/1 predicate:
297
298```
299 ?- delete_file(x, [recursive]).
300```
301
302
303*/
304delete_file(IFile, Opts) :-
305 true_file_name(IFile, File),
306 process_delete_file_opts(Opts, Dir, Recurse, Ignore, delete_file(File,Opts)),
307 delete_file(File, Dir, Recurse, Ignore).
308
309process_delete_file_opts(V, _, _, _, T) :- var(V), var,
310 throw(error(instantiation_error,T)).
311process_delete_file_opts([], off, off, off, _) :- process_delete_file_opts.
312process_delete_file_opts([V|_], _, _, _, T) :- var(V), var,
313 throw(error(instantiation_error,T)).
314process_delete_file_opts([directory|Opts], on, Recurse, Ignore, T) :- process_delete_file_opts,
315 process_delete_file_opts(Opts, _, Recurse, Ignore, T).
316process_delete_file_opts([recursive|Opts], Dir, on, Ignore, T) :- process_delete_file_opts,
317 process_delete_file_opts(Opts, Dir, _, Ignore, T).
318process_delete_file_opts([ignore|Opts], Dir, Recurse, on, T) :- process_delete_file_opts,
319 process_delete_file_opts(Opts, Dir, Recurse, _, T).
320process_delete_file_opts(Opts, _, _, _, T) :-
321 throw(error(domain_error(delete_file_option,Opts),T)).
322
323delete_file(IFile, Dir, Recurse, Ignore) :-
324 true_file_name(IFile, File),
325 file_property(File, Type, _, _, _Permissions, _, Ignore),
326 delete_file(Type, File, Dir, Recurse, Ignore).
327
328delete_file(N, File, _Dir, _Recurse, Ignore) :- number(N), number, % error.
329 handle_system_internal(N, Ignore, delete_file(File)).
330delete_file(directory, File, Dir, Recurse, Ignore) :-
331 delete_directory(Dir, File, Recurse, Ignore), delete_directory.
332delete_file(_, File, _Dir, _Recurse, Ignore) :-
333 unlink_file(File, Ignore).
334
335unlink_file(IFile, Ignore) :-
336 true_file_name(IFile, File),
337 unlink(File, N),
338 handle_system_internal(N, Ignore, delete_file(File)).
339
340delete_directory(on, File, _Recurse, Ignore) :-
341 rm_directory(File, Ignore).
342delete_directory(off, File, Recurse, Ignore) :-
343 delete_directory(Recurse, File, Ignore).
344
345rm_directory(File, Ignore) :-
346 rmdir(File, Error),
347 handle_system_internal(Error, Ignore, delete_file(File)).
348
349delete_directory(on, File, Ignore) :-
350 directory_files(File, FileList),
351 path_separator(D),
352 atom_concat(File, D, FileP),
353 delete_dirfiles(FileList, FileP, Ignore),
354 rmdir(File, Ignore).
355
356delete_dirfiles([], _, _).
357delete_dirfiles(['.'|Fs], File, Ignore) :- delete_dirfiles,
358 delete_dirfiles(Fs, File, Ignore).
359delete_dirfiles(['..'|Fs], File, Ignore) :- delete_dirfiles,
360 delete_dirfiles(Fs, File, Ignore).
361delete_dirfiles([F|Fs], File, Ignore) :-
362 atom_concat(File,F,TrueF),
363 delete_file(TrueF, off, on, Ignore),
364 delete_dirfiles(Fs, File, Ignore).
365
366handle_system_internal(Error, _Ignore, _G) :- var(Error), var.
367handle_system_internal(Error, off, G) :- atom(Error), atom,
368 throw(error(system_internal(Error),G)).
369handle_system_internal(Error, off, G) :-
370 error_message(Error, Message),
371 throw(error(system_internal(Message),G)).
372
373handle_system_internal(Error, _Id, _Ignore, _G) :- var(Error), var.
374handle_system_internal(Error, _SIG, off, G) :- integer(Error), integer,
375 error_message(Error, Message),
376 throw(error(system_internal(Message),G)).
377handle_system_internal(signal, SIG, off, G) :- handle_system_internal,
378 throw(error(system_internal(child_signal(SIG)),G)).
379handle_system_internal(stopped, SIG, off, G) :-
380 throw(error(system_internal(child_stopped(SIG)),G)).
381
382file_property(IFile, type(Type)) :-
383 true_file_name(IFile, File),
384 file_property(File, Type, _Size, _Date, _Permissions, _LinkName).
385file_property(IFile, size(Size)) :-
386 true_file_name(IFile, File),
387 file_property(File, _Type, Size, _Date, _Permissions, _LinkName).
388file_property(IFile, mod_time(Date)) :-
389 true_file_name(IFile, File),
390 file_property(File, _Type, _Size, Date, _Permissions, _LinkName).
391file_property(IFile, mode(Permissions)) :-
392 true_file_name(IFile, File),
393 file_property(File, _Type, _Size, _Date, Permissions, _LinkName).
394file_property(IFile, linkto(LinkName)) :-
395 true_file_name(IFile, File),
396 file_property(File, _Type, _Size, _Date, _Permissions, LinkName),
397 atom(LinkName).
398
399file_property(File, Type, Size, Date, Permissions, LinkName) :-
400 file_property(File, Type, Size, Date, Permissions, LinkName, Error),
401 handle_system_internal(Error, off, file_property(File)).
402
403
404/** @pred environ(? _EnvVar_,+ _EnvValue_)
405
406
407Unify environment variable _EnvVar_ with its value _EnvValue_,
408if there is one. This predicate is backtrackable in Unix systems, but
409not currently in Win32 configurations.
410
411```
412 ?- environ('HOME',V).
413
414V = 'C:\\cygwin\\home\\administrator' ?
415```
416_EnvVar_ may be bound to an atom, or just be
417 unbound. In the latter case environ/2 will enumerate over all
418 environment variables.
419
420*/
421environ(Na,Val) :- var(Na), var,
422 ( p_environ(_,S) -> environ_split(S,SNa,SVal) ; environ_split, environ_split ),
423 atom_codes(Na, SNa),
424 atom_codes(Val, SVal).
425environ(Na,Val) :- atom(Na), atom,
426 bound_environ(Na, Val).
427environ(Na,Val) :-
428 throw(error(type_error(atom,Na),environ(Na,Val))).
429
430bound_environ(Na, Val) :- var(Val), var,
431 getenv(Na,Val).
432bound_environ(Na, Val) :- atom(Val), atom,
433 putenv(Na,Val).
434bound_environ(Na, Val) :-
435 throw(error(type_error(atom,Val),environ(Na,Val))).
436
437environ_enum(X,X).
438environ_enum(X,X1) :-
439 Xi is X+1,
440 environ_enum(Xi,X1).
441
442environ_split([61|SVal], [], SVal) :- environ_split.
443environ_split([C|S],[C|SNa],SVal) :-
444 environ_split(S,SNa,SVal).
445
446/** @pred exec(+ Command, StandardStreams, -PID)
447 *
448 *
449 *
450 * Execute command _Command_ with its standard streams connected to the
451 * list [_InputStream_, _OutputStream_, _ErrorStream_]. A numeric
452 * identifier to the process that executes the command is returned as
453 * _PID_. The command is executed by the default shell `bin/sh -c` in
454 * Unix.
455 *
456 * The following example demonstrates the use of exec/3 to send a
457 * command and process its output:
458 *
459 *
460~~~
461 go :-
462 exec(ls,[std,pipe(S),null],P),
463 repeat,
464 get0(S,C),
465 (C = -1, close(S) ! ; put(C)).
466~~~
467 *
468 * The streams may be one of standard stream, `std`, null stream,
469 * `null`, or `pipe(S)`, where _S_ is a pipe stream. Note
470 * that it is up to the user to close the pipe.
471 *
472 *
473*/
474exec(Command, [StdIn, StdOut, StdErr], PID) :-
475 G = exec(Command, [StdIn, StdOut, StdErr], PID),
476 check_command_with_default_shell(Command, TrueCommand, G),
477 process_inp_stream_for_exec(StdIn, In, G, [], L1),
478 process_out_stream_for_exec(StdOut, Out, G, L1, L2),
479 process_err_stream_for_exec(StdErr, Err, G, L2, L3),
480 ( exec_command(TrueCommand, In, Out, Err, PID, Error) -> exec_command ; exec_command ),
481 close_temp_streams(L3),
482 handle_system_internal(Error, off, G).
483
484process_inp_stream_for_exec(Error, _, G, L, L) :- var(Error), var,
485 close_temp_streams(L),
486 throw(error(instantiation_error,G)).
487process_inp_stream_for_exec(null, null, _, L, L) :- process_inp_stream_for_exec.
488process_inp_stream_for_exec(std, 0, _, L, L) :- process_inp_stream_for_exec.
489process_inp_stream_for_exec(pipe(ForWriting), ForReading, _, L, [ForReading|L]) :- var(ForWriting), var,
490 open_pipe_stream(ForReading, ForWriting).
491process_inp_stream_for_exec(pipe(Stream), _, _, L, L) :- process_inp_stream_for_exec,
492 stream_property(Stream, input).
493process_inp_stream_for_exec(Stream, Stream, _, L, L) :-
494 stream_property(Stream, put).
495
496
497process_out_stream_for_exec(Error, _, G, L, L) :- var(Error), var,
498 close_temp_streams(L),
499 throw(error(instantiation_error,G)).
500process_out_stream_for_exec(null, null, _, L, L) :- process_out_stream_for_exec.
501process_out_stream_for_exec(std, 1, _, L, L) :- process_out_stream_for_exec.
502process_out_stream_for_exec(pipe(ForReading), ForWriting, _, L, [ForWriting|L]) :- var(ForReading), var,
503 open_pipe_stream(ForReading, ForWriting).
504process_out_stream_for_exec(pipe(Stream), _, _, L, L) :- process_out_stream_for_exec,
505 stream_property(Stream, output).
506process_out_stream_for_exec(Stream, Stream, _, L, L) :-
507 stream_property(Stream, output).
508
509process_err_stream_for_exec(Error, _, G, L, L) :- var(Error), var,
510 close_temp_streams(L),
511 throw(error(instantiation_error,G)).
512process_err_stream_for_exec(null, null, _, L, L) :- process_err_stream_for_exec.
513process_err_stream_for_exec(std, 2, _, L, L) :- process_err_stream_for_exec.
514process_err_stream_for_exec(pipe(ForReading), ForWriting, _, L, [ForWriting|L]) :- var(ForReading), var,
515 open_pipe_stream(ForReading, ForWriting).
516process_err_stream_for_exec(pipe(Stream), Stream, _, L, L) :- process_err_stream_for_exec,
517 stream_property(Stream, output).
518process_err_stream_for_exec(Stream, Stream, _, L, L) :-
519 stream_property(Stream, output).
520
521close_temp_streams([]).
522close_temp_streams([S|Ss]) :-
523 close(S),
524 close_temp_streams(Ss).
525
526/** @pred popen( +Command, +TYPE, -Stream)
527
528 * Provides the functionaluty of the Unix <tt>popen</tt> function. It
529 * opens a process by creating a pipe, forking and invoking _Command_ on
530a * the child process. Since a pipe is by definition unidirectional the
531 * _Type_ argument may be `read` or `write`, not both. The stream should
532 * be closed using close/1, there is no need for a special `pclose`
533 * command.
534 *
535 * The following example demonstrates the use of popen/3 to process the
536 * output of a command, note that popen/3 works as a simplified interface
537 * to the exec/3 command:
538 *
539```
540?- popen(ls,read,X),repeat, get0(X,C), (C = -1, ! ; put(C)).
541
542X = 'C:\\cygwin\\home\\administrator' ?
543```
544 *
545 * The implementation of popen/3 relies on exec/3.
546 *
547*/
548popen(Command, read, Stream) :-
549 exec(Command, [std,pipe(Stream),std], Stream).
550popen(Command, write, Stream) :-
551 exec(Command, [pipe(Stream),std,std], Stream).
552
553check_command_with_default_shell(Com, ComF, G) :-
554 check_command(Com, G),
555 os_command_postprocess(Com, ComF).
556
557%
558% make sure that Windows executes the command from $COMSPEC.
559%
560os_command_postprocess(Com, ComF) :- os_command_postprocess, os_command_postprocess,
561 atom_codes(Com, SC),
562 append(" /c ", SC, SC1),
563 getenv('COMSPEC', Shell0),
564 atom_codes(Shell0, Codes),
565 append(Codes, SC1, SCF),
566 atom_codes(ComF, SCF).
567os_command_postprocess(Com, Com).
568
569check_command(Com, G) :- var(Com), var,
570 throw(error(instantiation_error,G)).
571check_command(Com, _) :- atom(Com), atom.
572check_command(Com, G) :-
573 throw(error(type_error(atom,Com),G)).
574
575check_mode(Mode, _, G) :- var(Mode), var,
576 throw(error(instantiation_error,G)).
577check_mode(read, 0, _) :- check_mode.
578check_mode(write,1, _) :- check_mode.
579check_mode(Mode, G) :-
580 throw(error(domain_error(io_mode,Mode),G)).
581
582throw :-
583 G = throw,
584 get_shell0(FullCommand),
585 exec_command(FullCommand, 0, 1, 2, PID, Error),
586 handle_system_internal(Error, off, G),
587 wait(PID, _Status, Error, Id),
588 handle_system_internal(Error, got(FullCommand, Id), off, G).
589
590shell(Command) :-
591 G = shell(Command),
592 check_command(Command, G),
593 get_shell(Shell,Opt),
594 do_shell(Shell, Opt, Command, Status, Error),
595 Status = 0,
596 handle_system_internal(Error, off, G).
597
598shell(Command, Status) :-
599 G = shell(Command, Status),
600 check_command(Command, G),
601 get_shell(Shell,Opt),
602 do_shell(Shell, Opt, Command, Status, Error),
603 handle_system_internal(Error, off, G).
604
605/**
606 * @pred system(+ _S_)
607
608Passes command _S_ to the Bourne shell (on UNIX environments) or the
609current command interpreter in WIN32 environments.
610*/
611
612/**
613 * @pred system
614
615Passes command _S_ to the Bourne shell (on UNIX environments) or the
616current command interpreter in WIN32 environments.
617*/
618system :-
619 default_shell(Command),
620 do_system(Command, _Status, Error),
621 handle_system_internal(Error, off, system).
622
623default_shell(Shell) :- default_shell, default_shell,
624 getenv('COMSPEC', Shell).
625default_shell('/bin/sh').
626
627
628/** @pred system(+ _Command_,- _Res_)
629
630Interface to `system`: execute command _Command_ and unify
631 _Res_ with the result.
632
633
634n*/
635system(Command, Status) :-
636 G = system(Command, Status),
637 check_command(Command, G),
638 do_system(Command, Status, Error),
639 Status = 0,
640 handle_system_internal(Error, off, G).
641
642wait(PID,STATUS) :- var(PID), var,
643 throw(error(instantiation_error,wait(PID,STATUS))).
644wait(PID,STATUS) :- integer(PID), integer,
645 plwait(PID, STATUS, Error, _Detail),
646 handle_system_internal(Error, off, wait(PID,STATUS)).
647wait(PID,STATUS) :-
648 throw(error(type_error(integer,PID),wait(PID,STATUS))).
649
650%
651% host info
652%
653host_name(X) :-
654 host_name(X, Error),
655 handle_system_internal(Error, off, host_name(X)).
656
657host_id(X) :-
658 host_id(X0, Error),
659 handle_system_internal(Error, off, host_id(X)),
660 number_codes(X0, S),
661 atom_codes(X, S).
662
663pid(X) :-
664 pid(X, Error),
665 handle_system_internal(Error, off, pid(X)).
666
667kill(X,Y) :-
668 integer(X), integer(Y), integer,
669 kill(X, Y, Error),
670 handle_system_internal(Error, off, kill(X,Y)).
671kill(X,Y) :- (var(X) ; var(Y)), !,
672 throw(error(instantiation_error,kill(X,Y))).
673kill(X,Y) :- integer(X), integer,
674 throw(error(type_error(integer,Y),kill(X,Y))).
675kill(X,Y) :-
676 throw(error(type_error(integer,X),kill(X,Y))).
677
678mktemp(X,Y) :- var(X), var,
679 throw(error(instantiation_error,mktemp(X,Y))).
680mktemp(X,Y) :-
681 atom(X), atom,
682 mktemp(X, Y, Error),
683 handle_system_internal(Error, off, mktemp(X,Y)).
684mktemp(X,Y) :-
685 throw(error(type_error(atom,X),mktemp(X,Y))).
686
687tmpnam(X) :-
688 tmpnam(X, Error),
689 handle_system_internal(Error, off, tmpnam(X)).
690
691%%% Added from Theo, path_seperator is used to replace the c predicate dir_separator which is not OS aware
692
693tmpdir(TmpDir):-
694 tmpdir(Dir, Error),
695 handle_system_internal(Error, off, tmpdir(Dir)),
696 path_separator(D),
697 (atom_concat(_, D, Dir) ->
698 TmpDir = Dir
699 ;
700 atom_concat(Dir, D, TmpDir)
701 ).
702
703path_separator('\\'):-
704 path_separator, path_separator.
705path_separator('/').
706
707read_link(P,D,F) :-
708 read_link(P, D),
709 absolute_file_name(D, [], F).
710
711/** @pred rename_file(+ _OldFile_,+ _NewFile_)
712
713
714Create file _OldFile_ to _NewFile_. This predicate uses the
715`C` built-in function `rename`.
716
717
718*/
719rename_file(F0, F) :-
720 rename_file(F0, F, Error),
721 handle_system_internal(Error, off, rename_file(F0, F)).
722
723/** @pred directory_files(+ _Dir_,+ _List_)
724
725
726Given a directory _Dir_, directory_files/2 procedures a
727listing of all fniles and directories in the directory:
728
729```
730 ?- directory_files('.',L), writeq(L).
731['Makefile.~1~','sys.so','Makefile','sys.o',x,..,'.']
732```
733The predicates uses the `dirent` family of routines in Unix
734environments, and `findfirst` in WIN32 through the system_library buil
735
736*/
737
738:- meta_predicate directory_map(+,1,-),
739 rb_apply(+,+,2,-).
740
741/** @pred directory_map(+ _Dir_, 1:_P_)
742
743
744Given a directory _Dir_, directory_map/2 visits all files in _Dir_,
745and verifies whether `P(F)` holds, where _F_ is the file's absolute
746path.
747
748```
749 ?- directory_map('.', process).
750```
751
752The predicates performs a left-recursive traversal. It does not protect against file system errors and it does not check for symbolic links.
753
754*/
755directory_map(D, P) :-
756 working_directory(_, D),
757 list_directory(D,L),
758 d_map(L,D, P).
759
760d_map([],_,_).
761d_map(['.'|Fs],D, P) :-
762 d_map,
763 d_map(Fs,D, P).
764d_map(['..'|Fs],D, P) :-
765 d_map,
766 d_map(Fs, D, P).
767d_map([F|Fs], D, P) :-
768 absolute_file_name( F, File, [prefix(D)] ),
769 f_map(File, P),
770 d_map(Fs, D, P).
771
772f_map(File, P) :-
773 catch( file_property( File, type(directory) ), _, fail ),
774 directory_map( File, P).
775f_map(File, P) :-
776 call(P,File).
777
778
779
780/** @} */
781
absolute_file_name( -File:atom, +Path:atom, +Options:list)
catch( : Goal,+ Exception,+ Action)
close(+ S)
stream_property( Stream, Prop )
Definition: top.yap:2
throw(+ Ball)
working_directory( ?_CurDir_,? NextDir)
list_directory(+ Dir, -ListOfFiles)
load_foreign_files( Files, Libs, InitRoutine)
use_module( +Files )
atom_codes(?Atom, ?Codes)
number_codes(? I,? L)
putenv(+ E,+ S)
atom( T)
integer( T)
number( T)
var( T)
append(? List1,? List2,? List3)
datime(datime(- Year, - Month, - DayOfTheMonth, - Hour, - Minute, - Second)
delete_file(+ File,+ Opts)
directory_files(+ Dir,+ List)
directory_map(+ Dir, 1:P)
environ(? EnvVar,+ EnvValue)
exec(+ Command, StandardStreams, -PID)
file_property(+ File,? Property)
host_id(- Id)
host_name(- Name)
mktemp( Spec,- File)
mktime(+_Datime_, - Seconds)
pid(- Id)
popen( +Command, +TYPE, -Stream)
rename_file(+ OldFile,+ NewFile)
shell(+ Command)
shell(+ Command,- Status)
system(+ S)
Definition: system.yap:582
system(+ Command,- Res)
tmp_file(+_Base_, - File)
tmpnam(- File)