View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        jan@swi-prolog.org
    5    WWW:           https://www.swi-prolog.org
    6    Copyright (c)  2021-2023, SWI-Prolog Solutions b.v.
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(build_tools,
   36	  [ build_steps/3,              % +Steps, +SrcDir, +Options
   37	    prolog_install_prefix/1,    % -Prefix
   38	    run_process/3,              % +Executable, +Argv, +Options
   39	    has_program/3,              % +Spec, -Path, +Env
   40	    ensure_build_dir/3          % +Dir, +State0, -State
   41	  ]).   42:- autoload(library(lists), [selectchk/3, member/2, append/3, last/2]).   43:- autoload(library(option), [option/2, option/3, dict_options/2]).   44:- autoload(library(pairs), [pairs_values/2]).   45:- autoload(library(process), [process_create/3, process_wait/2]).   46:- autoload(library(readutil), [read_stream_to_codes/3]).   47:- autoload(library(dcg/basics), [string/3]).   48:- autoload(library(apply), [foldl/4, maplist/2]).   49:- autoload(library(filesex), [directory_file_path/3, make_directory_path/1]).   50:- autoload(library(prolog_config), [prolog_config/2]).   51:- autoload(library(solution_sequences), [distinct/2]).   52
   53% The plugins.  Load them in the order of preference.
   54:- use_module(conan).   55:- use_module(cmake).   56:- use_module(make).   57
   58:- multifile
   59    prolog:build_file/2,                % ?File, ?Toolchain
   60    prolog:build_step/4,                % ?Step, ?Tool, ?SrcDir, ?BuildDir
   61    prolog:build_environment/2,         % ?Name, ?Value
   62    prolog_pack:environment/2.          % ?Name, ?Value (backward compatibility)
   63
   64/** <module> Utilities for building foreign resources
   65
   66This module implements the build system   that is used by pack_install/1
   67and pack_rebuild/1. The build system is a plugin based system where each
   68plugin knows about a specific  build   toolchain.  The plugins recognise
   69whether they are applicable based on  the   existence  of files that are
   70unique to the toolchain.   Currently it supports
   71
   72  - [conan](https://conan.io/) for the installation of dependencies
   73  - [cmake](https://cmake.org/) for configuration and building
   74  - [GNU tools](https://www.gnu.org) including `automake` and `autoconf`
   75    for configuration and building
   76*/
   77
   78%!  build_steps(+Steps:list, SrcDir:atom, +Options) is det.
   79%
   80%   Run the desired build steps.  Normally,   Steps  is  the list below,
   81%   optionally prefixed with `distclean` or `clean`. `[test]` may be
   82%   omited if ``--no-test`` is effective.
   83%
   84%       [[dependencies], [configure], build, [test], install]
   85%
   86%   Each step finds an applicable toolchain  based on known unique files
   87%   and calls the matching plugin to perform  the step. A step may fail,
   88%   which causes the system to try an  alternative. A step that wants to
   89%   abort the build process must  throw  an   exception.
   90%
   91%   If a step fails, a warning message is printed. The message can be
   92%   suppressed by enclosing the step in square brackets.  Thus, in the
   93%   above example of Steps, only failure  by the `build` and `install`
   94%   steps result in warning messages; failure of the other steps is
   95%   silent.
   96%
   97%   The failure of a step can be made into an error by enclosing it
   98%   in curly brackets, e.g. `[[dependencies], [configure], {build}, [test], {install}]`
   99%   would throw an exception if either the `build` or `install` step failed.
  100%
  101%   Options are:
  102%   * pack_version(N)
  103%     where N is 1 or 2 (default: 1).
  104%     This determines the form of environment names that are set before
  105%     the  build tools are calledd.
  106%     For version 1, names such as `SWIPLVERSION` or `SWIHOME` are used.
  107%     For version 2, names such as `SWIPL_VERSION` or `SWIPL_HOME_DIR` are used.
  108%
  109%   @tbd If no tool  is  willing  to   execute  some  step,  the step is
  110%   skipped. This is ok for some steps such as `dependencies` or `test`.
  111%   Possibly we should force the `install` step to succeed?
  112
  113build_steps(Steps, SrcDir, Options) :-
  114    dict_options(Dict0, Options),
  115    setup_path,
  116    build_environment(BuildEnv, Options),
  117    State0 = Dict0.put(#{ env: BuildEnv,
  118			  src_dir: SrcDir
  119			}),
  120
  121    foldl(build_step, Steps, State0, _State).
  122
  123build_step(Spec, State0, State) :-
  124    build_step_(Spec, State0, State),
  125    post_step(Spec, State).
  126
  127build_step_(Spec, State0, State) :-
  128    step_name(Spec, Step),
  129    prolog:build_file(File, Tool),
  130    directory_file_path(State0.src_dir, File, Path),
  131    exists_file(Path),
  132    prolog:build_step(Step, Tool, State0, State),
  133    !.
  134build_step_([_], State, State) :-
  135    !.
  136build_step_({Step}, State, State) :-
  137    !,
  138    print_message(error, build(step_failed(Step))),
  139    throw(error(build(step_failed(Step)))).
  140build_step_(Step, State, State) :-
  141    print_message(warning, build(step_failed(Step))).
  142
  143step_name([Step], Name) => Name = Step.
  144step_name({Step}, Name) => Name = Step.
  145step_name(Step,   Name) => Name = Step.
  146
  147%!  post_step(+Step, +State) is det.
  148%
  149%   Run code after completion of a step.
  150
  151post_step(Step, State) :-
  152    step_name(Step, configure),
  153    !,
  154    save_build_environment(State).
  155post_step(_, _).
  156
  157
  158%!  ensure_build_dir(+Dir, +State0, -State) is det.
  159%
  160%   Create the build directory. Dir is normally   either '.' to build in
  161%   the source directory or `build` to create a `build` subdir.
  162
  163ensure_build_dir(_, State0, State) :-
  164    _ = State0.get(bin_dir),
  165    !,
  166    State = State0.
  167ensure_build_dir(., State0, State) :-
  168    !,
  169    State = State0.put(bin_dir, State0.src_dir).
  170ensure_build_dir(Dir, State0, State) :-
  171    directory_file_path(State0.src_dir, Dir, BinDir),
  172    make_directory_path(BinDir),
  173    !,
  174    State = State0.put(bin_dir, BinDir).
  175
  176
  177		 /*******************************
  178		 *          ENVIRONMENT		*
  179		 *******************************/
  180
  181%!  build_environment(-Env, +Options) is det.
  182%
  183%   Options are documented under build_steps/3.
  184%
  185%   Assemble a clean  build  environment   for  creating  extensions  to
  186%   SWI-Prolog. Env is a list of   `Var=Value` pairs. The variable names
  187%   depend on the `pack_version(Version)`  term   from  `pack.pl`.  When
  188%   absent or `1`, the old names are used. These names are confusing and
  189%   conflict with some build environments. Using `2` (or later), the new
  190%   names are used. The list below  first   names  the new name and than
  191%   between parenthesis, the old name.  Provided variables are:
  192%
  193%     $ ``PATH`` :
  194%     contains the environment path with the directory
  195%     holding the currently running SWI-Prolog instance prepended
  196%     in front of it.  As a result, `swipl` is always present and
  197%     runs the same SWI-Prolog instance as the current Prolog process.
  198%     $ ``SWIPL`` :
  199%     contains the absolute file name of the running executable.
  200%     $ ``SWIPL_PACK_VERSION`` :
  201%     Version of the pack system (1 or 2)
  202%     $ ``SWIPL_VERSION`` (``SWIPLVERSION``) :
  203%     contains the numeric SWI-Prolog version defined as
  204%     _|Major*10000+Minor*100+Patch|_.
  205%     $ ``SWIPL_HOME_DIR`` (``SWIHOME``) :
  206%     contains the directory holding the SWI-Prolog home.
  207%     $ ``SWIPL_ARCH`` (``SWIARCH``) :
  208%     contains the machine architecture identifier.
  209%     $ ``SWIPL_MODULE_DIR`` (``PACKSODIR``) :
  210%     constains the destination directory for shared objects/DLLs
  211%     relative to a Prolog pack, i.e., ``lib/$SWIARCH``.
  212%     $ ``SWIPL_MODULE_LIB`` (``SWISOLIB``) :
  213%     The SWI-Prolog library or an empty string when it is not required
  214%     to link modules against this library (e.g., ELF systems)
  215%     $ ``SWIPL_LIB`` (``SWILIB``) :
  216%     The SWI-Prolog library we need to link to for programs that
  217%     _embed_ SWI-Prolog (normally ``-lswipl``).
  218%     $ ``SWIPL_INCLUDE_DIRS`` :
  219%     CMake style variable that contains the directory holding
  220%     ``SWI-Prolog.h``, ``SWI-Stream.h`` and ``SWI-cpp.h``.
  221%     $ ``SWIPL_LIBRARIES_DIR`` :
  222%     CMake style variable that contains the directory holding `libswipl`
  223%     $ ``SWIPL_CC`` (``CC``) :
  224%     Prefered C compiler
  225%     $ ``SWIPL_LD`` (``LD``) :
  226%     Prefered linker
  227%     $ ``SWIPL_CFLAGS`` (``CFLAGS``) :
  228%     C-Flags for building extensions. Always contains ``-ISWIPL-INCLUDE-DIR``.
  229%     $ ``SWIPL_MODULE_LDFLAGS`` (``LDSOFLAGS``) :
  230%     Link flags for linking modules.
  231%     $ ``SWIPL_MODULE_EXT`` (``SOEXT``) :
  232%     File name extension for modules (e.g., `so` or `dll`)
  233%     $ ``SWIPL_PREFIX`` (``PREFIX``) :
  234%     Install prefix for global binaries, libraries and include files.
  235
  236build_environment(Env, Options) :-
  237    findall(Name=Value,
  238	    distinct(Name, user_environment(Name, Value)),
  239	    UserEnv),
  240    findall(Name=Value,
  241	    ( def_environment(Name, Value, Options),
  242	      \+ memberchk(Name=_, UserEnv)
  243	    ),
  244	    DefEnv),
  245    append(UserEnv, DefEnv, Env).
  246
  247user_environment(Name, Value) :-
  248    prolog:build_environment(Name, Value).
  249user_environment(Name, Value) :-
  250    prolog_pack:environment(Name, Value).
  251
  252%!  prolog:build_environment(-Name, -Value) is nondet.
  253%
  254%   Hook  to  define  the  environment   for  building  packs.  This
  255%   Multifile hook extends the  process   environment  for  building
  256%   foreign extensions. A value  provided   by  this  hook overrules
  257%   defaults provided by def_environment/3. In  addition to changing
  258%   the environment, this may be used   to pass additional values to
  259%   the environment, as in:
  260%
  261%     ==
  262%     prolog:build_environment('USER', User) :-
  263%         getenv('USER', User).
  264%     ==
  265%
  266%   @arg Name is an atom denoting a valid variable name
  267%   @arg Value is either an atom or number representing the
  268%          value of the variable.
  269
  270
  271%!  def_environment(-Name, -Value, +Options) is nondet.
  272%
  273%   True if Name=Value must appear in   the environment for building
  274%   foreign extensions.
  275
  276def_environment('PATH', Value, _) :-
  277    getenv('PATH', PATH),
  278    current_prolog_flag(executable, Exe),
  279    file_directory_name(Exe, ExeDir),
  280    prolog_to_os_filename(ExeDir, OsExeDir),
  281    current_prolog_flag(path_sep, Sep),
  282    atomic_list_concat([OsExeDir, Sep, PATH], Value).
  283def_environment('SWIPL', Value, _) :-
  284    current_prolog_flag(executable, Value).
  285def_environment('SWIPL_PACK_VERSION', Value, Options) :-
  286    option(pack_version(Value), Options, 1).
  287def_environment('SWIPL_PACK_PATH', Value, _Options) :-
  288    prolog_config(pack_path, Value).
  289def_environment(VAR, Value, Options) :-
  290    env_name(version, VAR, Options),
  291    current_prolog_flag(version, Value).
  292def_environment(VAR, Value, Options) :-
  293    env_name(home, VAR, Options),
  294    current_prolog_flag(home, Value).
  295def_environment(VAR, Value, Options) :-
  296    env_name(arch, VAR, Options),
  297    current_prolog_flag(arch, Value).
  298def_environment(VAR, Value, Options) :-
  299    env_name(module_dir, VAR, Options),
  300    current_prolog_flag(arch, Arch),
  301    atom_concat('lib/', Arch, Value).
  302def_environment(VAR, Value, Options) :-
  303    env_name(module_lib, VAR, Options),
  304    current_prolog_flag(c_libplso, Value).
  305def_environment(VAR, '-lswipl', Options) :-
  306    env_name(lib, VAR, Options).
  307def_environment(VAR, Value, Options) :-
  308    env_name(cc, VAR, Options),
  309    default_c_compiler(Value).
  310def_environment(VAR, Value, Options) :-
  311    env_name(ld, VAR, Options),
  312    (   getenv('LD', Value)
  313    ->  true
  314    ;   default_c_compiler(Value)
  315    ).
  316def_environment('SWIPL_INCLUDE_DIRS', Value, _) :- % CMake style environment
  317    current_prolog_flag(home, Home),
  318    atom_concat(Home, '/include', Value).
  319def_environment('SWIPL_LIBRARIES_DIR', Value, _) :-
  320    swipl_libraries_dir(Value).
  321def_environment(VAR, Value, Options) :-
  322    env_name(cflags, VAR, Options),
  323    (   getenv('CFLAGS', SystemFlags)
  324    ->  Extra = [' ', SystemFlags]
  325    ;   Extra = []
  326    ),
  327    current_prolog_flag(c_cflags, Value0),
  328    current_prolog_flag(home, Home),
  329    atomic_list_concat([Value0, ' -I"', Home, '/include"' | Extra], Value).
  330def_environment(VAR, Value, Options) :-
  331    env_name(module_ldflags, VAR, Options),
  332    (   getenv('LDFLAGS', SystemFlags)
  333    ->  Extra = [SystemFlags|System]
  334    ;   Extra = System
  335    ),
  336    (   current_prolog_flag(windows, true)
  337    ->  prolog_library_dir(LibDir),
  338	atomic_list_concat(['-L"', LibDir, '"'], SystemLib),
  339	System = [SystemLib]
  340    ;   prolog_config(apple_bundle_libdir, LibDir)
  341    ->  atomic_list_concat(['-L"', LibDir, '"'], SystemLib),
  342	System = [SystemLib]
  343    ;   current_prolog_flag(c_libplso, '')
  344    ->  System = []                 % ELF systems do not need this
  345    ;   prolog_library_dir(SystemLibDir),
  346	atomic_list_concat(['-L"',SystemLibDir,'"'], SystemLib),
  347	System = [SystemLib]
  348    ),
  349    current_prolog_flag(c_ldflags, LDFlags),
  350    atomic_list_concat([LDFlags, '-shared' | Extra], ' ', Value).
  351def_environment(VAR, Value, Options) :-
  352    env_name(module_ext, VAR, Options),
  353    current_prolog_flag(shared_object_extension, Value).
  354def_environment(VAR, Value, Options) :-
  355    env_name(prefix, VAR, Options),
  356    prolog_install_prefix(Value).
  357
  358swipl_libraries_dir(Dir) :-
  359    current_prolog_flag(windows, true),
  360    !,
  361    current_prolog_flag(home, Home),
  362    atom_concat(Home, '/bin', Dir).
  363swipl_libraries_dir(Dir) :-
  364    prolog_config(apple_bundle_libdir, Dir),
  365    !.
  366swipl_libraries_dir(Dir) :-
  367    prolog_library_dir(Dir).
  368
  369env_name(Id, Name, Options) :-
  370    option(pack_version(V), Options, 1),
  371    must_be(oneof([1,2]), V),
  372    env_name_v(Id, V, Name).
  373
  374env_name_v(version,        1, 'SWIPLVERSION').
  375env_name_v(version,        2, 'SWIPL_VERSION').
  376env_name_v(home,           1, 'SWIHOME').
  377env_name_v(home,           2, 'SWIPL_HOME_DIR').
  378env_name_v(module_dir,     1, 'PACKSODIR').
  379env_name_v(module_dir,     2, 'SWIPL_MODULE_DIR').
  380env_name_v(module_lib,     1, 'SWISOLIB').
  381env_name_v(module_lib,     2, 'SWIPL_MODULE_LIB').
  382env_name_v(lib,            1, 'SWILIB').
  383env_name_v(lib,            2, 'SWIPL_LIB').
  384env_name_v(arch,           1, 'SWIARCH').
  385env_name_v(arch,           2, 'SWIPL_ARCH').
  386env_name_v(cc,             1, 'CC').
  387env_name_v(cc,             2, 'SWIPL_CC').
  388env_name_v(ld,             1, 'LD').
  389env_name_v(ld,             2, 'SWIPL_LD').
  390env_name_v(cflags,         1, 'CFLAGS').
  391env_name_v(cflags,         2, 'SWIPL_CFLAGS').
  392env_name_v(module_ldflags, 1, 'LDSOFLAGS').
  393env_name_v(module_ldflags, 2, 'SWIPL_MODULE_LDFLAGS').
  394env_name_v(module_ext,     1, 'SOEXT').
  395env_name_v(module_ext,     2, 'SWIPL_MODULE_EXT').
  396env_name_v(prefix,         1, 'PREFIX').
  397env_name_v(prefix,         2, 'SWIPL_PREFIX').
  398
  399%!  prolog_library_dir(-Dir) is det.
  400%
  401%   True when Dir is the directory holding ``libswipl.$SOEXT``
  402
  403:- multifile
  404    prolog:runtime_config/2.  405
  406prolog_library_dir(Dir) :-
  407    prolog:runtime_config(c_libdir, Dir),
  408    !.
  409prolog_library_dir(Dir) :-
  410    current_prolog_flag(windows, true),
  411    \+ current_prolog_flag(msys2, true),
  412    current_prolog_flag(home, Home),
  413    !,
  414    atomic_list_concat([Home, bin], /, Dir).
  415prolog_library_dir(Dir) :-
  416    current_prolog_flag(home, Home),
  417    (   current_prolog_flag(c_libdir, Rel)
  418    ->  atomic_list_concat([Home, Rel], /, Dir)
  419    ;   current_prolog_flag(arch, Arch)
  420    ->  atomic_list_concat([Home, lib, Arch], /, Dir)
  421    ).
  422
  423%!  default_c_compiler(-CC) is semidet.
  424%
  425%   Try to find a  suitable  C   compiler  for  compiling  packages with
  426%   foreign code.
  427%
  428%   @tbd Needs proper defaults for Windows.  Find MinGW?  Find MSVC?
  429
  430default_c_compiler(CC) :-
  431    getenv('CC', CC),
  432    !.
  433default_c_compiler(CC) :-
  434    preferred_c_compiler(CC),
  435    has_program(path(CC), _),
  436    !.
  437
  438preferred_c_compiler(CC) :-
  439    current_prolog_flag(c_cc, CC).
  440preferred_c_compiler(gcc).
  441preferred_c_compiler(clang).
  442preferred_c_compiler(cc).
  443
  444%!  save_build_environment(+State:dict) is det.
  445%
  446%   Create  a  shell-script  ``buildenv.sh``  that  contains  the  build
  447%   environment. This may be _sourced_ in the build directory to run the
  448%   build steps outside Prolog. It  may   also  be  useful for debugging
  449%   purposes.
  450
  451:- det(save_build_environment/1).  452save_build_environment(State) :-
  453    Env = State.get(env),
  454    !,
  455    (   BuildDir = State.get(bin_dir)
  456    ->  true
  457    ;   BuildDir = State.get(src_dir)
  458    ),
  459    directory_file_path(BuildDir, 'buildenv.sh', EnvFile),
  460    setup_call_cleanup(
  461	open(EnvFile, write, Out),
  462	write_env_script(Out, Env),
  463	close(Out)).
  464save_build_environment(_).
  465
  466write_env_script(Out, Env) :-
  467    format(Out,
  468	   '# This file contains the environment that can be used to\n\c
  469	    # build the foreign pack outside Prolog.  This file must\n\c
  470	    # be loaded into a bourne-compatible shell using\n\c
  471	    #\n\c
  472	    #   $ source buildenv.sh\n\n',
  473	   []),
  474    forall(member(Var=Value, Env),
  475	   format(Out, '~w=\'~w\'\n', [Var, Value])),
  476    format(Out, '\nexport ', []),
  477    forall(member(Var=_, Env),
  478	   format(Out, ' ~w', [Var])),
  479    format(Out, '\n', []).
  480
  481%!  prolog_install_prefix(-Prefix) is semidet.
  482%
  483%   Return the directory that can be  passed into `configure` or `cmake`
  484%   to install executables and other  related   resources  in  a similar
  485%   location as SWI-Prolog itself.  Tries these rules:
  486%
  487%     1. If the Prolog flag `pack_prefix` at a writable directory, use
  488%        this.
  489%     2. If the current executable can be found on $PATH and the parent
  490%        of the directory of the executable is writable, use this.
  491%     3. If the user has a writable ``~/bin`` directory, use ``~``.
  492
  493prolog_install_prefix(Prefix) :-
  494    current_prolog_flag(pack_prefix, Prefix),
  495    access_file(Prefix, write),
  496    !.
  497prolog_install_prefix(Prefix) :-
  498    current_prolog_flag(os_argv, [Name|_]),
  499    has_program(path(Name), EXE),
  500    file_directory_name(EXE, Bin),
  501    file_directory_name(Bin, Prefix0),
  502    (   local_prefix(Prefix0, Prefix1)
  503    ->  Prefix = Prefix1
  504    ;   Prefix = Prefix0
  505    ),
  506    access_file(Prefix, write),
  507    !.
  508prolog_install_prefix(Prefix) :-
  509    expand_file_name(~, [UserHome]),
  510    directory_file_path(UserHome, bin, BinDir),
  511    exists_directory(BinDir),
  512    access_file(BinDir, write),
  513    !,
  514    Prefix = UserHome.
  515
  516local_prefix('/usr', '/usr/local').
  517
  518
  519		 /*******************************
  520		 *          RUN PROCESSES       *
  521		 *******************************/
  522
  523%!  run_process(+Executable, +Argv, +Options) is det.
  524%
  525%   Run Executable.  Defined options:
  526%
  527%     - directory(+Dir)
  528%       Execute in the given directory
  529%     - output(-Out)
  530%       Unify Out with a list of codes representing stdout of the
  531%       command.  Otherwise the output is handed to print_message/2
  532%       with level =informational=.
  533%     - error(-Error)
  534%       As output(Out), but messages are printed at level =error=.
  535%     - env(+Environment)
  536%       Environment passed to the new process.
  537%
  538%   If Executable is path(Program) and we   have  an environment we make
  539%   sure to use  the  ``PATH``  from   this  environment  for  searching
  540%   `Program`.
  541
  542run_process(path(Exe), Argv, Options) :-
  543    option(env(BuildEnv), Options),
  544    !,
  545    setup_call_cleanup(
  546	b_setval('$build_tool_env', BuildEnv),
  547	run_process(pack_build_path(Exe), Argv, Options),
  548	nb_delete('$build_tool_env')).
  549run_process(Executable, Argv, Options) :-
  550    \+ option(output(_), Options),
  551    \+ option(error(_), Options),
  552    current_prolog_flag(unix, true),
  553    current_prolog_flag(threads, true),
  554    !,
  555    process_create_options(Options, Extra),
  556    process_create(Executable, Argv,
  557		   [ stdout(pipe(Out)),
  558		     stderr(pipe(Error)),
  559		     process(PID)
  560		   | Extra
  561		   ]),
  562    thread_create(relay_output([output-Out, error-Error]), Id, []),
  563    process_wait(PID, Status),
  564    thread_join(Id, _),
  565    (   Status == exit(0)
  566    ->  true
  567    ;   throw(error(process_error(process(Executable, Argv), Status), _))
  568    ).
  569run_process(Executable, Argv, Options) :-
  570    process_create_options(Options, Extra),
  571    setup_call_cleanup(
  572	process_create(Executable, Argv,
  573		       [ stdout(pipe(Out)),
  574			 stderr(pipe(Error)),
  575			 process(PID)
  576		       | Extra
  577		       ]),
  578	(   read_stream_to_codes(Out, OutCodes, []),
  579	    read_stream_to_codes(Error, ErrorCodes, []),
  580	    process_wait(PID, Status)
  581	),
  582	(   close(Out),
  583	    close(Error)
  584	)),
  585    print_error(ErrorCodes, Options),
  586    print_output(OutCodes, Options),
  587    (   Status == exit(0)
  588    ->  true
  589    ;   throw(error(process_error(process(Executable, Argv), Status), _))
  590    ).
  591
  592process_create_options(Options, Extra) :-
  593    option(directory(Dir), Options, .),
  594    (   option(env(Env), Options)
  595    ->  Extra = [cwd(Dir), environment(Env)]
  596    ;   Extra = [cwd(Dir)]
  597    ).
  598
  599relay_output([]) :- !.
  600relay_output(Output) :-
  601    pairs_values(Output, Streams),
  602    wait_for_input(Streams, Ready, infinite),
  603    relay(Ready, Output, NewOutputs),
  604    relay_output(NewOutputs).
  605
  606relay([], Outputs, Outputs).
  607relay([H|T], Outputs0, Outputs) :-
  608    selectchk(Type-H, Outputs0, Outputs1),
  609    (   at_end_of_stream(H)
  610    ->  close(H),
  611	relay(T, Outputs1, Outputs)
  612    ;   read_pending_codes(H, Codes, []),
  613	relay(Type, Codes),
  614	relay(T, Outputs0, Outputs)
  615    ).
  616
  617relay(error,  Codes) :-
  618    set_prolog_flag(message_context, []),
  619    print_error(Codes, []).
  620relay(output, Codes) :-
  621    print_output(Codes, []).
  622
  623print_output(OutCodes, Options) :-
  624    option(output(Codes), Options),
  625    !,
  626    Codes = OutCodes.
  627print_output(OutCodes, _) :-
  628    print_message(informational, build(process_output(OutCodes))).
  629
  630print_error(OutCodes, Options) :-
  631    option(error(Codes), Options),
  632    !,
  633    Codes = OutCodes.
  634print_error(OutCodes, _) :-
  635    phrase(classify_message(Level), OutCodes, _),
  636    print_message(Level, build(process_output(OutCodes))).
  637
  638classify_message(error) -->
  639    string(_), "fatal:",
  640    !.
  641classify_message(error) -->
  642    string(_), "error:",
  643    !.
  644classify_message(warning) -->
  645    string(_), "warning:",
  646    !.
  647classify_message(informational) -->
  648    [].
  649
  650
  651:- multifile user:file_search_path/2.  652user:file_search_path(pack_build_path, Dir) :-
  653    nb_current('$build_tool_env', Env),
  654    memberchk('PATH'=Path, Env),
  655    current_prolog_flag(path_sep, Sep),
  656    atomic_list_concat(Dirs, Sep, Path),
  657    member(Dir, Dirs),
  658    Dir \== ''.
  659
  660%!  has_program(+Spec) is semidet.
  661%!  has_program(+Spec, -Path) is semidet.
  662%!  has_program(+Spec, -Path, +Env:list) is semidet.
  663%
  664%   True when the OS has the program  Spec at the absolute file location
  665%   Path. Normally called as   e.g.  has_program(path(cmake), CMakeExe).
  666%   The second allows passing in an  environment as Name=Value pairs. If
  667%   this contains a value for ``PATH``,  this   is  used rather than the
  668%   current path variable.
  669
  670has_program(Prog) :-
  671    has_program(Prog, _).
  672has_program(Program, Path) :-
  673    has_program(Program, Path, []).
  674
  675has_program(path(Program), Path, Env), memberchk('PATH'=_, Env) =>
  676    setup_call_cleanup(
  677	b_setval('$build_tool_env', Env),
  678	has_program(pack_build_path(Program), Path, []),
  679	nb_delete('$build_tool_env')).
  680has_program(Name, Path, Env), plain_program_name(Name) =>
  681    has_program(path(Name), Path, Env).
  682has_program(Program, Path, _Env) =>
  683    exe_options(ExeOptions),
  684    absolute_file_name(Program, Path,
  685		       [ file_errors(fail)
  686		       | ExeOptions
  687		       ]).
  688
  689plain_program_name(Name) :-
  690    atom(Name),
  691    \+ sub_atom(Name, _, _, _, '/').
  692
  693exe_options(Options) :-
  694    current_prolog_flag(windows, true),
  695    !,
  696    Options = [ extensions(['',exe,com]), access(read) ].
  697exe_options(Options) :-
  698    Options = [ access(execute) ].
  699
  700
  701		 /*******************************
  702		 *             OS PATHS		*
  703		 *******************************/
  704
  705setup_path :-
  706    current_prolog_flag(windows, true),
  707    \+ current_prolog_flag(msys2, true),
  708    !,
  709    setup_path([make, gcc]).
  710setup_path.
  711
  712%!  setup_path(+Programs) is det.
  713%
  714%   Deals  with  specific  platforms  to  add  specific  directories  to
  715%   ``$PATH`` such that we can  find   the  tools.  Currently deals with
  716%   MinGW on Windows to provide `make` and `gcc`.
  717
  718setup_path(Programs) :-
  719    maplist(has_program, Programs).
  720setup_path(_) :-
  721    current_prolog_flag(windows, true),
  722    !,
  723    (   mingw_extend_path
  724    ->  true
  725    ;   print_message(error, build(no_mingw))
  726    ).
  727setup_path(_).
  728
  729%!  mingw_extend_path is semidet.
  730%
  731%   Check that gcc.exe is on ``%PATH%``  and if not, try to extend the
  732%   search path.
  733
  734mingw_extend_path :-
  735    absolute_file_name(path('gcc.exe'), _,
  736		       [ access(exist),
  737			 file_errors(fail)
  738		       ]),
  739    !.
  740mingw_extend_path :-
  741    mingw_root(MinGW),
  742    directory_file_path(MinGW, bin, MinGWBinDir),
  743    atom_concat(MinGW, '/msys/*/bin', Pattern),
  744    expand_file_name(Pattern, MsysDirs),
  745    last(MsysDirs, MSysBinDir),
  746    prolog_to_os_filename(MinGWBinDir, WinDirMinGW),
  747    prolog_to_os_filename(MSysBinDir, WinDirMSYS),
  748    getenv('PATH', Path0),
  749    atomic_list_concat([WinDirMSYS, WinDirMinGW, Path0], ';', Path),
  750    setenv('PATH', Path),
  751    print_message(informational,
  752		  build(mingw_extend_path(WinDirMSYS, WinDirMinGW))).
  753
  754mingw_root(MinGwRoot) :-
  755    current_prolog_flag(executable, Exe),
  756    sub_atom(Exe, 1, _, _, :),
  757    sub_atom(Exe, 0, 1, _, PlDrive),
  758    Drives = [PlDrive,c,d],
  759    member(Drive, Drives),
  760    format(atom(MinGwRoot), '~a:/MinGW', [Drive]),
  761    exists_directory(MinGwRoot),
  762    !.
  763
  764		 /*******************************
  765		 *            MESSAGES          *
  766		 *******************************/
  767
  768:- multifile prolog:message//1.  769
  770prolog:message(build(Msg)) -->
  771    message(Msg).
  772
  773message(no_mingw) -->
  774    [ 'Cannot find MinGW and/or MSYS.'-[] ].
  775message(process_output(Codes)) -->
  776    process_output(Codes).
  777message(step_failed(Step)) -->
  778    [ 'No build plugin could execute build step ~p'-[Step] ].
  779message(mingw_extend_path(WinDirMSYS, WinDirMinGW)) -->
  780    [ 'Extended %PATH% with ~p and ~p'-[WinDirMSYS, WinDirMinGW] ].
  781
  782%!  process_output(+Codes)//
  783%
  784%   Emit process output  using  print_message/2.   This  preserves  line
  785%   breaks.
  786
  787process_output([]) -->
  788    !.
  789process_output(Codes) -->
  790    { string_codes(String, Codes),
  791      split_string(String, "\n", "\r", Lines)
  792    },
  793    [ at_same_line ],
  794    process_lines(Lines).
  795
  796process_lines([H|T]) -->
  797    [ '~s'-[H] ],
  798    (   {T==[""]}
  799    ->  [nl]
  800    ;   {T==[]}
  801    ->  [flush]
  802    ;   [nl], process_lines(T)
  803    )