View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           https://www.swi-prolog.org
    6    Copyright (c)  2008-2025, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    9                              SWI-Prolog Solutions b.v.
   10    All rights reserved.
   11
   12    Redistribution and use in source and binary forms, with or without
   13    modification, are permitted provided that the following conditions
   14    are met:
   15
   16    1. Redistributions of source code must retain the above copyright
   17       notice, this list of conditions and the following disclaimer.
   18
   19    2. Redistributions in binary form must reproduce the above copyright
   20       notice, this list of conditions and the following disclaimer in
   21       the documentation and/or other materials provided with the
   22       distribution.
   23
   24    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   25    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   26    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   27    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   28    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   29    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   30    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   31    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   32    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   33    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   34    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   35    POSSIBILITY OF SUCH DAMAGE.
   36*/
   37
   38:- module(process,
   39          [ process_create/3,           % +Exe, +Args, +Options
   40            process_wait/2,             % +PID, -Status
   41            process_wait/3,             % +PID, -Status, +Options
   42            process_id/1,               % -PID
   43            process_id/2,               % +Process, -PID
   44            is_process/1,               % +PID
   45            process_release/1,          % +PID
   46            process_kill/1,             % +PID
   47            process_group_kill/1,       % +PID
   48            process_group_kill/2,       % +PID, +Signal
   49            process_kill/2,             % +PID, +Signal
   50            process_which/2,            % +Exe, -AbsoluteFile
   51
   52            process_set_method/1        % +CreateMethod
   53          ]).   54:- multifile prolog:prolog_tool/4.   55:- dynamic   prolog:prolog_tool/4.   56
   57:- autoload(library(apply),[maplist/3]).   58:- autoload(library(error),[must_be/2,existence_error/2]).   59:- autoload(library(option),[select_option/3]).   60
   61:- use_foreign_library(foreign(process)).   62
   63:- predicate_options(process_create/3, 3,
   64                     [ stdin(any),
   65                       stdout(any),
   66                       stderr(any),
   67                       cwd(atom),
   68                       env(list(any)),
   69                       environment(list(any)),
   70                       priority(+integer),
   71                       process(-integer),
   72                       detached(+boolean),
   73                       window(+boolean)
   74                     ]).   75
   76/** <module> Create processes and redirect I/O
   77
   78The module library(process) implements interaction  with child processes
   79and unifies older interfaces such   as  shell/[1,2], open(pipe(command),
   80...) etc. This library is modelled after SICStus 4.
   81
   82The main interface is formed by process_create/3.   If the process id is
   83requested the process must be waited for using process_wait/2. Otherwise
   84the process resources are reclaimed automatically.
   85
   86In addition to the predicates, this module   defines  a file search path
   87(see user:file_search_path/2 and absolute_file_name/3) named `path` that
   88locates files on the system's  search   path  for  executables. E.g. the
   89following finds the executable for `ls`:
   90
   91    ?- absolute_file_name(path(ls), Path, [access(execute)]).
   92
   93__Incompatibilities and current limitations__
   94
   95  - Where SICStus distinguishes between an internal process id and
   96    the OS process id, this implementation does not make this
   97    distinction. This implies that is_process/1 is incomplete and
   98    unreliable.
   99
  100  - It is unclear what the detached(true) option is supposed to do.
  101    Disable signals in the child? Use setsid() to detach from the
  102    session? The current implementation uses setsid() on Unix systems.
  103
  104  - An extra option env([Name=Value, ...]) is added to
  105    process_create/3.  As of version 4.1 SICStus added
  106    environment(List) which _modifies_ the environment.  A
  107    compatible option was added to SWI-Prolog 7.7.23.
  108
  109  - Using prolog(Tool) for `Exe` is a SWI-Prolog extension.
  110
  111@tbd    Implement detached option in process_create/3
  112@compat SICStus 4
  113*/
  114
  115
  116%!  process_create(+Exe, +Args:list, +Options) is det.
  117%
  118%   Create a new process running the file   Exe and using arguments from
  119%   the  given  list.  Exe  is  a    file  specification  as  handed  to
  120%   absolute_file_name/3. Typically one use  the   `path`  file alias to
  121%   specify an executable file on the current PATH. The path `prolog` is
  122%   reserved. If Exe is prolog(Tool), a   Prolog utility is invoked that
  123%   belongs to the distribution of the calling Prolog process. `Tool` is
  124%   one of ``self``,  ``swipl``,  ``swipl-win``   or  ``swipl-ld``.  See
  125%   prolog:prolog_tool/4 for details.
  126%
  127%   Args is a list of arguments that are   handed to the new process. On
  128%   Unix systems, each element in the   list becomes a separate argument
  129%   in  the  new  process.  In  Windows,    the   arguments  are  simply
  130%   concatenated to form the commandline. Each argument itself is either
  131%   a primitive or a list of primitives. A primitive is either atomic or
  132%   a term file(Spec). Using file(Spec), the   system inserts a filename
  133%   using the OS filename  conventions  which   is  properly  quoted  if
  134%   needed.
  135%
  136%   Options:
  137%
  138%       - stdin(Spec)
  139%       - stdout(Spec)
  140%       - stderr(Spec)
  141%         Bind the standard streams of the new   process. Spec is one of
  142%         the terms below. If pipe(Pipe) is used, the Prolog stream is a
  143%         stream in text-mode using the encoding  of the default locale.
  144%         The encoding can be changed using   set_stream/2,  or by using
  145%         the  two-argument  form   of   `pipe`,    which   accepts   an
  146%         encoding(Encoding) option. The options   `stdout` and `stderr`
  147%         may use the same stream, in which case both output streams are
  148%         connected to the same Prolog stream.
  149%
  150%           - std
  151%             Just share with the Prolog I/O   streams.  On Unix, if the
  152%             `user_input`, etc. are bound to a   file handle but not to
  153%             0,1,2 the process I/O is  bound   to  the  file handles of
  154%             these streams.
  155%           - null
  156%             Bind to a _null_ stream. Reading from such a stream
  157%             returns end-of-file, writing produces no output
  158%           - pipe(-Stream)
  159%           - pipe(-Stream, +StreamOptions)
  160%             Attach  input  and/or  output  to  a  Prolog  stream.  The
  161%             optional StreamOptions argument is a  list of options that
  162%             affect the stream. Currently only  the options type(+Type)
  163%             and encoding(+Encoding) are supported, which have the same
  164%             meaning as the stream properties  of   the  same name (see
  165%             stream_property/2). StreamOptions is provided   mainly for
  166%             SICStus   compatibility   -   the   SWI-Prolog   predicate
  167%             set_stream/2 can be used for the same purpose.
  168%           - stream(+Stream)
  169%             Attach input or output to an  existing Prolog stream. This
  170%             stream must be associated with  an   OS  file  handle (see
  171%             stream_property/2, property `file_no`).  This   option  is
  172%             __not__ provided by the SICStus implementation.
  173%
  174%       - cwd(+Directory)
  175%         Run the new process in Directory.  Directory can be a compound
  176%         specification, which is converted  using absolute_file_name/3.
  177%         See also process_set_method/1.
  178%       - env(+List)
  179%         As environment(List), but _only_ the specified variables
  180%         are passed, i.e., no variables are _inherited_.
  181%       - environment(+List)
  182%         Specify  _additional_  environment  variables    for  the  new
  183%         process. List is a list of   `Name=Value` terms, where `Value`
  184%         is expanded the same way  as   the  Args  argument. If neither
  185%         `env` nor `environment` is passed the environment is inherited
  186%         from  the  Prolog  process.   At    most   one   env(List)  or
  187%         environment(List) term may appear in  the options. If multiple
  188%         appear a `permission_error` is raised for the second option.
  189%       - process(-PID)
  190%         Unify PID with the process id of the created process.
  191%       - detached(+Bool)
  192%         In Unix: If `true`,  detach  the   process  from  the terminal
  193%         Currently mapped to setsid(); Also creates a new process group
  194%         for the child In Windows: If   `true`, detach the process from
  195%         the current job via  the   CREATE_BREAKAWAY_FROM_JOB  flag. In
  196%         Vista and beyond, processes launched   from the shell directly
  197%         have  the  'compatibility   assistant'    attached   to   them
  198%         automatically unless they have  a   UAC  manifest  embedded in
  199%         them. This means that you will   get a permission denied error
  200%         if you try and assign  the  newly-created   PID  to  a job you
  201%         create yourself.
  202%       - window(+Bool)
  203%         If `true`, create a window for the process (Windows only)
  204%       - priority(+Priority)
  205%         In Unix: specifies the process priority  for the newly created
  206%         process. Priority must be  an  integer   between  -20  and 19.
  207%         Positive values are nicer to others,   and negative values are
  208%         less so. The default is zero. Users   are  free to lower their
  209%         own priority. Only the super-user may  _raise_ it to less-than
  210%         zero.
  211%
  212%   If the user specifies the  process(-PID)   option,  he __must__ call
  213%   process_wait/2 to reclaim the  process.   Without  this  option, the
  214%   system will wait for completion of the   process after the last pipe
  215%   stream is closed.
  216%
  217%   If the process is not waited for, it  must succeed with status 0. If
  218%   not, an process_error is raised.
  219%
  220%   __Windows notes__
  221%
  222%   On Windows this call is an interface to the CreateProcess() API. The
  223%   commandline consists of the basename of Exe and the arguments formed
  224%   from Args. Arguments  are  separated  by   a  single  space.  If all
  225%   characters satisfy iswalnum()  it  is   unquoted.  If  the  argument
  226%   contains a double-quote it is quoted   using  single quotes. If both
  227%   single and double quotes appear a  domain_error is raised, otherwise
  228%   double-quote are used.
  229%
  230%   The  CreateProcess()  API  has  many  options.  Currently  only  the
  231%   ``CREATE_NO_WINDOW`` options is supported  through the window(+Bool)
  232%   option. If omitted, the  default  is  to   use  this  option  if the
  233%   application has no console. Future versions   are  likely to support
  234%   more window specific options and replace win_exec/2.
  235%
  236%   __Examples__
  237%
  238%   First, a very simple example that   behaves  the same as ``shell('ls
  239%   -l')``, except for error handling:
  240%
  241%   ```
  242%   ?- process_create(path(ls), ['-l'], []).
  243%   ```
  244%
  245%   The following example uses grep to  find   all  matching  lines in a
  246%   file.
  247%
  248%   ```
  249%   grep(File, Pattern, Lines) :-
  250%           setup_call_cleanup(
  251%               process_create(path(grep), [ Pattern, file(File) ],
  252%                              [ stdout(pipe(Out))
  253%                              ]),
  254%               read_lines(Out, Lines),
  255%               close(Out)).
  256%
  257%   read_lines(Out, Lines) :-
  258%           read_line_to_codes(Out, Line1),
  259%           read_lines(Line1, Out, Lines).
  260%
  261%   read_lines(end_of_file, _, []) :- !.
  262%   read_lines(Codes, Out, [Line|Lines]) :-
  263%           atom_codes(Line, Codes),
  264%           read_line_to_codes(Out, Line2),
  265%           read_lines(Line2, Out, Lines).
  266%   ```
  267%
  268%   @error  process_error(Exe, Status) where Status is one of
  269%           exit(Code) or killed(Signal).  Raised if the process
  270%           is waited for (i.e., Options does not include
  271%           process(-PID)), and does not exit with status 0.
  272%   @bug    On Windows, environment(List) is handled as env(List),
  273%           i.e., the environment is not inherited.
  274
  275process_create(prolog(Prolog), Args, Options) =>
  276    prolog_executable(Prolog, Exe, Args, Args1),
  277    process_create(Exe, Args1, Options).
  278process_create(Exe, Args, Options) =>
  279    (   exe_options(ExeOptions),
  280        absolute_file_name(Exe, PlProg, ExeOptions)
  281    ->  true
  282    ),
  283    must_be(list, Args),
  284    maplist(map_arg, Args, Av),
  285    prolog_to_os_filename(PlProg, Prog),
  286    Term =.. [Prog|Av],
  287    expand_cwd_option(Options, Options1),
  288    expand_env_option(env, Options1, Options2),
  289    expand_env_option(environment, Options2, Options3),
  290    process_create(Term, Options3).
  291
  292%!  prolog_executable(+Tool, -Exe, +ArgvIn, -Argv) is det.
  293%!  prolog:prolog_tool(+Tool, -Exe, +ArgvIn, -Argv) is semidet.
  294%
  295%   Find the executable and commandline arguments for running Tool. This
  296%   provides    a    hook     for      process_create/3     called    as
  297%   process_create(prolog(Tool), ...). Tool is currently one of:
  298%
  299%     - `self`
  300%       Run Prolog itself.
  301%     - `swipl`
  302%       Run the commandline version, also when called from the
  303%       ``swipl-win`` _app_.
  304%     - `swipl-win`
  305%       Run the ``swipl-win`` _app_, also when called from the
  306%       commandline version.
  307%     - `swipl-ld`
  308%       Run the C/C++ compiler frontend to embed Prolog or build
  309%       foreign extensions.
  310%
  311%    prolog:prolog_tool/4 is defined as multifile and dynamic and can be
  312%    used for special cases. This hook is  notably intended to provide a
  313%    portable way of calling Prolog when Prolog is embedded.
  314%
  315%    For               example,               when                 using
  316%    [rolog](https://cran.r-project.org/web/packages/rolog/vignettes/rolog.html),
  317%    we can run Prolog using
  318%
  319%        R -s -e 'rswipl::swipl()', '—args' <Prolog Argv>
  320%
  321%    We can make process_create(prolog(swipl), ...) work using
  322%
  323%    ```
  324%    :- multifile prolog:prolog_tool/4.
  325%    prolog:prolog_tool(swipl, path('R'), Argv,
  326%                       [ '-s', '-e', 'rswipl::swipl()', '--args'
  327%                       | Argv
  328%                       ]).
  329%    ```
  330
  331prolog_executable(Prolog, Exe, Args0, Args),
  332    prolog:prolog_tool(Prolog, Exe, Args0, Args) =>
  333    true.
  334prolog_executable(self, Exe, Args0, Args) =>
  335    current_prolog_flag(executable, Exe),
  336    add_home_option(Args0, Args).
  337prolog_executable(Tool, Exe, Args0, Args),
  338    swipl_tool(Tool) =>
  339    current_prolog_flag(executable, Me),
  340    neighbour_exe(Tool, Me, Exe),
  341    add_home_option(Args0, Args).
  342
  343swipl_tool(swipl).
  344swipl_tool('swipl-win').
  345swipl_tool('swipl-ld').
  346
  347neighbour_exe(Target, Me, Exe) :-
  348    file_directory_name(Me, Dir),
  349    file_name_extension(_, Ext, Me),
  350    atomic_list_concat([Dir, Target], '/', Base),
  351    file_name_extension(Base, Ext, Exe).
  352
  353add_home_option(Args0, [HomeOption|Args0]) :-
  354    current_prolog_flag(home, Home),
  355    format(atom(HomeOption), '--home=~w', [Home]).
  356
  357%!  process_which(+Exe, -Path) is semidet.
  358%
  359%   True when Path is an absolute file   name for the specification Exe.
  360%   This deals with the search path as   well  as extensions used by the
  361%   OS.
  362
  363process_which(Exe, Path) :-
  364    exe_options(ExeOptions),
  365    absolute_file_name(Exe, Path, [file_errors(fail)|ExeOptions]),
  366    !.
  367
  368%!  exe_options(-Options) is multi.
  369%
  370%   Get options for absolute_file_name to find   an  executable file. On
  371%   Windows we first look for a  readable   file,  but  if this does not
  372%   exist we are happy with a existing file because the file may be a
  373%   [reparse point](https://docs.microsoft.com/en-us/windows/win32/fileio/reparse-points-and-file-operations)
  374
  375exe_options(Options) :-
  376    current_prolog_flag(windows, true),
  377    !,
  378    (   Options = [ extensions(['',exe,com]), access(read), file_errors(fail) ]
  379    ;   Options = [ extensions(['',exe,com]), access(exist) ]
  380    ).
  381exe_options(Options) :-
  382    Options = [ access(execute) ].
  383
  384expand_cwd_option(Options0, Options) :-
  385    select_option(cwd(Spec), Options0, Options1),
  386    !,
  387    (   compound(Spec)
  388    ->  absolute_file_name(Spec, PlDir, [file_type(directory), access(read)]),
  389        prolog_to_os_filename(PlDir, Dir),
  390        Options = [cwd(Dir)|Options1]
  391    ;   exists_directory(Spec)
  392    ->  Options = Options0
  393    ;   existence_error(directory, Spec)
  394    ).
  395expand_cwd_option(Options, Options).
  396
  397expand_env_option(Name, Options0, Options) :-
  398    Term =.. [Name,Value0],
  399    select_option(Term, Options0, Options1),
  400    !,
  401    must_be(list, Value0),
  402    maplist(map_env, Value0, Value),
  403    NewOption =.. [Name,Value],
  404    Options = [NewOption|Options1].
  405expand_env_option(_, Options, Options).
  406
  407map_env(Name=Value0, Name=Value) :-
  408    map_arg(Value0, Value).
  409
  410%!  map_arg(+ArgIn, -Arg) is det.
  411%
  412%   Map an individual argument. Primitives  are either file(Spec) or
  413%   an atomic value (atom, string, number).  If ArgIn is a non-empty
  414%   list,  all  elements  are   converted    and   the  results  are
  415%   concatenated.
  416
  417map_arg([], []) :- !.
  418map_arg(List, Arg) :-
  419    is_list(List),
  420    !,
  421    maplist(map_arg_prim, List, Prims),
  422    atomic_list_concat(Prims, Arg).
  423map_arg(Prim, Arg) :-
  424    map_arg_prim(Prim, Arg).
  425
  426map_arg_prim(file(Spec), File) :-
  427    !,
  428    (   compound(Spec)
  429    ->  absolute_file_name(Spec, PlFile)
  430    ;   PlFile = Spec
  431    ),
  432    prolog_to_os_filename(PlFile, File).
  433map_arg_prim(Arg, Arg).
  434
  435
  436%!  process_id(-PID) is det.
  437%
  438%   True if PID is the process id of the running Prolog process.
  439%
  440%   @deprecated     Use current_prolog_flag(pid, PID)
  441
  442process_id(PID) :-
  443    current_prolog_flag(pid, PID).
  444
  445%!  process_id(+Process, -PID) is det.
  446%
  447%   PID is the process id of Process.  Given that they are united in
  448%   SWI-Prolog, this is a simple unify.
  449
  450process_id(PID, PID).
  451
  452%!  is_process(+PID) is semidet.
  453%
  454%   True if PID might  be  a   process.  Succeeds  for  any positive
  455%   integer.
  456
  457is_process(PID) :-
  458    integer(PID),
  459    PID > 0.
  460
  461%!  process_release(+PID)
  462%
  463%   Release process handle.  In this implementation this is the same
  464%   as process_wait(PID, _).
  465
  466process_release(PID) :-
  467    process_wait(PID, _).
  468
  469%!  process_wait(+PID, -Status) is det.
  470%!  process_wait(+PID, -Status, +Options) is det.
  471%
  472%   True if PID completed with  Status.   This  call normally blocks
  473%   until the process is finished.  Options:
  474%
  475%       * timeout(+Timeout)
  476%       Default: `infinite`.  If this option is a number, the
  477%       waits for a maximum of Timeout seconds and unifies Status
  478%       with `timeout` if the process does not terminate within
  479%       Timeout.  In this case PID is _not_ invalidated.  On Unix
  480%       systems only timeout 0 and `infinite` are supported.  A
  481%       0-value can be used to poll the status of the process.
  482%
  483%       * release(+Bool)
  484%       Do/do not release the process.  We do not support this flag
  485%       and a domain_error is raised if release(false) is provided.
  486%
  487%   @arg  Status is one of exit(Code) or killed(Signal), where
  488%         Code and Signal are integers.  If the `timeout` option
  489%         is used Status is unified with `timeout` after the wait
  490%         timed out.
  491
  492process_wait(PID, Status) :-
  493    process_wait(PID, Status, []).
  494
  495%!  process_kill(+PID) is det.
  496%!  process_kill(+PID, +Signal) is det.
  497%
  498%   Send signal to process PID.  Default   is  `term`.  Signal is an
  499%   integer, Unix signal name (e.g. `SIGSTOP`)   or  the more Prolog
  500%   friendly variation one gets after   removing  `SIG` and downcase
  501%   the result: `stop`. On Windows systems,   Signal  is ignored and
  502%   the process is terminated using   the TerminateProcess() API. On
  503%   Windows systems PID must  be   obtained  from  process_create/3,
  504%   while any PID is allowed on Unix systems.
  505%
  506%   @compat SICStus does not accept the prolog friendly version.  We
  507%           choose to do so for compatibility with on_signal/3.
  508
  509process_kill(PID) :-
  510    process_kill(PID, term).
  511
  512
  513%!  process_group_kill(+PID) is det.
  514%!  process_group_kill(+PID, +Signal) is det.
  515%
  516%   Send signal to the group containing process PID.  Default   is
  517%   `term`.   See process_wait/1  for  a  description  of  signal
  518%   handling. In Windows, the same restriction on PID applies: it
  519%   must have been created from process_create/3, and the the group
  520%   is terminated via the TerminateJobObject API.
  521
  522process_group_kill(PID) :-
  523    process_group_kill(PID, term).
  524
  525
  526%!  process_set_method(+Method) is det.
  527%
  528%   Determine how the process is created on  Unix systems. Method is one
  529%   of `spawn` (default), `fork` or `vfork`.   If  the method is `spawn`
  530%   but this cannot be used because it is either not supported by the OS
  531%   or the cwd(Dir) option is given `fork` is used.
  532%
  533%   The problem is to be understood   as  follows. The official portable
  534%   and safe method to create a process is using the fork() system call.
  535%   This call however copies the process   page tables and get seriously
  536%   slow  as  the  (Prolog)  process  is   multiple  giga  bytes  large.
  537%   Alternatively, we may use vfork() which   avoids copying the process
  538%   space. But, the safe usage as guaranteed   by  the POSIX standard of
  539%   vfork() is insufficient for our purposes.  On practical systems your
  540%   mileage may vary. Modern posix   systems also provide posix_spawn(),
  541%   which provides a safe and portable   alternative  for the fork() and
  542%   exec() sequence that may be implemented using   fork()  or may use a
  543%   fast  but  safe  alternative.  Unfortunately  posix_spawn()  doesn't
  544%   support the option to specify the   working  directory for the child
  545%   and we cannot use working_directory/2 as   the  working directory is
  546%   shared between threads.
  547%
  548%   Summarizing, the default is  safe  and  tries   to  be  as  fast  as
  549%   possible. On some scenarios and on some   OSes  it is possible to do
  550%   better. It is generally a good  idea   to  avoid  using the cwd(Dir)
  551%   option of process_create/3 as without we can use posix_spawn().
  552
  553
  554                 /*******************************
  555                 *            MESSAGES          *
  556                 *******************************/
  557
  558:- multifile
  559    prolog:error_message/3.  560
  561prolog:error_message(process_error(File, exit(Status))) -->
  562    [ 'Process "~w": exit status: ~w'-[File, Status] ].
  563prolog:error_message(process_error(File, killed(Signal))) -->
  564    [ 'Process "~w": killed by signal ~w'-[File, Signal] ].
  565prolog:error_message(existence_error(source_sink, path(Exe))) -->
  566    [ 'Could not find executable file "~p" in '-[Exe] ],
  567    path_var.
  568
  569path_var -->
  570    (   { current_prolog_flag(windows, true) }
  571    ->  [ '%PATH%'-[] ]
  572    ;   [ '$PATH'-[] ]
  573    )