1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2018, VU University Amsterdam
    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(c_locations,
   36          [ c_lib_path/3,               % +Name, -Path, +Options
   37            cpp/2,                      % -Command, -Args
   38
   39            ldconfig/4,                 % ?Name, ?Path, ?Version, ?Flags
   40            ldconfig_flush/0
   41          ]).   42:- use_module(library(error)).   43:- use_module(library(readutil)).   44:- use_module(library(process)).   45:- use_module(library(apply)).   46:- use_module(library(option)).   47:- use_module(library(dcg/basics)).   48:- use_module(library(filesex)).

Define resource locations for the ffi library

This module provides the mapping from library names to concrete files that can be loaded. This is used by c_import/3. While C compilers typically allow one to specify a library as, e.g., -lm, the actual naming and physical location of the file providing this library is compiler and system dependent.

This module defines c_lib_path/2 to find the concrete file implementing a C library. Hooks may be used to extend this predicate:

   68:- multifile
   69    user:file_search_path/2,
   70    ffi:library_path_hook/3,                    % +Spec, -Path, +Options
   71    ffi:cpp_hook/2,				% -Command, -Argv
   72    ffi:compatible_architecture/1,
   73    ffi:cpu_alias/2.
 cpp(-Command, -Argv) is det
Provide the Command and Argv for process_create/3 to call the C proprocessor reading the C input from standard input.
   80cpp(Command, Argv) :-
   81    ffi:cpp_hook(Command, Argv),
   82    !.
   83cpp(path(gcc), ['-E', '-xc', -]).
 c_lib_path(+Spec, -Path, +Options) is det
Find a shared object from Spec. Spec is one of:
Concrete file
If spec is an atom or string denoting an existing file, this is used.
Alias(File)
Handled to absolute_file_name/3 using the options access(execute) and extensions(['',Ext]), where Ext is the value for the Prolog flag shared_object_extension
Plain atom
Platform dependent search. Currently implemented for
  • Systems that support ldconfig -p (e.g., Linux)

Additional search strategies may be realised by defining rules for library_path_hook/2 with the same signature.

To be done
- Extend the platform specific search strategies.
 ffi:library_path_hook(+Name, -Path, +Options) is semidet
Multifile hook that can be defined to resolve a library to a concrete file. The hook is tried as first option by c_lib_path/2.
  111c_lib_path(Name, Path, Options) :-
  112    ffi:library_path_hook(Name, Path, Options),
  113    !.
  114c_lib_path(Name, Path, Options) :-
  115    atomic(Name),
  116    relative_file(Name, AbsName, Options),
  117    add_extension(AbsName, File),
  118    exists_file(File),
  119    !,
  120    Path = File.
  121c_lib_path(Spec, Path, _Options) :-
  122    compound(Spec),
  123    !,
  124    find_on_path(Spec, Path).
  125c_lib_path(Name, Path, _Options) :-
  126    ldconfig(Name, Path),
  127    !.
  128c_lib_path(Spec, Path, _Options) :-
  129    find_on_path(c_lib(Spec), Path),
  130    !.
  131c_lib_path(libc, '/usr/lib/libSystem.B.dylib', _Options) :-
  132    current_prolog_flag(apple, true),           % MacOS 11 hack
  133    !.
  134c_lib_path(libm, '/usr/lib/libSystem.B.dylib', _Options) :-
  135    current_prolog_flag(apple, true),           % MacOS 11 hack
  136    !.
  137c_lib_path(Name, _Path, _Options) :-
  138    existence_error(c_library, Name).
  139
  140relative_file(Name, AbsName, _Options) :-
  141    is_absolute_file_name(Name),
  142    !,
  143    AbsName = Name.
  144relative_file(Name, AbsName, Options) :-
  145    option(relative_to(Dir), Options),
  146    !,
  147    add_arch(Dir, Dir1),
  148    directory_file_path(Dir1, Name, AbsName).
  149relative_file(Name, Name, _).
  150
  151add_extension(Name, Name).
  152add_extension(Base, Name) :-
  153    current_prolog_flag(shared_object_extension, Ext),
  154    file_name_extension(Base, Ext, Name).
  155
  156add_arch(Dir0, Dir) :-
  157    current_prolog_flag(arch, Arch),
  158    directory_file_path(Dir0, Arch, Dir).
  159add_arch(Dir, Dir).
  160
  161find_on_path(Spec, Path) :-
  162    current_prolog_flag(shared_object_extension, Ext),
  163    absolute_file_name(Spec, Path,
  164                       [ access(execute),
  165                         extensions(['',Ext]),
  166                         file_errors(fail)
  167                       ]).
  168
  169
  170user:file_search_path(c_lib, '/usr/lib').
  171
  172
  173		 /*******************************
  174		 *            LDCONFIG		*
  175		 *******************************/
 ldconfig(+Name, -Path) is semidet
Find the best matching library from the given base name
  181ldconfig(Name, Path) :-
  182    findall(l(Path, Version, Flags),
  183            ldconfig(Name, Path, Version, Flags),
  184            Candidates),
  185    (   Candidates = [One]
  186    ->  One = l(Path,_,_)
  187    ;   include(compatible, Candidates, Compatible),
  188        Compatible \== []
  189    ->  latest_version(Compatible, l(Path,_,_))
  190    ;   latest_version(Candidates, l(Path,_,_))
  191    ).
  192
  193compatible(l(_,_,Flags)) :-
  194    ffi:compatible_architecture(Flags),
  195    !.
  196compatible(l(_,_,Flags)) :-
  197    compatible_architecture(Flags).
  198
  199latest_version([One], One) :-
  200    !.
  201latest_version([H1,H2|T], Latest) :-
  202    version_list(H1, V1),
  203    version_list(H2, V2),
  204    (   later_version(V1, V2)
  205    ->  H = H1
  206    ;   H = H2
  207    ),
  208    latest_version([H|T], Latest).
  209
  210version_list(l(_,-1,_), [-1]) :-
  211    !.
  212version_list(l(_,V,_), L) :-
  213    split_string(V, ".", "", L0),
  214    maplist(try_number, L0, L).
  215
  216try_number(V, N) :-
  217    atom_number(V, N),
  218    !.
  219try_number(V, V).
  220
  221later_version([H|T1], [H|T2]) :-
  222    !,
  223    later_version(T1, T2).
  224later_version(V1, V2) :-
  225    V1 @> V2.
 ldconfig(?Name, ?Path, ?Version, ?Flags) is nondet
True when Name is the base name of a library in the ldconfig cache.
Arguments:
Name- is the base name of the library, without version or extension.
Path- is the absolute file name of the library
Version- is the version extension as an atom
Flags- is a list of atoms with flags about the library
  237:- dynamic
  238    ldconfig_cache/4,
  239    ldconfig_cache_loaded/1.  240
  241ldconfig(Name, Path, Version, Flags) :-
  242    ldconfig_cache_loaded(_),
  243    !,
  244    ldconfig_cache(Name, Path, Version, Flags).
  245ldconfig(Name, Path, Version, Flags) :-
  246    with_mutex(c_locations,
  247               import_ldconfig_cache),
  248    ldconfig_cache(Name, Path, Version, Flags).
 ldconfig_flush
Flush the library cache maintained for ldconfig.
  254ldconfig_flush :-
  255    retractall(ldconfig_cache(_,_,_,_)),
  256    retractall(ldconfig_cache_loaded(_)).
  257
  258import_ldconfig_cache :-
  259    ldconfig_cache_loaded(_), !.
  260import_ldconfig_cache :-
  261    ld_config_path(LdConfig),
  262    setup_call_cleanup(
  263        process_create(LdConfig, ['-p'],
  264                       [ stdout(pipe(Out))
  265                       ]),
  266        read_ldconfig(Out, 1),
  267        close(Out)),
  268    get_time(Now),
  269    asserta(ldconfig_cache_loaded(Now)).
  270
  271ld_config_path(Path) :-
  272    exists_file('/sbin/ldconfig'),
  273    !,
  274    Path = '/sbin/ldconfig'.
  275ld_config_path(Path) :-
  276    absolute_file_name(path(ldconfig), Path,
  277                       [ access(execute),
  278                         file_errors(fail)
  279                       ]).
  280
  281read_ldconfig(Out, Line) :-
  282    read_line_to_codes(Out, Codes),
  283    (   Codes == end_of_file
  284    ->  true
  285    ;   (   phrase(ldconfig_line(Name, Path, Version, Flags), Codes)
  286        ->  assertz(ldconfig_cache(Name, Path, Version, Flags))
  287        ;   Line == 1                   % first line may be comment
  288        ->  true
  289        ;   phrase(comment, Codes, _)   % Comment may also be elsewhere
  290        ->  true
  291        ;   print_message(warning, ldconfig(could_not_parse(Line, Codes)))
  292        ),
  293        Line2 is Line+1,
  294        read_ldconfig(Out, Line2)
  295    ).
  296
  297ldconfig_line(Name, Path, Version, Flags) -->
  298    whites,
  299    string(NameChars), ".",
  300    extension(_Ext),
  301    opt_version(Version), !,
  302    whites, "(", flags(Flags), ")", whites, "=>", whites, !,
  303    string(PathChars), eos, !,
  304    { atom_codes(Name, NameChars),
  305      atom_codes(Path, PathChars)
  306    }.
  307
  308extension(so)    --> "so".
  309extension(dylib) --> "dylib".
  310extension(dll)   --> "dll".
  311
  312opt_version(Version) -->
  313    ".", version(Versions), !,
  314    { atomic_list_concat(Versions, '.', Version) }.
  315opt_version(-1) --> white.
  316
  317version([H|T]) -->
  318    string(Chars),
  319    version_sep(Cont), !,
  320    { string_codes(H, Chars) },
  321    (   {Cont==true}
  322    ->  version(T)
  323    ;   {T=[]}
  324    ).
  325
  326version_sep(true) --> ".", !.
  327version_sep(false) --> white.
  328
  329flags([H|T]) -->
  330    string(Chars),
  331    flag_sep(Cont), !,
  332    { atom_codes(H, Chars) },
  333    (   {Cont == true}
  334    ->  flags(T)
  335    ;   {T=[]}
  336    ).
  337
  338flag_sep(true)  --> ",", !.
  339flag_sep(false), ")" --> ")", !.
  340
  341comment -->
  342    "Cache generated by:".
 compatible_architecture(+Flags)
Check the the library is compatible with the current SWI-Prolog architecture.
  350compatible_architecture(Flags) :-
  351    cpu(CPU),
  352    memberchk(CPU, Flags),
  353    !.
  354
  355cpu(CPU) :-
  356    current_prolog_flag(arch, Arch),
  357    split_string(Arch, "-", "", [CPUString|_]),
  358    atom_string(CPU0, CPUString),
  359    (   CPU = CPU0
  360    ;   ffi:cpu_alias(CPU0, CPU)
  361    ;   cpu_alias(CPU0, CPU)
  362    ).
 cpu_alias(+ArchCPU, -LDConfigCPU) is nondet
Provide a mapping from the CPU as known in the Prolog arch flag and the identifiers used by ldconfig.
  369cpu_alias(x86_64, 'x86-64').
  370
  371
  372		 /*******************************
  373		 *            MESSAGES		*
  374		 *******************************/
  375
  376:- multifile
  377    prolog:message//1.  378
  379prolog:message(ldconfig(could_not_parse(Line, Codes))) -->
  380    [ 'ldconfig import: ~d: could not parse ~s'-[Line, Codes] ]