library(process) provides a portable high level interface 
to create and manage processes.
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.
Unix fork() is the only way to create new processes and fork/1 
is a simple direct interface to it.
permission_error(fork, process, main) is raised if the 
calling thread is not the only thread in the process. Forking a Prolog 
process with threads will typically deadlock because only the calling 
thread is cloned in the fork, while all thread synchronization are 
cloned.
fork_exec(Command) :-
      (   fork(child)
      ->  exec(Command)
      ;   true
      ).
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.
library(syslog)./tmp/pl-out.<pid>. 
Output is line buffered (see
set_stream/2).
library(syslog) allows for sending output to the Unix 
logging service.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.