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, 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(cpa_config, []).   32:- use_bundle(html_page).   33:- use_module(library(conf_d)).   34:- use_module(library(pairs)).   35:- use_module(library(apply)).   36:- use_module(library(ordsets)).   37:- use_module(pldoc(doc_index)).   38:- use_module(cliopatria(hooks)).   39:- use_module(user(user_db)).   40:- use_module(components(messages)).   41:- if(exists_source(library(filesex))).   42:- use_module(library(filesex)).   43:- endif.

ClioPatria configuration interface

This application provides a web-interface for configuration management by adding files to config-enabled. */

   51:- http_handler(cliopatria('admin/configuration'), configuration, []).   52:- http_handler(cliopatria('admin/reconfigure'),   reconfigure,	  []).   53
   54cliopatria:menu_item(250=admin/configuration,  'Plugins').
 configuration(+Request)
HTTP handler that shows the current status of available and installed configuration modules.
   61configuration(_Request) :-
   62	authorized(admin(config)),
   63	reply_html_page(cliopatria(admin),
   64			title('Server plugin configuration'),
   65			[ h1('Server plugin configuration'),
   66			  \edit_config_table([edit(true)]),
   67			  \insert_html_file(html('help-config.html'))
   68			]).
 edit_config_table(+Options)
HTML Component that shows the available and installed configuration components.
   75edit_config_table(Options) -->
   76	{ option(edit(true), Options) }, !,
   77	html(form([ action(location_by_id(reconfigure)),
   78		    method('GET')
   79		  ],
   80		  \config_table(Options))).
   81edit_config_table(Options) -->
   82	config_table(Options).
   83
   84config_table(Options) -->
   85	{ config_files(Configs)
   86	},
   87	html(table(class(form),
   88		   [ \config_table_header
   89		   | \config_modules(Configs, 1, Options)
   90		   ])).
   91
   92config_table_header -->
   93	html(tr(class(header),
   94		[th('Config'), th('Title'), th('Status')])).
   95
   96config_modules([], _, Options) -->
   97	(   { option(edit(true), Options) }
   98	->  html(tr(class(buttons),
   99		    td([ colspan(3), align(right), style('padding-top:1em;')
  100		       ],
  101		       [ input(type(reset)),
  102			 input([type(submit),value('Update configuration')])
  103		       ])))
  104	;   []
  105	).
  106config_modules([H|T], OE, Options) -->
  107	{ config_module_status(H, Status) },
  108	odd_even_row(OE, OE1, \config_module(Status, H, Options)),
  109	config_modules(T, OE1, Options).
  110
  111config_module_status(_-[_,-], not) :- !.
  112config_module_status(_-[-,_], local) :- !.
  113config_module_status(_-[Templ,Installed], Status) :-
  114	conf_d_member_data(file, Templ, TemplFile),
  115	conf_d_member_data(file, Installed, InstalledFile),
  116	compare_files(TemplFile, InstalledFile, Status).
  117
  118config_module(Status, Data, Options) -->
  119	{ Data = Key-_Members,
  120	  prop_member(Status, Data, Props)
  121	},
  122	html([ td(\config_key(Key, Props)),
  123	       td(\config_title(Props)),
  124	       \config_installed(Status, Key, Options)
  125	     ]).
  126
  127prop_member(not, _-[Templ,_], Templ) :- !.
  128prop_member(_,	 _-[_,Installed], Installed).
  129
  130
  131config_key(Key, Data) -->
  132	{ conf_d_member_data(file, Data, File),
  133	  doc_file_href(File, HREF)
  134	},
  135	html(a(href(HREF), Key)).
  136
  137config_title(Data) -->
  138	{ conf_d_member_data(title, Data, Title) }, !,
  139	html([ Title ]).
  140config_title(_) -->
  141	html([]).
  142
  143config_installed(Value, Key, Options) -->
  144	{ option(edit(true), Options),
  145	  findall(o(O,L,LC), ( option(O,L,A,LC),
  146			       (   Value==O
  147			       ->  true
  148			       ;   memberchk(Value, A)
  149			       )
  150			     ),
  151		  Pairs)
  152	}, !,
  153	html(td(class(buttons),
  154		select([name(Key),style('width:100%')],
  155		       \installed_options(Pairs, Value)))).
  156config_installed(Value, _, _) -->
  157	{ option(Value, Label, _, _)
  158	},
  159	html(td(Label)).
  160
  161installed_options([], _) --> [].
  162installed_options([H|T], Value) -->
  163	installed_option(H, Value),
  164	installed_options(T, Value).
  165
  166installed_option(o(V,L,_LC), V) -->
  167	html(option([value(V),selected], L)).
  168installed_option(o(V,_L,LC), _) -->
  169	html(option([value(V),class(change)], LC)).
  170
  171option(not,				% Id
  172       'Not installed',			% Label if current status
  173       [linked,copied,modified],	% State that can be changed to me
  174       'Remove').			% Label to change
  175option(linked,
  176       'Installed (linked)',
  177       [not,copied,modified],
  178       'Link').
  179option(copied,
  180       'Installed (copied)',
  181       [not,linked,modified],
  182       'Copy').
  183option(modified,
  184       'Installed (modified)',
  185       [],
  186       '').
  187option(local,
  188       'Local',
  189       [],
  190       '').
 compare_files(+File, +File2, -Status) is det
Compare two files, unifying Status with one of linked, copied or modified.
  197compare_files(Templ, Installed, Status) :-
  198	(   same_file(Templ, Installed)
  199	->  Status = linked
  200	;   link_file(Installed)
  201	->  Status = linked
  202	;   same_file_content(Templ, Installed)
  203	->  Status = copied
  204	;   Status = modified
  205	).
  206
  207link_file(File) :-
  208	setup_call_cleanup(open(File, read, In),
  209			   read_line_to_codes(In, Line),
  210			   close(In)),
  211	atom_codes('/* Linked config file */', Line).
  212
  213same_file_content(File1, File2) :-
  214	setup_call_cleanup((open(File1, read, In1),
  215			    open(File2, read, In2)),
  216			   same_stream_content(In1, In2),
  217			   (close(In2), close(In1))).
  218
  219same_stream_content(In1, In2) :-
  220	get_code(In1, C1),
  221	get_code(In2, C2),
  222	same_stream_content(C1, C2, In1, In2).
  223
  224same_stream_content(C, C, In1, In2) :-
  225	(   C == -1
  226	->  true
  227	;   same_stream_content(In1, In2)
  228	).
 config_files(-Configs)
Get the current configuration status.
  235config_files(Configs) :-
  236	conf_d_configuration(config_available(.),
  237			     'config-enabled',
  238			     Configs).
 reconfigure(+Request)
Update configuration on the basis of the menu.
  245reconfigure(Request) :-
  246	authorized(admin(reconfigure)),
  247	http_link_to_id(configuration, [], HREF),
  248	http_parameters(Request, [], [form_data(Form)]),
  249	call_showing_messages(update_config(Form),
  250			      [ footer(h4(['Done. ',
  251					   a(href(HREF),
  252					     'back to configuration')]))
  253			      ]).
  254
  255update_config(Form) :-
  256	config_files(Configs),
  257	maplist(update_config_key(Form, Updated), Configs),
  258	(   var(Updated)
  259	->  print_message(informational, config(no_changes))
  260	;   conf_d_reload
  261	).
  262
  263update_config_key(Form, Updated, Config) :-
  264	Config = Key-Versions,
  265	config_module_status(Config, CurrentStatus),
  266	(   memberchk(Key=NewStatus, Form),
  267	    NewStatus \== CurrentStatus
  268	->  update_config_file(CurrentStatus, NewStatus, Versions),
  269	    Updated = true
  270	;   true
  271	).
  272
  273update_config_file(linked, not, [_,Installed]) :- !,
  274	conf_d_member_data(file, Installed, File),
  275	delete_file(File),
  276	print_message(informational, config(delete(File))).
  277update_config_file(_, not, [_,Installed]) :- !,
  278	conf_d_member_data(file, Installed, File),
  279	atom_concat(File, '.disabled', DisabledFile),
  280	catch(delete_file(DisabledFile), _, true),
  281	rename_file(File, DisabledFile),
  282	print_message(informational, config(rename(File, DisabledFile))).
  283update_config_file(not, linked, [Templ,_]) :-
  284	conf_d_member_data(file, Templ, File),
  285	file_base_name(File, Base),
  286	local_conf_dir(Dir),
  287	atomic_list_concat([Dir, /, Base], NewFile),
  288	link_prolog_file(File, NewFile),
  289	print_message(informational, config(link(NewFile))).
  290update_config_file(copied, linked, [Templ,Installed]) :-
  291	conf_d_member_data(file, Templ, TemplFile),
  292	conf_d_member_data(file, Installed, InstalledFile),
  293	delete_file(InstalledFile),
  294	link_prolog_file(TemplFile, InstalledFile),
  295	print_message(informational, config(link(InstalledFile))).
  296update_config_file(not, copied, [Templ,_]) :-
  297	conf_d_member_data(file, Templ, File),
  298	file_base_name(File, Base),
  299	local_conf_dir(Dir),
  300	atomic_list_concat([Dir, /, Base], NewFile),
  301	copy_file(File, NewFile),
  302	print_message(informational, config(copy(NewFile))).
  303update_config_file(linked, copied, [Templ,Installed]) :-
  304	conf_d_member_data(file, Templ, TemplFile),
  305	conf_d_member_data(file, Installed, InstalledFile),
  306	delete_file(InstalledFile),
  307	copy_file(TemplFile, InstalledFile),
  308	print_message(informational, config(copy(InstalledFile))).
 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.
See also
- copied from library(setup). Do not alter without synchronising.
  321link_prolog_file(Source, Dest) :-
  322	relative_file_name(Source, Dest, Rel),
  323	catch(link_file(Rel, Dest, symbolic), Error, true),
  324	(   var(Error)
  325	->  true
  326	;   catch(create_link_file(Dest, Rel), E2, true)
  327	->  (   var(E2)
  328	    ->	true
  329	    ;	throw(E2)
  330	    )
  331	;   throw(Error)
  332	).
 create_link_file(+Dest, +Rel) 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.
  340create_link_file(Dest, Rel) :-
  341	(   access_file(Dest, exist)
  342	->  delete_file(Dest)
  343	;   true
  344	),
  345	setup_call_cleanup(open(Dest, write, Out),
  346			   ( format(Out, '/* Linked config file */~n', []),
  347			     format(Out, ':- ~q.~n', [consult(Rel)])
  348			   ),
  349			   close(Out)).
  350
  351
  352local_conf_dir(Dir) :-
  353	absolute_file_name('config-enabled', Dir,
  354			   [ file_type(directory),
  355			     access(write)
  356			   ]).
  357
  358
  359:- multifile prolog:message//1.  360
  361prolog:message(config(Action)) -->
  362	message(Action).
  363
  364message(delete(File)) --> ['Deleted '], file(File).
  365message(rename(Old, New)) --> ['Renamed '], file(Old), [' into '], file(New).
  366message(link(File)) --> ['Linked '], file(File).
  367message(copy(File)) --> ['Copied '], file(File).
  368message(no_changes) --> ['No changes; configuration is left untouched'].
  369
  370file(Path) -->
  371	{ working_directory(Dir,Dir),
  372	  ensure_slash(Dir, RelTo),
  373	  relative_file_name(Path, RelTo, Rel)
  374	},
  375	[ '~w'-[Rel] ].
  376
  377ensure_slash(Dir0, Dir) :-
  378	(   sub_atom(Dir0, _, _, 0, /)
  379	->  Dir = Dir0
  380	;   atom_concat(Dir0, /, Dir)
  381	)