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): 2007-2017, University of Amsterdam,
    7		   VU University Amsterdam
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31:- module(setup,
   32	  [ setup_scripts/2,		% +SrcDir, +DestDir
   33	    setup_default_config/3,	% +SrcDir, +DestDir, +Options
   34	    setup_prolog_executable/1,	% -Exec for #!
   35	    setup_goodbye/0,
   36	    copy_file_with_vars/3	% +In, +Out, +Vars
   37	  ]).   38:- use_module(library(apply)).   39:- use_module(library(filesex)).   40:- use_module(library(option)).   41:- use_module(library(lists)).   42:- use_module(library(conf_d)).   43:- use_module(library(apply_macros), []).

Configuration (setup) of ClioPatria

*/

   49:- multifile
   50	substitutions/1.
 setup_scripts(+SrcDir, +DstDir)
Copy all *.in files in SrcDir into DstDir, replacing variables denoted as @NAME@. Defined variables are:
SWIPL
The SWI-Prolog executable as it must be used in #!
CLIOPATRIA
Directory that holds the ClioPatria system
CWD
The (current) installation directory
PARENTDIR
Parent of CWD. This can be useful if the startup-script is located in a subdirectory of a project.
   67setup_scripts(SrcDir, DstDir) :-
   68	substitutions(Vars),
   69	print_message(informational, setup(localize_dir(SrcDir))),
   70	atom_concat(SrcDir, '/*.in', Pattern),
   71	expand_file_name(Pattern, Files),
   72	maplist(install_file(Vars, DstDir), Files).
   73
   74install_file(Vars, Dest, InFile) :-
   75	(   exists_directory(Dest)
   76	->  file_name_extension(File, in, InFile),
   77	    file_base_name(File, Base0),
   78	    rename_script(Base0, Base),
   79	    directory_file_path(Dest, Base, DstFile)
   80	;   DstFile = Dest
   81	),
   82	copy_file_with_vars(InFile, DstFile, Vars),
   83	make_runnable(DstFile),
   84	print_message(informational, setup(install_file(DstFile))).
 rename_script(+ScriptIn, -Script)
Rename scripts to satisfy the target file name association.
   90rename_script(Run, Script) :-
   91	current_prolog_flag(associate, Ext),
   92	file_name_extension(run, _, Run),
   93	file_name_extension(run, Ext, Script), !.
   94rename_script(Script, Script).
 make_runnable(+File)
Make a file executable if it starts with #!
  100make_runnable(File) :-
  101	setup_call_cleanup(
  102	    open(File, read, In),
  103	    read_line_to_codes(In, Line),
  104	    close(In)),
  105	phrase("#!", Line, _), !,
  106	'$mark_executable'(File).
  107make_runnable(_).
 setup_prolog_executable(?Var, ?Value)
Executable to put in #!Path. On Windows this is bogus, but it may not contain spaces, so we include the default Unix RPM location.
  116setup_prolog_executable(PL) :-
  117	catch(getenv('SWIPL', PL), _, fail), !.
  118setup_prolog_executable('/usr/bin/swipl') :-
  119	current_prolog_flag(windows, true), !.
  120setup_prolog_executable(PL) :-
  121	current_prolog_flag(executable, Exe),
  122	file_base_name(Exe, Base),
  123	(   which(Base, PL)
  124	->  true
  125	;   PL = Exe
  126	).
  127
  128which(File, Path) :-
  129	catch(getenv('PATH', SearchPath), _, fail),
  130	atomic_list_concat(Parts, :, SearchPath),
  131	member(Dir, Parts),
  132	directory_file_path(Dir, File, Path),
  133	access_file(Path, execute).
 setup_default_config(+ConfigEnabled, +ConfigAvail, +Options)
Setup the enabled cofiguration directory from the given ConfigAvail. If Options include help(true), this prints a set of available options.
  141setup_default_config(ConfigEnabled, ConfigAvail, Options) :-
  142	option(help(true), Options), !,
  143	setup_config_help(ConfigEnabled, ConfigAvail).
  144setup_default_config(ConfigEnabled, ConfigAvail, Options) :-
  145	setup_config_enabled(ConfigEnabled, Options),
  146	default_config(ConfigEnabled, ConfigAvail, Options).
  147
  148
  149setup_config_enabled(ConfigEnabled, Options) :-
  150	(   exists_directory(ConfigEnabled)
  151	->  true
  152	;   make_directory(ConfigEnabled)
  153	),
  154	directory_file_path(ConfigEnabled, 'README.txt', Readme),
  155	(   exists_file(Readme)
  156	->  true
  157	;   option(readme(ReadMeIn), Options)
  158	->  print_message(informational,
  159			  setup(install_file('README.txt', ConfigEnabled))),
  160	    substitutions(Vars),
  161	    install_file(Vars, Readme, ReadMeIn)
  162	).
 default_config(+ConfigEnabledDir, +ConfigAvailDir, +Options)
Install a default configuration in ConfigEnabledDir based on the information from ConfigAvailDir. Options:
without(Base)
Skip this file from the installation
with(Base)
Add this file to the installation
  174default_config(ConfigEnabled, ConfigAvail, Options) :-
  175	directory_file_path(ConfigEnabled, 'config.done', DoneFile),
  176	(   exists_file(DoneFile)
  177	->  read_file_to_terms(DoneFile, Installed, [])
  178	;   Installed = []
  179	),
  180	include(with, Options, Requests),
  181	maplist(with_file(ConfigAvail), Requests, With),
  182	config_defaults(ConfigAvail, Defaults0),
  183	exclude(without(Options), Defaults0, Defaults),
  184	append(Defaults, With, Install),
  185	(   Install \== []
  186	->  setup_call_cleanup(open_done(DoneFile, Out),
  187			       maplist(install_config(Installed,
  188						      ConfigEnabled,
  189						      ConfigAvail,
  190						      Out, Options),
  191				       Install),
  192			       close(Out))
  193	;   true
  194	).
  195
  196without(Options, file(Key,_,_)) :-
  197	memberchk(without(Key), Options).
  198
  199with(with(_)).
  200
  201with_file(ConfigAvail, with(Key), file(Key, Path, link)) :-
  202	directory_file_path(ConfigAvail, Key, FileBase),
  203	absolute_file_name(FileBase, Path,
  204			   [ access(read),
  205			     file_type(prolog)
  206			   ]).
  207
  208open_done(DoneFile, Out) :-
  209	exists_file(DoneFile), !,
  210	open(DoneFile, append, Out).
  211open_done(DoneFile, Out) :-
  212	open(DoneFile, write, Out),
  213	format(Out, '/* Generated file~n', []),
  214	format(Out, '   Keep track of installed config files~n', []),
  215	format(Out, '*/~n~n', []).
  216
  217install_config(Installed, ConfigEnabled, ConfigAvail, Out, Options,
  218	       file(_Key, File, How0)) :-
  219	file_base_name(File, Base),
  220	\+ ( memberchk(file(IFile,_,_), Installed),
  221	     file_base_name(IFile, Base)
  222	   ), !,
  223	final_how(How0, How, Options),
  224	install_config_file(How, ConfigEnabled, File),
  225	get_time(Now),
  226	Stamp is round(Now),
  227	format(Out, '~q.~n', [file(Base, ConfigAvail, Stamp)]).
  228install_config(_, _, _, _, _, _).
  229
  230final_how(link, How, Options) :- !,
  231	(   option(link(true), Options)
  232	->  How = link
  233	;   How = include
  234	).
  235final_how(How, How, _).
 config_defaults(+ConfigAvail, -Defaults) is det
Defaults is a list of file(Key, File, How) that indicates which available config files must be installed by default.
Arguments:
ConfigAvail- is either a directory or an alias.
  245config_defaults(ConfigAvail, Defaults) :-
  246	compound(ConfigAvail), !,
  247	findall(Defs,
  248		(   absolute_file_name(ConfigAvail, Dir,
  249				       [ file_type(directory),
  250					 solutions(all),
  251					 access(read)
  252				       ]),
  253		    config_defaults_dir(Dir, Defs)
  254		),
  255		AllDefs),
  256	append(AllDefs, Defaults).
  257config_defaults(ConfigAvail, Defaults) :-
  258	config_defaults_dir(ConfigAvail, Defaults).
  259
  260
  261config_defaults_dir(ConfigAvail, Defaults) :-
  262	directory_file_path(ConfigAvail, 'DEFAULTS', DefFile),
  263	access_file(DefFile, read), !,
  264	read_file_to_terms(DefFile, Terms, []),
  265	config_defaults(Terms, ConfigAvail, Defaults).
  266config_defaults_dir(_, []).
  267
  268config_defaults([], _, []).
  269config_defaults([H|T0], ConfigAvail, [F|T]) :-
  270	config_default(H, ConfigAvail, F), !,
  271	config_defaults(T0, ConfigAvail, T).
  272config_defaults([_|T0], ConfigAvail, T) :-
  273	config_defaults(T0, ConfigAvail, T).
  274
  275
  276config_default((Head :- Body), ConfigAvail, File) :- !,
  277	call(Body),
  278	config_default(Head, ConfigAvail, File).
  279config_default(config(FileBase, How), ConfigAvail,
  280	       file(Key, Path, How)) :- !,
  281	(   File = FileBase
  282	;   prolog_file_type(Ext, prolog),
  283	    file_name_extension(FileBase, Ext, File)
  284	),
  285	directory_file_path(ConfigAvail, File, Path),
  286	exists_file(Path),
  287	file_base_name(File, Base),
  288	file_name_extension(Key, _, Base).
  289config_default(Term, _, _) :-
  290	domain_error(config_term, Term).
 setup_config_help(+ConfigEnabled, +ConfigAvail) is det
  295setup_config_help(ConfigEnabled, ConfigAvail) :-
  296	doc_collect(true),
  297	config_defaults(ConfigAvail, Defaults),
  298	conf_d_configuration(ConfigAvail, ConfigEnabled, Configs),
  299	partition(default_config(Defaults), Configs, Default, NonDefault),
  300	maplist(config_help(without), Default, Without),
  301	maplist(config_help(with), NonDefault, With),
  302	print_message(informational, setup(general)),
  303	print_message(informational, setup(without(Without))),
  304	print_message(informational, setup(with(With))),
  305	print_message(informational, setup(advice)).
  306
  307default_config(Defaults, Key-_) :-
  308	memberchk(file(Key,_,_), Defaults).
  309
  310config_help(With, Key-[Example,_], Help) :-
  311	(   conf_d_member_data(title, Example, Title)
  312	->  true
  313	;   Title = 'no description'
  314	),
  315	Help =.. [With,Key,Title].
 install_config_file(+How, +ConfDir, +File) is det
Install the configuration file File in the configuration directory ConfDir. How dictates how the file is installed and is one of:
link
Link the file. This means that the configured system updates the config file if it is updated in the package.
include
As link, but avoiding the nead for symlinks
copy
Copy the file. This is used if the config file in the package is merely a skeleton that needs to be instantiated for the specific ClioPatria installation.
  334install_config_file(_, ConfDir, Path) :-
  335	file_base_name(Path, File),
  336	directory_file_path(ConfDir, File, Dest),
  337	exists_file(Dest), !.
  338install_config_file(link, ConfDir, Source) :-
  339	file_base_name(Source, File),
  340	directory_file_path(ConfDir, File, Dest),
  341	print_message(informational, setup(install_file(File))),
  342	link_prolog_file(Source, Dest).
  343install_config_file(include, ConfDir, Source) :-
  344	file_base_name(Source, File),
  345	directory_file_path(ConfDir, File, Dest),
  346	print_message(informational, setup(install_file(File))),
  347	include_prolog_file(Source, Dest).
  348install_config_file(copy, ConfDir, Source) :-
  349	file_base_name(Source, File),
  350	directory_file_path(ConfDir, File, Dest),
  351	print_message(informational, setup(install_file(File))),
  352	copy_file(Source, Dest).
 link_prolog_file(+SourcePath, +DestDir) is det
Install a skeleton file by linking it. If it is not possible to create a symbolic link (typically on system that do not support proper links such as Windows), create a Prolog `link' file that loads the target.
  361link_prolog_file(Source, Dest) :-
  362	relative_file_name(Source, Dest, Rel),
  363	catch(link_file(Rel, Dest, symbolic), Error, true),
  364	(   var(Error)
  365	->  true
  366	;   include_prolog_file(Source, Dest)
  367	->  true
  368	;   throw(Error)
  369	).
 include_prolog_file(+Source, +Dest) is det
Creat a link file for a Prolog file. Make sure to delete the target first, to avoid an accidental write through a symbolic link.
  377include_prolog_file(Source, Dest) :-
  378	(   access_file(Dest, exist)
  379	->  delete_file(Dest)
  380	;   true
  381	),
  382	file_base_name(Source, File),
  383	file_name_extension(Base, pl, File),
  384	atomic_list_concat([link_, Base, '_conf'], LinkModule),
  385	setup_call_cleanup(
  386	    open(Dest, write, Out),
  387	    ( format(Out, '/* Linked config file */~n', []),
  388	      format(Out, ':- module(~q, []).~n', [LinkModule]),
  389	      format(Out, ':- ~q.~n', [reexport(config_available(Base))])
  390	    ),
  391	    close(Out)).
 setup_goodbye
Say we are done. Waits for the user in Windows to allow the user read messages.
  398setup_goodbye :-
  399	current_prolog_flag(windows, true), !,
  400	format(user_error, '~N~nReady.  Press any key to exit. ', []),
  401	get_single_char(_),
  402	format(' Goodbye!~n'),
  403	halt.
  404setup_goodbye :-
  405	halt.
  406
  407
  408		 /*******************************
  409		 *	       UTIL		*
  410		 *******************************/
 copy_file_with_vars(+File, +DirOrFile, +Bindings) is det
As cp File DirOrFile, while substituting @var@ from Bindings using copy_stream_with_vars/3.
  417copy_file_with_vars(File, DirOrFile, Bindings) :-
  418	destination_file(DirOrFile, File, Dest),
  419	open(File, read, In),
  420	open(Dest, write, Out),
  421	call_cleanup(copy_stream_with_vars(In, Out, Bindings),
  422		     (close(In), close(Out))).
  423
  424destination_file(Dir, File, Dest) :-
  425	exists_directory(Dir), !,
  426	atomic_list_concat([Dir, File], /, Dest).
  427destination_file(Dest, _, Dest).
 copy_stream_with_vars(+In:stream, +Out:stream, +Bindings:list(Var=Name)) is det
Copy all data from In to Out, while replacing @var@ with a binding from Bindings. In addition, !var! is replaced with a Prolog-quoted version of the variable content.
Arguments:
Bindings- List of Var=Name or Var(Name). If exact case match fails, the match is retried with the lowercase name.
  440copy_stream_with_vars(In, Out, []) :- !,
  441	copy_stream_data(In, Out).
  442copy_stream_with_vars(In, Out, Bindings) :-
  443	get_code(In, C0),
  444	copy_with_vars(C0, In, Out, Bindings).
  445
  446copy_with_vars(-1, _, _, _) :- !.
  447copy_with_vars(0'@, In, Out, Bindings) :- !,
  448	insert_var(0'@, C2, In, Out, Bindings),
  449	copy_with_vars(C2, In, Out, Bindings).
  450copy_with_vars(0'!, In, Out, Bindings) :- !,
  451	insert_var(0'!, C2, In, Out, Bindings),
  452	copy_with_vars(C2, In, Out, Bindings).
  453copy_with_vars(C0, In, Out, Bindings) :-
  454	put_code(Out, C0),
  455	get_code(In, C1),
  456	copy_with_vars(C1, In, Out, Bindings).
  457
  458insert_var(Mark, C2, In, Out, Bindings) :-
  459	get_code(In, C0),
  460	read_var_name(C0, In, VarNameS, C1),
  461	atom_codes(VarName, VarNameS),
  462	(   C1 == Mark,
  463	    var_value(VarName, Value, Bindings)
  464	->  (   Mark == 0'@
  465	    ->  format(Out, '~w', [Value])
  466	    ;   format(Out, '~q', [Value])
  467	    ),
  468	    get_code(In, C2)
  469	;   format(Out, '~c~w', [Mark, VarName]),
  470	    C2 = C1
  471	).
  472
  473read_var_name(C0, In, [C0|T], End) :-
  474	code_type(C0, alpha), !,
  475	get_code(In, C1),
  476	read_var_name(C1, In, T, End).
  477read_var_name(C0, _In, [], C0).
  478
  479var_value(Name, Value, Vars) :-
  480	memberchk(Name=Value, Vars), !.
  481var_value(Name, Value, Vars) :-
  482	Term =.. [Name,Value],
  483	memberchk(Term, Vars), !.
  484var_value(Name, Value, Vars) :-
  485	downcase_atom(Name, Lwr),
  486	Lwr \== Name,
  487	var_value(Lwr, Value, Vars).
  488
  489
  490		 /*******************************
  491		 *	      MESSAGES		*
  492		 *******************************/
  493
  494:- multifile
  495	prolog:message//1.  496
  497prolog:message(setup(Term)) -->
  498	message(Term).
  499
  500message(localize_dir(SrcDir)) -->
  501	[ 'Localizing scripts from ~p ...'-[SrcDir] ].
  502message(install_file(File, Dir)) -->
  503	[ 'Installing ~w in ~w ...'-[File, Dir] ].
  504message(install_file(File)) -->
  505	{ file_base_name(File, Base) },
  506	[ ' Installing ~w ...'-[Base] ].
  507message(without(List)) -->
  508	[ nl, 'Use --without-X to disable default components' ],
  509	help(List).
  510message(with(List)) -->
  511	[ nl, 'Use --with-X to enable non-default components' ],
  512	help(List).
  513message(general) -->
  514	[ 'ClioPatria setup program', nl, nl,
  515	  'General options', nl,
  516	  '  --link~t~28|Use symbolic links in config-enabled'-[]
  517	].
  518message(advice) -->
  519	[ nl, 'Typical setup for local interactive usage', nl,
  520	  '  --with-debug --with-localhost'-[]
  521	].
  522
  523help([]) --> [].
  524help([H|T]) -->
  525	[nl],
  526	help(H),
  527	help(T).
  528help(without(Key, Title)) -->
  529	[ '  --without-~w~t~28|~w'-[Key, Title] ].
  530help(with(Key, Title)) -->
  531	[ '  --with-~w~t~28|~w'-[Key, Title] ]