popen support

This commit is contained in:
Vitor Santos Costa
2018-04-24 17:51:00 +01:00
parent 2c1d6910de
commit af848f28aa
10 changed files with 788 additions and 750 deletions

View File

@@ -64,21 +64,6 @@ available by loading the
:- use_module(library(readutil),
[read_line_to_codes/2]).
re_open(S, Mode, S) :-
is_stream(S),
!,
current_stream(_, Mode, S).
re_open(F, Mode, S) :-
open(F, Mode, S).
re_open(S, Mode, S, Props) :-
is_stream(S),
!,
current_stream(_, Mode, S),
maplist( set_stream(S), Props).
re_open(F, Mode, S, Props) :-
open(F, Mode, S, Props).
/**
@pred search_for(+ _Char_,+ _Line_)
Search for a character _Char_ in the list of codes _Line_.
@@ -469,8 +454,8 @@ process(StreamInp, Command) :-
the output stream is accessible through `filter_output`.
*/
file_filter(Inp, Out, Command) :-
re_open(Inp, read, StreamInp, [alias(filter_input)]),
re_open(Out, write, StreamOut),
open(Inp, read, StreamInp, [alias(filter_input)]),
open(Out, write, StreamOut),
filter(StreamInp, StreamOut, Command),
close(StreamInp),
close(StreamOut).
@@ -482,8 +467,8 @@ Same as file_filter/3, but before starting the filter execute
_Arguments_.
*/
file_filter_with_initialization(Inp, Out, Command, FormatString, Parameters) :-
re_open(Inp, read, StreamInp, [alias(filter_input)]),
re_open(Out, write, StreamOut, [alias(filter_output)]),
open(Inp, read, StreamInp, [alias(filter_input)]),
open(Out, write, StreamOut, [alias(filter_output)]),
format(StreamOut, FormatString, Parameters),
filter(StreamInp, StreamOut, Command),
close(StreamInp),
@@ -498,8 +483,8 @@ _StartGoal_, and call _ENdGoal_ as an epilog.
The input stream are always accessible through `filter_output` and `filter_input`.
*/
file_filter_with_start_end(Inp, Out, Command, StartGoal, EndGoal) :-
re_open(Inp, read, StreamInp, [alias(filter_input)]),
re_open(Out, write, StreamOut, [alias(filter_output)]),
open(Inp, read, StreamInp, [alias(filter_input)]),
open(Out, write, StreamOut, [alias(filter_output)]),
call( StartGoal, StreamInp, StreamOut ),
filter(StreamInp, StreamOut, Command),
call( EndGoal, StreamInp, StreamOut ),
@@ -525,7 +510,7 @@ file_filter_with_start_end(Inp, Out, Command, StartGoal, EndGoal) :-
file_select(Inp, Command) :-
( retract(alias(F)) -> true ; F = '' ),
atom_concat(filter_input, F, Alias),
re_open(Inp, read, StreamInp, [Alias]),
open(Inp, read, StreamInp, [Alias]),
atom_concat('_', F, NF),
assert( alias(NF) ),
repeat,

View File

@@ -2,9 +2,9 @@
* *
* YAP Prolog *
* *
* Yap Prolog was developed at NCCUP - Universidade do Porto *
* Yap Prolog was developed at NCCUP - Universidade do Porto *
* *
* Copyright L.Damas, V.S.Costa and Universidade do Porto 1985-1997 *
* Copyright L.Damas, V.S.Costa and Universidade do Porto 1985-1997 *
* *
**************************************************************************
* *
@@ -74,44 +74,7 @@ are available through the `use_module(library(system))` command.
*/
/**
@pred datime(datime(- _Year_, - _Month_, - _DayOfTheMonth_, - _Hour_, - _Minute_, - _Second_)
The datime/1 procedure returns the current date and time, with
information on _Year_, _Month_, _DayOfTheMonth_,
_Hour_, _Minute_, and _Second_. The _Hour_ is returned
on local time. This function uses the WIN32
`GetLocalTime` function or the Unix `localtime` function.
~~~~~
?- datime(X).
X = datime(2001,5,28,15,29,46) ?
~~~~~
*/
/** @pred environ(+ _E_,- _S_)
Given an environment variable _E_ this predicate unifies the second argument _S_ with its value.
*/
/** @pred system(+ _S_)
Passes command _S_ to the Bourne shell (on UNIX environments) or the
current command interpreter in WIN32 environments.
*/
/** @pred working_directory(- _CurDir_,? _NextDir_)
@@ -176,27 +139,6 @@ X = 'C:\\cygwin\\home\\administrator' ?
~~~~~
*/
/** @pred exec(+ _Command_, _StandardStreams_,- _PID_)
Execute command _Command_ with its standard streams connected to
the list [_InputStream_, _OutputStream_, _ErrorStream_]. The
process that executes the command is returned as _PID_. The
command is executed by the default shell `bin/sh -c` in Unix.
The following example demonstrates the use of exec/3 to send a
command and process its output:
~~~~~
exec(ls,[std,pipe(S),null],P),repeat, get0(S,C), (C = -1, close(S) ! ; put(C)).
~~~~~
The streams may be one of standard stream, `std`, null stream,
`null`, or `pipe(S)`, where _S_ is a pipe stream. Note
that it is up to the user to close the pipe.
*/
/** @pred file_exists(+ _File_)
@@ -289,37 +231,7 @@ process. An interface to the <tt>getpid</tt> function.
*/
/** @pred popen(+ _Command_, + _TYPE_, - _Stream_)
Interface to the <tt>popen</tt> function. It opens a process by creating a
pipe, forking and invoking _Command_ on the current shell. Since a
pipe is by definition unidirectional the _Type_ argument may be
`read` or `write`, not both. The stream should be closed
using close/1, there is no need for a special `pclose`
command.
The following example demonstrates the use of popen/3 to process
the output of a command, as exec/3 would do:
~~~~~{.prolog}
?- popen(ls,read,X),repeat, get0(X,C), (C = -1, ! ; put(C)).
X = 'C:\\cygwin\\home\\administrator' ?
~~~~~
The WIN32 implementation of popen/3 relies on exec/3.
*/
/** @pred rename_file(+ _OldFile_,+ _NewFile_)
Create file _OldFile_ to _NewFile_. This predicate uses the
`C` built-in function `rename`.
*/
/** @pred read_link(+ SymbolicLink, -Link, -NewPath)
@@ -423,6 +335,24 @@ also `absolute_file_name/2` and chdir/1.
% time builtins
/**
@pred datime(datime(- _Year_, - _Month_, - _DayOfTheMonth_, - _Hour_, - _Minute_, - _Second_)
The datime/1 procedure returns the current date and time, with
information on _Year_, _Month_, _DayOfTheMonth_,
_Hour_, _Minute_, and _Second_. The _Hour_ is returned
on local time. This function uses the WIN32
`GetLocalTime` function or the Unix `localtime` function.
~~~~~
?- datime(X).
X = datime(2001,5,28,15,29,46) ?
~~~~~
*/
datime(X) :-
datime(X, Error),
handle_system_internal(Error, off, datime(X)).
@@ -567,10 +497,14 @@ file_property(File, Type, Size, Date, Permissions, LinkName) :-
handle_system_internal(Error, off, file_property(File)).
%
% environment manipulation.
%
/** @pred environ(+E, -S)
Given an environment variable _E_ this predicate unifies the second
argument _S_ with its value. _E_ may be bound to an atom, or just be
unbound. In the latter case environ/2 will enumerate over all
environment variables.
*/
environ(Na,Val) :- var(Na), !,
environ_enum(0,I),
( p_environ(I,S) -> environ_split(S,SNa,SVal) ; !, fail ),
@@ -597,9 +531,33 @@ environ_split([61|SVal], [], SVal) :- !.
environ_split([C|S],[C|SNa],SVal) :-
environ_split(S,SNa,SVal).
%
% process execution
%
/** @pred exec(+ _Command_, _StandardStreams_,- _PID_)
*
*
*
* Execute command _Command_ with its standard streams connected to the
* list [_InputStream_, _OutputStream_, _ErrorStream_]. A numeric
* identifier to the process that executes the command is returned as
* _PID_. The command is executed by the default shell `bin/sh -c` in
* Unix.
*
* The following example demonstrates the use of exec/3 to send a
* command and process its output:
*
* ~~~~~
go :-
exec(ls,[std,pipe(S),null],P),
repeat,
get0(S,C),
(C = -1, close(S) ! ; put(C)).
~~~~~
*
* The streams may be one of standard stream, `std`, null stream,
* `null`, or `pipe(S)`, where _S_ is a pipe stream. Note
* that it is up to the user to close the pipe.
*
*
*/
exec(Command, [StdIn, StdOut, StdErr], PID) :-
G = exec(Command, [StdIn, StdOut, StdErr], PID),
check_command_with_default_shell(Command, TrueCommand, G),
@@ -652,8 +610,32 @@ close_temp_streams([S|Ss]) :-
close(S),
close_temp_streams(Ss).
popen(Command, Mode, Stream) :-
open(pipe(Command), Mode, Stream).
/** @pred popen(+ _Command_, + _TYPE_, - _Stream_)
* Provides the functionaluty of the Unix <tt>popen</tt> function. It
* opens a process by creating a pipe, forking and invoking _Command_ on
* the child process. Since a pipe is by definition unidirectional the
* _Type_ argument may be `read` or `write`, not both. The stream should
* be closed using close/1, there is no need for a special `pclose`
* command.
*
* The following example demonstrates the use of popen/3 to process the
* output of a command, note that popen/3 works as a simplified interface
* to the exec/3 command:
*
~~~~~{.prolog}
?- popen(ls,read,X),repeat, get0(X,C), (C = -1, ! ; put(C)).
X = 'C:\\cygwin\\home\\administrator' ?
~~~~~
*
* The implementation of popen/3 relies on exec/3.
*
*/
popen(Command, read, Stream) :-
exec(Command, [std,pipe(Stream),std], Stream).
popen(Command, write, Stream) :-
exec(Command, [pipe(Stream),std,std], Stream).
check_command_with_default_shell(Com, ComF, G) :-
check_command(Com, G),
@@ -811,5 +793,23 @@ read_link(P,D,F) :-
read_link(P, D),
absolute_file_name(D, [], F).
/** @pred rename_file(+ _OldFile_,+ _NewFile_)
Create file _OldFile_ to _NewFile_. This predicate uses the
`C` built-in function `rename`.
*/
rename_file(F0, F) :-
rename_file(F0, F, Error),
handle_system_internal(Error, off, rename_file(F0, F))).
/** @pred system(+ _S_)
Passes command _S_ to the Bourne shell (on UNIX environments) or the
current command interpreter in WIN32 environments.
*/
/** @} */

View File

@@ -729,7 +729,15 @@ static YAP_Bool execute_command(void) {
#endif /* UNIX code */
}
/* execute a command as a detached process */
/** @pred system(+ _S_)
Passes command _S_ to the Bourne shell (on UNIX environments) or the
current command interpreter in WIN32 environments.
Note that it executes them command as a detached process. It requires
`system` to be implemented by the system library.
*/
static YAP_Bool do_system(void) {
char *command = (char *)YAP_AtomName(YAP_AtomOfTerm(YAP_ARG1));
#if HAVE_SYSTEM