View source with raw comments or as raw
    1/*  Part of ClioPatria SeRQL and SPARQL server
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2010 VU University Amsterdam
    7
    8    This program is free software; you can redistribute it and/or
    9    modify it under the terms of the GNU General Public License
   10    as published by the Free Software Foundation; either version 2
   11    of the License, or (at your option) any later version.
   12
   13    This program is distributed in the hope that it will be useful,
   14    but WITHOUT ANY WARRANTY; without even the implied warranty of
   15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16    GNU General Public License for more details.
   17
   18    You should have received a copy of the GNU General Public
   19    License along with this library; if not, write to the Free Software
   20    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   21
   22    As a special exception, if you link this library with other files,
   23    compiled with a Free Software compiler, to produce an executable, this
   24    library does not by itself cause the resulting executable to be covered
   25    by the GNU General Public License. This exception does not however
   26    invalidate any other reasons why the executable file might be covered by
   27    the GNU General Public License.
   28*/
   29
   30:- module(conf_d,
   31	  [ load_conf_d/2,		% +Directories, +Options
   32	    conf_d_enabled/1,		% -ConfDir
   33	    conf_d_reload/0,
   34	    conf_d_members/3,		% +Directory, -FileData, +Options
   35	    conf_d_member_data/3,	% ?Field, +FileData, -Value
   36	    conf_d_configuration/3	% +Available, +Enabled, -Configs
   37	  ]).   38:- use_module(library(option)).   39:- use_module(library(ordsets)).   40:- use_module(library(lists)).   41:- use_module(library(apply)).   42:- use_module(library(version)).   43:- use_module(library(prolog_xref)).   44:- if(exists_source(library(pldoc/doc_process))).   45:- use_module(library(pldoc)).   46:- use_module(library(pldoc/doc_process)).   47:- endif.

Load configuration directories

This module deals with loading configuration-files from a directory. This is pretty simple because we assume that configuration files are Prolog source-files. We (can) use file_search_path/2 to define one or more configuration directories.

Files are loaded in alphabetical order. If one config file requires another, there are two solutions:

 load_conf_d(+Spec, +Options) is det
Locate configuration directories and load their config files. Config files themselves are Prolog source files. Options:
solutions(+Sols)
Passed to absolute_file_name/3. Default is all, loading config files from all directories described by Spec.
extension(+Ext)
File-name extension for the config files. Default is pl.

Other options are passed to load_files/2.

Arguments:
Spec- is either the specification of a directory according to absolute_file_name/3 or a list thereof. Duplicate directories are removed.
To be done
- There is a bug forking processes in one thread and waiting for X11 in another, which deadlocks in fork_atfree(). So, we must ensure we have the git versions in time :-(
   86load_conf_d(Spec, Options) :-
   87	set_top_dir,
   88	select_option(solutions(Sols), Options, LoadOptions0, all),
   89	merge_options(LoadOptions0,
   90		      [ if(changed),
   91			extension(pl)
   92		      ], LoadOptions),
   93	phrase(collect_dirs(Spec, Sols), Dirs),
   94	list_to_set(Dirs, Set),
   95	maplist(conf_d_files(Options), Set, Pairs),
   96	keep_last(Pairs, Final),
   97	maplist(load_conf_dir(LoadOptions), Final),
   98	git_update_versions(_).		% See above
   99
  100collect_dirs([], _) --> !.
  101collect_dirs([H|T], Sols) --> !,
  102	collect_dirs(H, Sols),
  103	collect_dirs(T, Sols).
  104collect_dirs(Spec, Sols) -->
  105	findall(Dir, absolute_file_name(Spec, Dir,
  106					[ file_type(directory),
  107					  file_errors(fail),
  108					  access(read),
  109					  solutions(Sols)
  110					])).
  111
  112
  113:- dynamic
  114	conf_d/3.			% Directory, Options, Files
  115
  116load_conf_dir(Options, Dir-Files) :-
  117	delete(Options, extension(_), LoadOptions),
  118	update_conf_d(Dir, Files, Options),
  119	maplist(load_conf(LoadOptions), Files).
  120
  121load_conf(Options, File) :-
  122	print_message(informational, conf_d(load(File))),
  123	load_files(user:File, [module(File)|Options]).
  124
  125conf_d_files(Options, Dir, Dir-Files) :-
  126	option(extension(Ext), Options, pl),
  127	atomic_list_concat([Dir, '/*.', Ext], Pattern),
  128	expand_file_name(Pattern, Matches),
  129	include(accessible, Matches, MatchedFiles),
  130	maplist(absolute_file_name, MatchedFiles, CanonicalFiles),
  131	sort(CanonicalFiles, Files).
  132
  133accessible(File) :-
  134	access_file(File, read).
 keep_last(+PairsIn, -PairsOut) is det
PairsIn is a list Dir-Files holding Files to be loaded from Dir. We remove all files from Files that appear with a later directory.
  142keep_last([], []).
  143keep_last([Dir-Files0|T0], [Dir-Files|T]) :-
  144	exclude(in_later_dir(T0), Files0, Files),
  145	keep_last(T0, T).
  146
  147in_later_dir(Pairs, File) :-
  148	file_base_name(File, Base),
  149	\+ multi(Base),
  150	member(_-Files, Pairs),
  151	member(F2, Files),
  152	file_base_name(F2, Base).
  153
  154multi('010-packs.pl').
  155
  156update_conf_d(Dir, Files, Options) :-
  157	\+ conf_d(Dir, _, _), !,
  158	assert(conf_d(Dir, Options, Files)).
  159update_conf_d(Dir, Files, Options) :-
  160	retract(conf_d(Dir, _, OldFiles)), !,
  161	ord_subtract(OldFiles, Files, Removed),
  162	(   Removed \== []
  163	->  print_message(informational, conf_d(unload(Removed))),
  164	    catch(maplist(unload_file, Removed), E,
  165		  print_message(error, E))
  166	;   true
  167	),
  168	ord_subtract(Files, OldFiles, New),
  169	(   New \== []
  170	->  print_message(informational, conf_d(new(New)))
  171	;   true
  172	),
  173	assert(conf_d(Dir, Options, Files)).
 conf_d_enabled(-Dir) is nondet
True if Dir is a directory from which config files are loaded.
  179conf_d_enabled(Dir) :-
  180	conf_d(Dir, _, _).
 conf_d_reload is det
Reload configuration files after adding or deleting config files. Note that this is not exactly the same as restarting the server. First of all, the order in which the files are loaded may be different and second, wiping a config file only wipes the clauses and module. Side effects, for example due to executed directives, are not reverted.
  191conf_d_reload :-
  192	findall(Dir-Options-Files, conf_d(Dir, Options, Files), Triples),
  193	forall(member(Dir-Options-Files, Triples),
  194	       load_conf_dir(Options, Dir-Files)).
 conf_d_members(+Dir, -InfoRecords:list, Options) is det
Provide information about config files in Dir.
Arguments:
InfoRecords- is a list of terms. The predicate conf_d_member_data/3 must be used to extract data from these terms.
  204conf_d_members(DirSpec, InfoRecords, Options) :-
  205	findall(Files,
  206		( absolute_file_name(DirSpec, Dir,
  207				     [ file_type(directory),
  208				       solutions(all)
  209				     ]),
  210		  conf_d_files(Dir, Files, Options)
  211		), FileLists),
  212	append(FileLists, Files0),
  213	sort(Files0, Files), % remove duplicates introduced by absolute & relative ClioPatria paths
  214	maplist(conf_file, Files, InfoRecords).
  215
  216conf_file(File, config_file(Path, Module, Title)) :-
  217	xref_public_list(File, Path, Module, _Public, _Meta, []), !,
  218	(   current_predicate(doc_comment/4),
  219	    doc_comment(_:module(Title), Path:_, _Summary, _Comment)
  220	->  true
  221	;   true
  222	).
  223conf_file(File, config_file(File, _Module, _Title)).
 conf_d_member_data(?Field, +ConfigInfo, ?Value) is nondet
True if Value is the value for Field in ConfigInfo. ConfigInfo is an opaque term as returned by conf_d_info/3. Defined fields are:
file
Absolute path of the file
module
Module defined in the file (can fail)
title
Comment-title (from /** <module> Title .. */)
loaded
Boolean, indicating whether the file is currently loaded.
  240conf_d_member_data(file,   config_file(F, _, _), F).
  241conf_d_member_data(module, config_file(_, M, _), M) :- nonvar(M).
  242conf_d_member_data(title,  config_file(_, _, T), T) :- nonvar(T).
  243conf_d_member_data(loaded, config_file(F, _, _), B) :-
  244	(   source_file(F)
  245	->  B = true
  246	;   B = false
  247	).
 set_top_dir
Maintains a file search path cp_application to point to the directory from which the configuration is loaded. Normally, that is the directory holding run.pl.
  256set_top_dir :-
  257	(   source_file(add_relative_search_path(_,_), File)
  258	->  file_directory_name(File, Dir)
  259	;   prolog_load_context(directory, Dir)
  260	->  true
  261	;   working_directory(Dir,Dir)
  262	),
  263	(   user:file_search_path(cp_application, Dir)
  264	->  true
  265	;   assert(user:file_search_path(cp_application, Dir))
  266	).
 conf_d_configuration(+Available, +Enabled, -Configs) is det
Arguments:
Available- is a directory or alias providing the available configurations (e.g., config_available(.))
Enabled- is a directory or alias providing the installed configuration (e.g., 'config-enabled')
Configs- is a list if Key-[Example,Installed], where either is (-) or a config data item as required by conf_d_member_data/3. The list is sorted on Key.
  278conf_d_configuration(Available, Enabled, Configs) :-
  279	keyed_config(Available, Templ),
  280	keyed_config(Enabled, Installed),
  281	merge_pairlists([Templ, Installed], Configs).
  282
  283
  284keyed_config(Dir, List) :-
  285	conf_d_members(Dir, TemplMembers, []),
  286	map_list_to_pairs(key_by_file, TemplMembers, List0),
  287	keysort(List0, List).
  288
  289key_by_file(Data, Key) :-
  290	conf_d_member_data(file, Data, Path),
  291	file_name_extension(Plain, _, Path),
  292	file_base_name(Plain, Key).
  293
  294
  295		 /*******************************
  296		 *	       LIB		*
  297		 *******************************/
 merge_pairlists(+PairLists, -Merged)
PairLists is a list of lists of K-V pairs. Merged is a K-VL list, where each VL is a list of values on K in PairLists. Missing values are returned as (-). For example:
?- merge_pairlists([ [a-1, d-4],
                     [a-1, c-3],
                     [b-2]
                   ], Merged).
Merged = [a-[1,1,-], b-[-,-,2], d-[4,-,-], c-[-,3,-]].
To be done
- Is this useful and generic enough for library(pairs)?
  315merge_pairlists(Lists, Merged) :-
  316	heads(Lists, Heads),
  317	sort(Heads, Sorted),
  318	merge_pairlists(Sorted, Lists, Merged).
  319
  320heads([], []).
  321heads([[K-_|_]|T0], [K|T]) :- !,
  322	heads(T0, T).
  323heads([[]|T0], T) :-
  324	heads(T0, T).
  325
  326merge_pairlists([], _, []).
  327merge_pairlists([K|T0], Lists, [K-Vs|T]) :-
  328	take_key(Lists, K, NewLists, NewKsUnsorted, Vs),
  329	sort(NewKsUnsorted, NewKs),
  330	ord_union(T0, NewKs, Ks),
  331	merge_pairlists(Ks, NewLists, T).
  332
  333take_key([], _, [], [], []).
  334take_key([List|T0], K, NewLists, NewKs, Vs) :-
  335	(   List = [KH-V|ListT],
  336	    KH == K
  337	->  NewLists = [ListT|T],
  338	    Vs = [V|Vs1],
  339	    (	ListT = [NewK-_|_]
  340	    ->	NewKs = [NewK|NewKs1]
  341	    ;	NewKs1 = NewKs
  342	    ),
  343	    take_key(T0, K, T, NewKs1, Vs1)
  344	;   NewLists = [List|T],
  345	    Vs = [(-)|Vs1],
  346	    take_key(T0, K, T, NewKs, Vs1)
  347	).
  348
  349
  350		 /*******************************
  351		 *	      MESSAGES		*
  352		 *******************************/
  353
  354:- multifile
  355	prolog:message//1.  356
  357prolog:message(conf_d(Message)) -->
  358	message(Message).
  359
  360message(unload(Files)) -->
  361	[ 'Unloaded the following config files:'-[] ],
  362	files(Files).
  363message(new(Files)) -->
  364	[ 'Added the following config files:'-[] ],
  365	files(Files).
  366message(load(File)) -->
  367	[ 'Config: ~w'-[File] ].
  368
  369files([]) --> [].
  370files([H|T]) --> [ nl, '    ~w'-[H] ], files(T)