1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2000-2017, University of Amsterdam 7 VU University Amsterdam 8 All rights reserved. 9 10 Redistribution and use in source and binary forms, with or without 11 modification, are permitted provided that the following conditions 12 are met: 13 14 1. Redistributions of source code must retain the above copyright 15 notice, this list of conditions and the following disclaimer. 16 17 2. Redistributions in binary form must reproduce the above copyright 18 notice, this list of conditions and the following disclaimer in 19 the documentation and/or other materials provided with the 20 distribution. 21 22 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 23 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 24 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 25 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 26 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 27 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 28 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 29 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 30 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 31 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 32 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 33 POSSIBILITY OF SUCH DAMAGE. 34*/ 35 36:- module(unix, 37 [ fork/1, % -'client'|pid 38 exec/1, % +Command(...Args...) 39 fork_exec/1, % +Command(...Args...) 40 wait/2, % -Pid, -Reason 41 kill/2, % +Pid. +Signal 42 pipe/2, % +Read, +Write 43 dup/2, % +From, +To 44 detach_IO/0, 45 detach_IO/1, % +Stream 46 environ/1 % -[Name=Value] 47 ]). 48:- use_module(library(shlib)).
64:- use_foreign_library(foreign(unix), install_unix).
Unix fork()
is the only way to create new processes and fork/1
is a simple direct interface to it.
88fork(Pid) :-
89 fork_warn_threads,
90 fork_(Pid).
96fork_warn_threads :- 97 findall(T, other_thread(T), Others), 98 ( Others == [] 99 -> true 100 ; Others == [gc] 101 -> thread_signal(gc, abort), 102 thread_join(gc, _) 103 ; throw(error(permission_error(fork, process, main), 104 context(_, running_threads(Others)))) 105 ). 106 107other_thread(T) :- 108 thread_self(Me), 109 thread_property(T, status(Status)), 110 T \== Me, 111 ( Status == running 112 -> true 113 ; print_message(warning, fork(join(T, Status))), 114 thread_join(T, _), 115 fail 116 ).
fork_exec(Command) :- ( fork(child) -> exec(Command) ; true ).
132fork_exec(Command) :-
133 ( fork_(child)
134 -> exec(Command)
135 ; true
136 ).
execvp()
. Here are some
examples:
exec(ls('-l'))
exec('/bin/ls'('-l', '/home/jan'))
Unix exec()
is the only way to start an executable file
executing. It is commonly used together with fork/1. For example
to start netscape on an URL in the background, do:
run_netscape(URL) :- ( fork(child), exec(netscape(URL)) ; true ).
Using this code, netscape remains part of the process-group of the invoking Prolog process and Prolog does not wait for netscape to terminate. The predicate wait/2 allows waiting for a child, while detach_IO/0 disconnects the child as a deamon process.
exited(ExitCode)
if the child with pid Pid was terminated by
calling exit()
(Prolog halt/1). ExitCode is the return status.
Status is unified with signaled(Signal)
if the child died due to
a software interrupt (see kill/2). Signal contains the signal
number. Finally, if the process suspended execution due to a
signal, Status is unified with stopped(Signal)
.SIG
prefix and mapping to lowercase. E.g. int
is the same as
SIGINT
in C. The meaning of the signal numbers can be found in
the Unix manual.:- use_module(library(unix)). fork_demo(Result) :- pipe(Read, Write), fork(Pid), ( Pid == child -> close(Read), format(Write, '~q.~n', [hello(world)]), flush_output(Write), halt ; close(Write), read(Read, Result), close(Read) ).
dup2()
, copying the underlying filedescriptor
and thus making both streams point to the same underlying
object. This is normally used together with fork/1 and pipe/2 to
talk to an external program that is designed to communicate
using standard I/O.
Both FromStream and ToStream either refer to a Prolog stream or
an integer descriptor number to refer directly to OS
descriptors. See also demo/pipe.pl
in the source-distribution of
this package.
user_input
, user_output
and
user_error
are closed if they are connected to a terminal
(see tty
property in stream_property/2). Input streams are
rebound to a dummy stream that returns EOF. Output streams are
reboud to forward their output to Stream.setsid()
if
provided or using ioctl()
TIOCNOTTY
on /dev/tty
.To ignore all output, it may be rebound to a null stream. For example:
..., open_null_stream(Out), detach_IO(Out).
The detach_IO/1 should be called only once per process. Subsequent calls silently succeed without any side effects.
/tmp/pl-out.<pid>
. Output is line buffered (see
set_stream/2).
272detach_IO :- 273 current_prolog_flag(pid, Pid), 274 atom_concat('/tmp/pl-out.', Pid, TmpFile), 275 open(TmpFile, write, Out, [alias(daemon_output)]), 276 set_stream(Out, buffer(line)), 277 detach_IO(Out). 278 279:- if(current_predicate(prctl/1)). 280:- export(prctl/1).
293:- endif. 294 295:- if(current_predicate(sysconf/1)). 296:- export(sysconf/1).
sysconf(1)
for details. Conf is
a term Config(Value), where Value is always an integer. Config
is the sysconf()
name after removing =_SC_= and conversion to
lowercase. Currently support the following configuration info:
arg_max
, child_max
, clk_tck
, open_max
, pagesize
,
phys_pages
, avphys_pages
, nprocessors_conf
and
nprocessors_onln
. Note that not all values may be supported on
all operating systems.309:- endif. 310 311 /******************************* 312 * MESSAGES * 313 *******************************/ 314 315:- multifile 316 prolog:message//1. 317 318prologmessage(fork(join(T, Status))) --> 319 [ 'Fork: joining thead ~p (status: ~p)'-[T, Status] ]
Unix specific operations
The
library(unix)
library provides the commonly used Unix primitives to deal with process management. These primitives are useful for many tasks, including server management, parallel computation, exploiting and controlling other processes, etc.The predicates in this library are modelled closely after their native Unix counterparts.
library(process)
provides a portable high level interface to create and manage processes. */