View source with raw 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-2024, 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)

Utilities for building foreign resources

This module implements the build system that is used by pack_install/1 and pack_rebuild/1. The build system is a plugin based system where each plugin knows about a specific build toolchain. The plugins recognise whether they are applicable based on the existence of files that are unique to the toolchain. Currently it supports

 build_steps(+Steps:list, SrcDir:atom, +Options) is det
Run the desired build steps. Normally, Steps is the list below, optionally prefixed with distclean or clean. [test] may be omited if --no-test is effective.
[[dependencies], [configure], build, [test], install]

Each step finds an applicable toolchain based on known unique files and calls the matching plugin to perform the step. A step may fail, which causes the system to try an alternative. A step that wants to abort the build process must throw an exception.

If a step fails, a warning message is printed. The message can be suppressed by enclosing the step in square brackets. Thus, in the above example of Steps, only failure by the build and install steps result in warning messages; failure of the other steps is silent.

The failure of a step can be made into an error by enclosing it in curly brackets, e.g. [[dependencies], [configure], {build}, [test], {install}] would throw an exception if either the build or install step failed.

Options are:

pack_version(N)
where N is 1 or 2 (default: 1). This determines the form of environment names that are set before the build tools are calledd. For version 1, names such as SWIPLVERSION or SWIHOME are used. For version 2, names such as SWIPL_VERSION or SWIPL_HOME_DIR are used.

@tbd If no tool is willing to execute some step, the step is skipped. This is ok for some steps such as dependencies or test. Possibly we should force the install step to succeed?

  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.
 post_step(+Step, +State) is det
Run code after completion of a step.
  151post_step(Step, State) :-
  152    step_name(Step, configure),
  153    !,
  154    save_build_environment(State).
  155post_step(_, _).
 ensure_build_dir(+Dir, +State0, -State) is det
Create the build directory. Dir is normally either '.' to build in the source directory or build to create a build subdir.
  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		 *******************************/
 build_environment(-Env, +Options) is det
Options are documented under build_steps/3.

Assemble a clean build environment for creating extensions to SWI-Prolog. Env is a list of Var=Value pairs. The variable names depend on the pack_version(Version) term from pack.pl. When absent or 1, the old names are used. These names are confusing and conflict with some build environments. Using 2 (or later), the new names are used. The list below first names the new name and than between parenthesis, the old name. Provided variables are:

PATH
contains the environment path with the directory holding the currently running SWI-Prolog instance prepended in front of it. As a result, swipl is always present and runs the same SWI-Prolog instance as the current Prolog process.
SWIPL
contains the absolute file name of the running executable.
SWIPL_PACK_VERSION
Version of the pack system (1 or 2)
SWIPL_VERSION (SWIPLVERSION)
contains the numeric SWI-Prolog version defined as Major*10000+Minor*100+Patch.
SWIPL_HOME_DIR (SWIHOME)
contains the directory holding the SWI-Prolog home.
SWIPL_ARCH (SWIARCH)
contains the machine architecture identifier.
SWIPL_MODULE_DIR (PACKSODIR)
constains the destination directory for shared objects/DLLs relative to a Prolog pack, i.e., lib/$SWIARCH.
SWIPL_MODULE_LIB (SWISOLIB)
The SWI-Prolog library or an empty string when it is not required to link modules against this library (e.g., ELF systems)
SWIPL_LIB (SWILIB)
The SWI-Prolog library we need to link to for programs that embed SWI-Prolog (normally -lswipl).
SWIPL_INCLUDE_DIRS
CMake style variable that contains the directory holding SWI-Prolog.h, SWI-Stream.h and SWI-cpp.h.
SWIPL_LIBRARIES_DIR
CMake style variable that contains the directory holding libswipl
SWIPL_CC (CC)
Prefered C compiler
SWIPL_CXX (CXX)
Prefered C++ compiler
SWIPL_LD (LD)
Prefered linker
SWIPL_CFLAGS (CFLAGS)
C-Flags for building extensions. Always contains -ISWIPL-INCLUDE-DIR.
SWIPL_MODULE_LDFLAGS (LDSOFLAGS)
Link flags for linking modules.
SWIPL_MODULE_EXT (SOEXT)
File name extension for modules (e.g., so or dll)
SWIPL_PREFIX (PREFIX)
Install prefix for global binaries, libraries and include files.
  238build_environment(Env, Options) :-
  239    findall(Name=Value,
  240	    distinct(Name, user_environment(Name, Value)),
  241	    UserEnv),
  242    findall(Name=Value,
  243	    ( def_environment(Name, Value, Options),
  244	      \+ memberchk(Name=_, UserEnv)
  245	    ),
  246	    DefEnv),
  247    append(UserEnv, DefEnv, Env).
  248
  249user_environment(Name, Value) :-
  250    prolog:build_environment(Name, Value).
  251user_environment(Name, Value) :-
  252    prolog_pack:environment(Name, Value).
 prolog:build_environment(-Name, -Value) is nondet
Hook to define the environment for building packs. This Multifile hook extends the process environment for building foreign extensions. A value provided by this hook overrules defaults provided by def_environment/3. In addition to changing the environment, this may be used to pass additional values to the environment, as in:
prolog:build_environment('USER', User) :-
    getenv('USER', User).
Arguments:
Name- is an atom denoting a valid variable name
Value- is either an atom or number representing the value of the variable.
 def_environment(-Name, -Value, +Options) is nondet
True if Name=Value must appear in the environment for building foreign extensions.
  278def_environment('PATH', Value, _) :-
  279    getenv('PATH', PATH),
  280    current_prolog_flag(executable, Exe),
  281    file_directory_name(Exe, ExeDir),
  282    prolog_to_os_filename(ExeDir, OsExeDir),
  283    current_prolog_flag(path_sep, Sep),
  284    atomic_list_concat([OsExeDir, Sep, PATH], Value).
  285def_environment('SWIPL', Value, _) :-
  286    current_prolog_flag(executable, Value).
  287def_environment('SWIPL_PACK_VERSION', Value, Options) :-
  288    option(pack_version(Value), Options, 1).
  289def_environment('SWIPL_PACK_PATH', Value, _Options) :-
  290    prolog_config(pack_path, Value).
  291def_environment(VAR, Value, Options) :-
  292    env_name(version, VAR, Options),
  293    current_prolog_flag(version, Value).
  294def_environment(VAR, Value, Options) :-
  295    env_name(home, VAR, Options),
  296    current_prolog_flag(home, Value).
  297def_environment(VAR, Value, Options) :-
  298    env_name(arch, VAR, Options),
  299    current_prolog_flag(arch, Value).
  300def_environment(VAR, Value, Options) :-
  301    env_name(module_dir, VAR, Options),
  302    current_prolog_flag(arch, Arch),
  303    atom_concat('lib/', Arch, Value).
  304def_environment(VAR, Value, Options) :-
  305    env_name(module_lib, VAR, Options),
  306    current_prolog_flag(c_libplso, Value).
  307def_environment(VAR, '-lswipl', Options) :-
  308    env_name(lib, VAR, Options).
  309def_environment(VAR, Value, Options) :-
  310    env_name(cc, VAR, Options),
  311    default_c_compiler(Value).
  312def_environment(VAR, Value, Options) :-
  313    env_name(cxx, VAR, Options),
  314    default_cxx_compiler(Value).
  315def_environment(VAR, Value, Options) :-
  316    env_name(ld, VAR, Options),
  317    (   getenv('LD', Value)
  318    ->  true
  319    ;   default_c_compiler(Value)
  320    ).
  321def_environment('SWIPL_INCLUDE_DIRS', Value, _) :- % CMake style environment
  322    current_prolog_flag(home, Home),
  323    atom_concat(Home, '/include', Value).
  324def_environment('SWIPL_LIBRARIES_DIR', Value, _) :-
  325    swipl_libraries_dir(Value).
  326def_environment(VAR, Value, Options) :-
  327    env_name(cflags, VAR, Options),
  328    (   getenv('CFLAGS', SystemFlags)
  329    ->  Extra = [' ', SystemFlags]
  330    ;   Extra = []
  331    ),
  332    current_prolog_flag(c_cflags, Value0),
  333    current_prolog_flag(home, Home),
  334    atomic_list_concat([Value0, ' -I"', Home, '/include"' | Extra], Value).
  335def_environment(VAR, Value, Options) :-
  336    env_name(module_ldflags, VAR, Options),
  337    (   getenv('LDFLAGS', SystemFlags)
  338    ->  Extra = [SystemFlags|System]
  339    ;   Extra = System
  340    ),
  341    (   current_prolog_flag(windows, true)
  342    ->  prolog_library_dir(LibDir),
  343	atomic_list_concat(['-L"', LibDir, '"'], SystemLib),
  344	System = [SystemLib]
  345    ;   prolog_config(apple_bundle_libdir, LibDir)
  346    ->  atomic_list_concat(['-L"', LibDir, '"'], SystemLib),
  347	System = [SystemLib]
  348    ;   current_prolog_flag(c_libplso, '')
  349    ->  System = []                 % ELF systems do not need this
  350    ;   prolog_library_dir(SystemLibDir),
  351	atomic_list_concat(['-L"',SystemLibDir,'"'], SystemLib),
  352	System = [SystemLib]
  353    ),
  354    current_prolog_flag(c_ldflags, LDFlags),
  355    atomic_list_concat([LDFlags, '-shared' | Extra], ' ', Value).
  356def_environment(VAR, Value, Options) :-
  357    env_name(module_ext, VAR, Options),
  358    current_prolog_flag(shared_object_extension, Value).
  359def_environment(VAR, Value, Options) :-
  360    env_name(prefix, VAR, Options),
  361    prolog_install_prefix(Value).
  362
  363swipl_libraries_dir(Dir) :-
  364    current_prolog_flag(windows, true),
  365    !,
  366    current_prolog_flag(home, Home),
  367    atom_concat(Home, '/bin', Dir).
  368swipl_libraries_dir(Dir) :-
  369    prolog_config(apple_bundle_libdir, Dir),
  370    !.
  371swipl_libraries_dir(Dir) :-
  372    prolog_library_dir(Dir).
  373
  374env_name(Id, Name, Options) :-
  375    option(pack_version(V), Options, 1),
  376    must_be(oneof([1,2]), V),
  377    env_name_v(Id, V, Name).
  378
  379env_name_v(version,        1, 'SWIPLVERSION').
  380env_name_v(version,        2, 'SWIPL_VERSION').
  381env_name_v(home,           1, 'SWIHOME').
  382env_name_v(home,           2, 'SWIPL_HOME_DIR').
  383env_name_v(module_dir,     1, 'PACKSODIR').
  384env_name_v(module_dir,     2, 'SWIPL_MODULE_DIR').
  385env_name_v(module_lib,     1, 'SWISOLIB').
  386env_name_v(module_lib,     2, 'SWIPL_MODULE_LIB').
  387env_name_v(lib,            1, 'SWILIB').
  388env_name_v(lib,            2, 'SWIPL_LIB').
  389env_name_v(arch,           1, 'SWIARCH').
  390env_name_v(arch,           2, 'SWIPL_ARCH').
  391env_name_v(cc,             1, 'CC').
  392env_name_v(cc,             2, 'SWIPL_CC').
  393env_name_v(cxx,            1, 'CXX').
  394env_name_v(cxx,            2, 'SWIPL_CXX').
  395env_name_v(ld,             1, 'LD').
  396env_name_v(ld,             2, 'SWIPL_LD').
  397env_name_v(cflags,         1, 'CFLAGS').
  398env_name_v(cflags,         2, 'SWIPL_CFLAGS').
  399env_name_v(module_ldflags, 1, 'LDSOFLAGS').
  400env_name_v(module_ldflags, 2, 'SWIPL_MODULE_LDFLAGS').
  401env_name_v(module_ext,     1, 'SOEXT').
  402env_name_v(module_ext,     2, 'SWIPL_MODULE_EXT').
  403env_name_v(prefix,         1, 'PREFIX').
  404env_name_v(prefix,         2, 'SWIPL_PREFIX').
 prolog_library_dir(-Dir) is det
True when Dir is the directory holding libswipl.$SOEXT
  410:- multifile
  411    prolog:runtime_config/2.  412
  413prolog_library_dir(Dir) :-
  414    prolog:runtime_config(c_libdir, Dir),
  415    !.
  416prolog_library_dir(Dir) :-
  417    current_prolog_flag(windows, true),
  418    \+ current_prolog_flag(msys2, true),
  419    current_prolog_flag(home, Home),
  420    !,
  421    atomic_list_concat([Home, bin], /, Dir).
  422prolog_library_dir(Dir) :-
  423    current_prolog_flag(home, Home),
  424    (   current_prolog_flag(c_libdir, Rel)
  425    ->  atomic_list_concat([Home, Rel], /, Dir)
  426    ;   current_prolog_flag(arch, Arch)
  427    ->  atomic_list_concat([Home, lib, Arch], /, Dir)
  428    ).
 default_c_compiler(-CC) is semidet
Try to find a suitable C compiler for compiling packages with foreign code.
To be done
- Needs proper defaults for Windows. Find MinGW? Find MSVC?
  437default_c_compiler(CC) :-
  438    getenv('CC', CC),
  439    !.
  440default_c_compiler(CC) :-
  441    preferred_c_compiler(CC0),
  442    has_program(CC0, CC),
  443    !.
  444
  445default_cxx_compiler(CXX) :-
  446    getenv('CXX', CXX),
  447    !.
  448default_cxx_compiler(CXX) :-
  449    preferred_cxx_compiler(CXX0),
  450    has_program(CXX0, CXX),
  451    !.
  452
  453preferred_c_compiler(CC) :-
  454    current_prolog_flag(c_cc, CC).
  455preferred_c_compiler(gcc).
  456preferred_c_compiler(clang).
  457preferred_c_compiler(cc).
  458
  459preferred_cxx_compiler(CXX) :-
  460    current_prolog_flag(c_cxx, CXX).
  461preferred_cxx_compiler('g++').
  462preferred_cxx_compiler('clang++').
  463preferred_cxx_compiler('c++').
 save_build_environment(+State:dict) is det
Create a shell-script buildenv.sh that contains the build environment. This may be sourced in the build directory to run the build steps outside Prolog. It may also be useful for debugging purposes.
  473:- det(save_build_environment/1).  474save_build_environment(State) :-
  475    Env = State.get(env),
  476    !,
  477    (   BuildDir = State.get(bin_dir)
  478    ->  true
  479    ;   BuildDir = State.get(src_dir)
  480    ),
  481    directory_file_path(BuildDir, 'buildenv.sh', EnvFile),
  482    setup_call_cleanup(
  483	open(EnvFile, write, Out),
  484	write_env_script(Out, Env),
  485	close(Out)).
  486save_build_environment(_).
  487
  488write_env_script(Out, Env) :-
  489    format(Out,
  490	   '# This file contains the environment that can be used to\n\c
  491	    # build the foreign pack outside Prolog.  This file must\n\c
  492	    # be loaded into a bourne-compatible shell using\n\c
  493	    #\n\c
  494	    #   $ source buildenv.sh\n\n',
  495	   []),
  496    forall(member(Var=Value, Env),
  497	   format(Out, '~w=\'~w\'\n', [Var, Value])),
  498    format(Out, '\nexport ', []),
  499    forall(member(Var=_, Env),
  500	   format(Out, ' ~w', [Var])),
  501    format(Out, '\n', []).
 prolog_install_prefix(-Prefix) is semidet
Return the directory that can be passed into configure or cmake to install executables and other related resources in a similar location as SWI-Prolog itself. Tries these rules:
  1. If the Prolog flag pack_prefix at a writable directory, use this.
  2. If the current executable can be found on $PATH and the parent of the directory of the executable is writable, use this.
  3. If the user has a writable ~/bin directory, use ~.
  515prolog_install_prefix(Prefix) :-
  516    current_prolog_flag(pack_prefix, Prefix),
  517    access_file(Prefix, write),
  518    !.
  519prolog_install_prefix(Prefix) :-
  520    current_prolog_flag(os_argv, [Name|_]),
  521    has_program(path(Name), EXE),
  522    file_directory_name(EXE, Bin),
  523    file_directory_name(Bin, Prefix0),
  524    (   local_prefix(Prefix0, Prefix1)
  525    ->  Prefix = Prefix1
  526    ;   Prefix = Prefix0
  527    ),
  528    access_file(Prefix, write),
  529    !.
  530prolog_install_prefix(Prefix) :-
  531    expand_file_name(~, [UserHome]),
  532    directory_file_path(UserHome, bin, BinDir),
  533    exists_directory(BinDir),
  534    access_file(BinDir, write),
  535    !,
  536    Prefix = UserHome.
  537
  538local_prefix('/usr', '/usr/local').
  539
  540
  541		 /*******************************
  542		 *          RUN PROCESSES       *
  543		 *******************************/
 run_process(+Executable, +Argv, +Options) is det
Run Executable. Defined options:
directory(+Dir)
Execute in the given directory
output(-Out)
Unify Out with a list of codes representing stdout of the command. Otherwise the output is handed to print_message/2 with level informational.
error(-Error)
As output(Out), but messages are printed at level error.
env(+Environment)
Environment passed to the new process.

If Executable is path(Program) and we have an environment we make sure to use the PATH from this environment for searching Program.

  564run_process(path(Exe), Argv, Options) :-
  565    option(env(BuildEnv), Options),
  566    !,
  567    setup_call_cleanup(
  568	b_setval('$build_tool_env', BuildEnv),
  569	run_process(pack_build_path(Exe), Argv, Options),
  570	nb_delete('$build_tool_env')).
  571run_process(Executable, Argv, Options) :-
  572    \+ option(output(_), Options),
  573    \+ option(error(_), Options),
  574    current_prolog_flag(unix, true),
  575    current_prolog_flag(threads, true),
  576    !,
  577    process_create_options(Options, Extra),
  578    process_create(Executable, Argv,
  579		   [ stdout(pipe(Out)),
  580		     stderr(pipe(Error)),
  581		     process(PID)
  582		   | Extra
  583		   ]),
  584    thread_create(relay_output([output-Out, error-Error]), Id, []),
  585    process_wait(PID, Status),
  586    thread_join(Id, _),
  587    (   Status == exit(0)
  588    ->  true
  589    ;   throw(error(process_error(process(Executable, Argv), Status), _))
  590    ).
  591run_process(Executable, Argv, Options) :-
  592    process_create_options(Options, Extra),
  593    setup_call_cleanup(
  594	process_create(Executable, Argv,
  595		       [ stdout(pipe(Out)),
  596			 stderr(pipe(Error)),
  597			 process(PID)
  598		       | Extra
  599		       ]),
  600	(   read_stream_to_codes(Out, OutCodes, []),
  601	    read_stream_to_codes(Error, ErrorCodes, []),
  602	    process_wait(PID, Status)
  603	),
  604	(   close(Out),
  605	    close(Error)
  606	)),
  607    print_error(ErrorCodes, Options),
  608    print_output(OutCodes, Options),
  609    (   Status == exit(0)
  610    ->  true
  611    ;   throw(error(process_error(process(Executable, Argv), Status), _))
  612    ).
  613
  614process_create_options(Options, Extra) :-
  615    option(directory(Dir), Options, .),
  616    (   option(env(Env), Options)
  617    ->  Extra = [cwd(Dir), environment(Env)]
  618    ;   Extra = [cwd(Dir)]
  619    ).
  620
  621relay_output([]) :- !.
  622relay_output(Output) :-
  623    pairs_values(Output, Streams),
  624    wait_for_input(Streams, Ready, infinite),
  625    relay(Ready, Output, NewOutputs),
  626    relay_output(NewOutputs).
  627
  628relay([], Outputs, Outputs).
  629relay([H|T], Outputs0, Outputs) :-
  630    selectchk(Type-H, Outputs0, Outputs1),
  631    (   at_end_of_stream(H)
  632    ->  close(H),
  633	relay(T, Outputs1, Outputs)
  634    ;   read_pending_codes(H, Codes, []),
  635	relay(Type, Codes),
  636	relay(T, Outputs0, Outputs)
  637    ).
  638
  639relay(error,  Codes) :-
  640    set_prolog_flag(message_context, []),
  641    print_error(Codes, []).
  642relay(output, Codes) :-
  643    print_output(Codes, []).
  644
  645print_output(OutCodes, Options) :-
  646    option(output(Codes), Options),
  647    !,
  648    Codes = OutCodes.
  649print_output(OutCodes, _) :-
  650    print_message(informational, build(process_output(OutCodes))).
  651
  652print_error(OutCodes, Options) :-
  653    option(error(Codes), Options),
  654    !,
  655    Codes = OutCodes.
  656print_error(OutCodes, _) :-
  657    phrase(classify_message(Level), OutCodes, _),
  658    print_message(Level, build(process_output(OutCodes))).
  659
  660classify_message(error) -->
  661    string(_), "fatal:",
  662    !.
  663classify_message(error) -->
  664    string(_), "error:",
  665    !.
  666classify_message(warning) -->
  667    string(_), "warning:",
  668    !.
  669classify_message(informational) -->
  670    [].
  671
  672
  673:- multifile user:file_search_path/2.  674user:file_search_path(pack_build_path, Dir) :-
  675    nb_current('$build_tool_env', Env),
  676    memberchk('PATH'=Path, Env),
  677    current_prolog_flag(path_sep, Sep),
  678    atomic_list_concat(Dirs, Sep, Path),
  679    member(Dir, Dirs),
  680    Dir \== ''.
 has_program(+Spec) is semidet
 has_program(+Spec, -Path) is semidet
 has_program(+Spec, -Path, +Env:list) is semidet
True when the OS has the program Spec at the absolute file location Path. Normally called as e.g. has_program(path(cmake), CMakeExe). The second allows passing in an environment as Name=Value pairs. If this contains a value for PATH, this is used rather than the current path variable.
  692has_program(Prog) :-
  693    has_program(Prog, _).
  694has_program(Program, Path) :-
  695    has_program(Program, Path, []).
  696
  697has_program(path(Program), Path, Env), memberchk('PATH'=_, Env) =>
  698    setup_call_cleanup(
  699	b_setval('$build_tool_env', Env),
  700	has_program(pack_build_path(Program), Path, []),
  701	nb_delete('$build_tool_env')).
  702has_program(Name, Path, Env), plain_program_name(Name) =>
  703    has_program(path(Name), Path, Env).
  704has_program(Program, Path, _Env) =>
  705    exe_options(ExeOptions),
  706    absolute_file_name(Program, Path,
  707		       [ file_errors(fail)
  708		       | ExeOptions
  709		       ]).
  710
  711plain_program_name(Name) :-
  712    atom(Name),
  713    \+ sub_atom(Name, _, _, _, '/').
  714
  715exe_options(Options) :-
  716    current_prolog_flag(windows, true),
  717    !,
  718    Options = [ extensions(['',exe,com]), access(read) ].
  719exe_options(Options) :-
  720    Options = [ access(execute) ].
  721
  722
  723		 /*******************************
  724		 *             OS PATHS		*
  725		 *******************************/
  726
  727setup_path :-
  728    current_prolog_flag(windows, true),
  729    \+ current_prolog_flag(msys2, true),
  730    !,
  731    setup_path([make, gcc]).
  732setup_path.
 setup_path(+Programs) is det
Deals with specific platforms to add specific directories to $PATH such that we can find the tools. Currently deals with MinGW on Windows to provide make and gcc.
  740setup_path(Programs) :-
  741    maplist(has_program, Programs).
  742setup_path(_) :-
  743    current_prolog_flag(windows, true),
  744    !,
  745    (   mingw_extend_path
  746    ->  true
  747    ;   print_message(error, build(no_mingw))
  748    ).
  749setup_path(_).
 mingw_extend_path is semidet
Check that gcc.exe is on %PATH% and if not, try to extend the search path.
  756mingw_extend_path :-
  757    absolute_file_name(path('gcc.exe'), _,
  758		       [ access(exist),
  759			 file_errors(fail)
  760		       ]),
  761    !.
  762mingw_extend_path :-
  763    mingw_root(MinGW),
  764    directory_file_path(MinGW, bin, MinGWBinDir),
  765    atom_concat(MinGW, '/msys/*/bin', Pattern),
  766    expand_file_name(Pattern, MsysDirs),
  767    last(MsysDirs, MSysBinDir),
  768    prolog_to_os_filename(MinGWBinDir, WinDirMinGW),
  769    prolog_to_os_filename(MSysBinDir, WinDirMSYS),
  770    getenv('PATH', Path0),
  771    atomic_list_concat([WinDirMSYS, WinDirMinGW, Path0], ';', Path),
  772    setenv('PATH', Path),
  773    print_message(informational,
  774		  build(mingw_extend_path(WinDirMSYS, WinDirMinGW))).
  775
  776mingw_root(MinGwRoot) :-
  777    current_prolog_flag(executable, Exe),
  778    sub_atom(Exe, 1, _, _, :),
  779    sub_atom(Exe, 0, 1, _, PlDrive),
  780    Drives = [PlDrive,c,d],
  781    member(Drive, Drives),
  782    format(atom(MinGwRoot), '~a:/MinGW', [Drive]),
  783    exists_directory(MinGwRoot),
  784    !.
  785
  786		 /*******************************
  787		 *            MESSAGES          *
  788		 *******************************/
  789
  790:- multifile prolog:message//1.  791
  792prolog:message(build(Msg)) -->
  793    message(Msg).
  794
  795message(no_mingw) -->
  796    [ 'Cannot find MinGW and/or MSYS.'-[] ].
  797message(process_output(Codes)) -->
  798    process_output(Codes).
  799message(step_failed(Step)) -->
  800    [ 'No build plugin could execute build step ~p'-[Step] ].
  801message(mingw_extend_path(WinDirMSYS, WinDirMinGW)) -->
  802    [ 'Extended %PATH% with ~p and ~p'-[WinDirMSYS, WinDirMinGW] ].
 process_output(+Codes)//
Emit process output using print_message/2. This preserves line breaks.
  809process_output([]) -->
  810    !.
  811process_output(Codes) -->
  812    { string_codes(String, Codes),
  813      split_string(String, "\n", "\r", Lines)
  814    },
  815    [ at_same_line ],
  816    process_lines(Lines).
  817
  818process_lines([H|T]) -->
  819    [ '~s'-[H] ],
  820    (   {T==[""]}
  821    ->  [nl]
  822    ;   {T==[]}
  823    ->  [flush]
  824    ;   [nl], process_lines(T)
  825    )