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:           http://www.swi-prolog.org
    6    Copyright (c)  2021, 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_conan,
   36          []).   37:- autoload(library(apply), [foldl/4]).   38:- autoload(library(filesex), [directory_file_path/3]).   39:- autoload(library(lists), [select/4, append/3]).   40:- autoload(library(readutil), [read_line_to_string/2]).   41:- autoload(library(build/tools), [ensure_build_dir/3, run_process/3]).   42:- autoload(library(dcg/basics), [whites/2, remainder/3]).   43
   44:- use_module(tools).

Support Conan dependency handling

Conan is a cross-platform package manager for (notably) C and C++. It can be used to get access to dependencies required by the pack. This notably provides an alternative for libraries that are either not well maintained by e.g., the Linux distributions or where the public versions are often outdated.

A conan step is excuted if a file conanfile.txt or conanfile.py is found. This plugin knows about conan virtualenv and if this is enabled it adds the environment settings from the generated vitualenv to the build process. */

   60:- multifile
   61    prolog:build_file/2,
   62    prolog:build_step/4,                % +Step, +Tool, +SrcDir, +BuildDir
   63    prolog:build_config/5.              % +Type, +Tool, +SrcDir, +BuildDir, -Config
   64
   65prolog:build_file('conanfile.txt',  conan).
   66prolog:build_file('conanfile.py',   conan).
   67
   68prolog:build_step(dependencies, conan, State0, State) :-
   69    ensure_build_dir(build, State0, State1),
   70    run_process(path(conan), ['install', '-b', missing, State1.src_dir],
   71                [ env(State1.env),
   72                  directory(State1.bin_dir)
   73                ]),
   74    load_conan_virtualenv(State1, State).
   75
   76load_conan_virtualenv(State0, State) :-
   77    directory_file_path(State0.bin_dir, 'environment.sh.env', ConanEnvFile),
   78    (   exists_file(ConanEnvFile)
   79    ->  import_environment(ConanEnvFile, State0.env, Env),
   80        State = State0.put(env,Env)
   81    ;   State = State0
   82    ).
 import_environment(+File, +Env0, -Env) is det
Extend the environment using settings from File. This currently aims at conan virtual environments. File is supposed to contain variable assignments in POSIX shell compatible syntax. Value assignments deals with single and double quotes as well as interpolated variables. Variable substitution deals with plain variables, ${VAR-Default}, ${VAR:-Default}, ${VAR+Alternative} and ${VAR:+Alternative}
   95import_environment(File, Env0, Env) :-
   96    setup_call_cleanup(
   97        open(File, read, In),
   98        join_environment(In, Env0, Env),
   99        close(In)).
  100
  101join_environment(In, Env0, Env) :-
  102    read_line_to_string(In, Line),
  103    (   Line == end_of_file
  104    ->  Env = Env0
  105    ;   join_line(Line, Env0, Env1),
  106        join_environment(In, Env1, Env)
  107    ).
  108
  109join_line(Line, Env0, Env) :-
  110    string_codes(Line, Codes),
  111    phrase(env_assigments(Assignments, Env0), Codes),
  112    foldl(env_assign, Assignments, Env0, Env).
  113
  114env_assign(Var=Value, Env0, Env) :-
  115    select(Var=_, Env0, Var=Value, Env),
  116    !.
  117env_assign(Var=Value, Env, [Var=Value|Env]).
  118
  119env_assigments([Var=Value|T], Env) -->
  120    whites,
  121    vname(Var), "=", !,
  122    var_value(ValueCodes, Env, -1),
  123    { atom_codes(Value, ValueCodes) },
  124    env_assigments(T, Env).
  125env_assigments([], _) -->
  126    whites,
  127    (   "#"
  128    ->  remainder(_)
  129    ;   []
  130    ).
  131
  132var_value(Codes, Env, EOF) -->
  133    "\"",
  134    !,
  135    dquoted(Codes, Tail, Env),
  136    var_value(Tail, Env, EOF).
  137var_value(Codes, Env, EOF) -->
  138    "\'",
  139    !,
  140    squoted(Codes, Tail),
  141    var_value(Tail, Env, EOF).
  142var_value(Codes, Env, EOF) -->
  143    "$",
  144    !,
  145    subst_var(Codes, Tail, Env),
  146    var_value(Tail, Env, EOF).
  147var_value([H|T], Env0, EOF) -->
  148    [H],
  149    { \+ (   H == EOF
  150         ;   H == -1,
  151             code_type(H, white)
  152         )
  153    },
  154    !,
  155    var_value(T, Env0, EOF).
  156var_value([], _, _) -->
  157    [].
  158
  159dquoted(Codes, Tail, _) -->
  160    "\"",
  161    !,
  162    { Tail = Codes }.
  163dquoted(Codes, Tail, Env) -->
  164    "$",
  165    !,
  166    subst_var(Codes, Tail0, Env),
  167    dquoted(Tail0, Tail, Env).
  168dquoted([H|T], Tail, Env) -->
  169    [H],
  170    dquoted(T, Tail, Env).
  171
  172squoted(Codes, Tail) -->
  173    "'",
  174    !,
  175    { Tail = Codes }.
  176squoted([H|T], Tail) -->
  177    [H],
  178    squoted(T, Tail).
  179
  180subst_var(Codes, Tail, Env) -->
  181    "{",
  182    !, vname(Name),
  183    var_default(Name, Env, Codes, Tail),
  184    "}".
  185subst_var(Codes, Tail, Env) -->
  186    vname(Name),
  187    {   memberchk(Name=Value, Env)
  188    ->  string_codes(Value, CodesC),
  189        append(CodesC, Tail, Codes)
  190    ;   Tail = Codes
  191    }.
  192
  193vname(Name) -->
  194    [C],
  195    { code_type(C, csymf) },
  196    vname_cont(Cs),
  197    { atom_codes(Name, [C|Cs]) }.
  198
  199vname_cont([H|T]) -->
  200    [H],
  201    { code_type(H, csym) },
  202    !,
  203    vname_cont(T).
  204vname_cont([]) -->
  205    [].
  206
  207var_default(Name, Env, Codes, Tail) -->
  208    var_def_sep(Op, Null),
  209    var_value(Default, Env, 0'}),
  210    {   Op == (-)
  211    ->  (   memberchk(Name=Value, Env),
  212            \+ isnull(Null, Value)
  213        ->  string_codes(Value, CodesC),
  214            append(CodesC, Tail, Codes)
  215        ;   append(Default, Tail, Codes)
  216        )
  217    ;   Op == (+),
  218        (   memberchk(Name=Value, Env),
  219            \+ isnull(Null, Value)
  220        ->  append(Default, Tail, Codes)
  221        ;   Tail = Codes
  222        )
  223    }.
  224
  225var_def_sep(-, false) --> "-".
  226var_def_sep(-, true)  --> ":-".
  227var_def_sep(+, false) --> "+".
  228var_def_sep(+, true)  --> ":+".
  229
  230isnull(false, _).
  231isnull(true, '').
  232isnull(true, "")