View source with formatted comments or as raw
    1/*  Part of ClioPatria SeRQL and SPARQL server
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2010-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(conf_d,
   36          [ load_conf_d/2,              % +Directories, +Options
   37            conf_d_enabled/1,           % -ConfDir
   38            conf_d_reload/0,
   39            conf_d_members/3,           % +Directory, -FileData, +Options
   40            conf_d_member_data/3,       % ?Field, +FileData, -Value
   41            conf_d_configuration/3      % +Available, +Enabled, -Configs
   42          ]).   43:- use_module(library(option)).   44:- use_module(library(ordsets)).   45:- use_module(library(lists)).   46:- use_module(library(apply)).   47:- use_module(library(version)).   48:- use_module(library(prolog_xref)).   49:- if(exists_source(library(pldoc/doc_process))).   50:- use_module(library(pldoc)).   51:- use_module(library(pldoc/doc_process)).   52:- endif.   53
   54/** <module> Load configuration directories
   55
   56This module deals with  loading   configuration-files  from a directory.
   57This is pretty simple because  we   assume  that configuration files are
   58Prolog  source-files.  We  (can)  use    file_search_path/2   to  define
   59one or more configuration directories.
   60
   61Files are loaded in alphabetical  order.   If  one  config file requires
   62another, there are two solutions:
   63
   64    * Use some numbering scheme, e.g., name the files 00-prefixes.pl,
   65    01-paths.pl, etc.
   66    * Use a use_module/1 call to include the config file(s) on which we
   67    depend.
   68*/
   69
   70%!  load_conf_d(+Spec, +Options) is det.
   71%
   72%   Locate configuration directories and load   their  config files.
   73%   Config files themselves are Prolog source files.  Options:
   74%
   75%       * solutions(+Sols)
   76%       Passed to absolute_file_name/3.  Default is =all=, loading
   77%       config files from all directories described by Spec.
   78%       * extension(+Ext)
   79%       File-name extension for the config files.  Default is =pl=.
   80%
   81%   Other options are passed to load_files/2.
   82%
   83%   @param  Spec is either the specification of a directory according
   84%           to absolute_file_name/3 or a list thereof.  Duplicate
   85%           directories are removed.
   86%   @tbd    There is a bug forking processes in one thread and
   87%           waiting for X11 in another, which deadlocks in
   88%           fork_atfree().  So, we must ensure we have the git
   89%           versions in time :-(
   90
   91load_conf_d(Spec, Options) :-
   92    set_top_dir,
   93    select_option(solutions(Sols), Options, LoadOptions0, all),
   94    merge_options(LoadOptions0,
   95                  [ if(changed),
   96                    extension(pl)
   97                  ], LoadOptions),
   98    phrase(collect_dirs(Spec, Sols), Dirs),
   99    list_to_set(Dirs, Set),
  100    maplist(conf_d_files(Options), Set, Pairs),
  101    keep_last(Pairs, Final),
  102    maplist(load_conf_dir(LoadOptions), Final),
  103    git_update_versions(_).         % See above
  104
  105collect_dirs([], _) --> !.
  106collect_dirs([H|T], Sols) -->
  107    !,
  108    collect_dirs(H, Sols),
  109    collect_dirs(T, Sols).
  110collect_dirs(Spec, Sols) -->
  111    findall(Dir, absolute_file_name(Spec, Dir,
  112                                    [ file_type(directory),
  113                                      file_errors(fail),
  114                                      access(read),
  115                                      solutions(Sols)
  116                                    ])).
  117
  118
  119:- dynamic
  120    conf_d/3.                       % Directory, Options, Files
  121
  122load_conf_dir(Options, Dir-Files) :-
  123    delete(Options, extension(_), LoadOptions),
  124    update_conf_d(Dir, Files, Options),
  125    maplist(load_conf(LoadOptions), Files).
  126
  127load_conf(Options, File) :-
  128    print_message(informational, conf_d(load(File))),
  129    load_files(user:File, [module(File)|Options]).
  130
  131conf_d_files(Options, Dir, Dir-Files) :-
  132    option(extension(Ext), Options, pl),
  133    atomic_list_concat([Dir, '/*.', Ext], Pattern),
  134    expand_file_name(Pattern, Matches),
  135    include(accessible, Matches, MatchedFiles),
  136    maplist(absolute_file_name, MatchedFiles, CanonicalFiles),
  137    sort(CanonicalFiles, Files).
  138
  139accessible(File) :-
  140    access_file(File, read).
  141
  142%!  keep_last(+PairsIn, -PairsOut) is det.
  143%
  144%   PairsIn is a list Dir-Files holding Files to be loaded from Dir.
  145%   We remove all  files  from  Files   that  appear  with  a  later
  146%   directory.
  147
  148keep_last([], []).
  149keep_last([Dir-Files0|T0], [Dir-Files|T]) :-
  150    exclude(in_later_dir(T0), Files0, Files),
  151    keep_last(T0, T).
  152
  153in_later_dir(Pairs, File) :-
  154    file_base_name(File, Base),
  155    \+ multi(Base),
  156    member(_-Files, Pairs),
  157    member(F2, Files),
  158    file_base_name(F2, Base).
  159
  160multi('010-packs.pl').
  161
  162update_conf_d(Dir, Files, Options) :-
  163    \+ conf_d(Dir, _, _),
  164    !,
  165    assert(conf_d(Dir, Options, Files)).
  166update_conf_d(Dir, Files, Options) :-
  167    retract(conf_d(Dir, _, OldFiles)),
  168    !,
  169    ord_subtract(OldFiles, Files, Removed),
  170    (   Removed \== []
  171    ->  print_message(informational, conf_d(unload(Removed))),
  172        catch(maplist(unload_file, Removed), E,
  173              print_message(error, E))
  174    ;   true
  175    ),
  176    ord_subtract(Files, OldFiles, New),
  177    (   New \== []
  178    ->  print_message(informational, conf_d(new(New)))
  179    ;   true
  180    ),
  181    assert(conf_d(Dir, Options, Files)).
  182
  183%!  conf_d_enabled(-Dir) is nondet.
  184%
  185%   True if Dir is a directory from which config files are loaded.
  186
  187conf_d_enabled(Dir) :-
  188    conf_d(Dir, _, _).
  189
  190%!  conf_d_reload is det.
  191%
  192%   Reload configuration files  after  adding   or  deleting  config
  193%   files. Note that this is not exactly  the same as restarting the
  194%   server. First of all, the order in   which  the files are loaded
  195%   may be different and second, wiping a config file only wipes the
  196%   clauses and module. Side effects, for   example  due to executed
  197%   directives, are *not* reverted.
  198
  199conf_d_reload :-
  200    findall(Dir-Options-Files, conf_d(Dir, Options, Files), Triples),
  201    forall(member(Dir-Options-Files, Triples),
  202           load_conf_dir(Options, Dir-Files)).
  203
  204%!  conf_d_members(+Dir, -InfoRecords:list, Options) is det
  205%
  206%   Provide information about config files in Dir.
  207%
  208%   @param InfoRecords is a list of terms. The predicate
  209%   conf_d_member_data/3 must be used to extract data from these
  210%   terms.
  211
  212conf_d_members(DirSpec, InfoRecords, Options) :-
  213    findall(Files,
  214            ( absolute_file_name(DirSpec, Dir,
  215                                 [ file_type(directory),
  216                                   solutions(all)
  217                                 ]),
  218              conf_d_files(Dir, Files, Options)
  219            ), FileLists),
  220    append(FileLists, Files0),
  221    sort(Files0, Files), % remove duplicates introduced by absolute & relative ClioPatria paths
  222    maplist(conf_file, Files, InfoRecords).
  223
  224conf_file(File, config_file(Path, Module, Title)) :-
  225    xref_public_list(File, Path, Module, _Public, _Meta, []),
  226    !,
  227    (   current_predicate(doc_comment/4),
  228        doc_comment(_:module(Title), Path:_, _Summary, _Comment)
  229    ->  true
  230    ;   true
  231    ).
  232conf_file(File, config_file(File, _Module, _Title)).
  233
  234%!  conf_d_member_data(?Field, +ConfigInfo, ?Value) is nondet.
  235%
  236%   True if Value is the value   for Field in ConfigInfo. ConfigInfo
  237%   is an opaque term as returned   by conf_d_info/3. Defined fields
  238%   are:
  239%
  240%       * file
  241%       Absolute path of the file
  242%       * module
  243%       Module defined in the file (can fail)
  244%       * title
  245%       Comment-title (from /** <module> Title .. */)
  246%       * loaded
  247%       Boolean, indicating whether the file is currently loaded.
  248
  249conf_d_member_data(file,   config_file(F, _, _), F).
  250conf_d_member_data(module, config_file(_, M, _), M) :- nonvar(M).
  251conf_d_member_data(title,  config_file(_, _, T), T) :- nonvar(T).
  252conf_d_member_data(loaded, config_file(F, _, _), B) :-
  253    (   source_file(F)
  254    ->  B = true
  255    ;   B = false
  256    ).
  257
  258
  259%!  set_top_dir
  260%
  261%   Maintains a file search path =cp_application=   to  point to the
  262%   directory from which the configuration is loaded. Normally, that
  263%   is the directory holding =|run.pl|=.
  264
  265set_top_dir :-
  266    (   source_file(add_relative_search_path(_,_), File)
  267    ->  file_directory_name(File, Dir)
  268    ;   prolog_load_context(directory, Dir)
  269    ->  true
  270    ;   working_directory(Dir,Dir)
  271    ),
  272    (   user:file_search_path(cp_application, Dir)
  273    ->  true
  274    ;   assert(user:file_search_path(cp_application, Dir))
  275    ).
  276
  277%!  conf_d_configuration(+Available, +Enabled, -Configs) is det.
  278%
  279%   @param  Available is a directory or alias providing the
  280%           available configurations (e.g., config_available(.))
  281%   @param  Enabled is a directory or alias providing the installed
  282%           configuration (e.g., 'config-enabled')
  283%   @param  Configs is a list if Key-[Example,Installed], where
  284%           either is (-) or a config data item as required by
  285%           conf_d_member_data/3.  The list is sorted on Key.
  286
  287conf_d_configuration(Available, Enabled, Configs) :-
  288    keyed_config(Available, Templ),
  289    keyed_config(Enabled, Installed),
  290    merge_pairlists([Templ, Installed], Configs).
  291
  292
  293keyed_config(Dir, List) :-
  294    conf_d_members(Dir, TemplMembers, []),
  295    map_list_to_pairs(key_by_file, TemplMembers, List0),
  296    keysort(List0, List).
  297
  298key_by_file(Data, Key) :-
  299    conf_d_member_data(file, Data, Path),
  300    file_name_extension(Plain, _, Path),
  301    file_base_name(Plain, Key).
  302
  303
  304                 /*******************************
  305                 *             LIB              *
  306                 *******************************/
  307
  308%!  merge_pairlists(+PairLists, -Merged)
  309%
  310%   PairLists is a list of lists  of   K-V  pairs.  Merged is a K-VL
  311%   list, where each VL is  a  list   of  values  on K in PairLists.
  312%   Missing values are returned as (-).  For example:
  313%
  314%     ==
  315%     ?- merge_pairlists([ [a-1, d-4],
  316%                          [a-1, c-3],
  317%                          [b-2]
  318%                        ], Merged).
  319%     Merged = [a-[1,1,-], b-[-,-,2], d-[4,-,-], c-[-,3,-]].
  320%     ==
  321%
  322%   @tbd Is this useful and generic enough for library(pairs)?
  323
  324merge_pairlists(Lists, Merged) :-
  325    heads(Lists, Heads),
  326    sort(Heads, Sorted),
  327    merge_pairlists(Sorted, Lists, Merged).
  328
  329heads([], []).
  330heads([[K-_|_]|T0], [K|T]) :-
  331    !,
  332    heads(T0, T).
  333heads([[]|T0], T) :-
  334    heads(T0, T).
  335
  336merge_pairlists([], _, []).
  337merge_pairlists([K|T0], Lists, [K-Vs|T]) :-
  338    take_key(Lists, K, NewLists, NewKsUnsorted, Vs),
  339    sort(NewKsUnsorted, NewKs),
  340    ord_union(T0, NewKs, Ks),
  341    merge_pairlists(Ks, NewLists, T).
  342
  343take_key([], _, [], [], []).
  344take_key([List|T0], K, NewLists, NewKs, Vs) :-
  345    (   List = [KH-V|ListT],
  346        KH == K
  347    ->  NewLists = [ListT|T],
  348        Vs = [V|Vs1],
  349        (   ListT = [NewK-_|_]
  350        ->  NewKs = [NewK|NewKs1]
  351        ;   NewKs1 = NewKs
  352        ),
  353        take_key(T0, K, T, NewKs1, Vs1)
  354    ;   NewLists = [List|T],
  355        Vs = [(-)|Vs1],
  356        take_key(T0, K, T, NewKs, Vs1)
  357    ).
  358
  359
  360                 /*******************************
  361                 *            MESSAGES          *
  362                 *******************************/
  363
  364:- multifile
  365    prolog:message//1.  366
  367prolog:message(conf_d(Message)) -->
  368    message(Message).
  369
  370message(unload(Files)) -->
  371    [ 'Unloaded the following config files:'-[] ],
  372    files(Files).
  373message(new(Files)) -->
  374    [ 'Added the following config files:'-[] ],
  375    files(Files).
  376message(load(File)) -->
  377    [ 'Config: ~w'-[File] ].
  378
  379files([]) --> [].
  380files([H|T]) --> [ nl, '    ~w'-[H] ], files(T)