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@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 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(http_settings,
   32	  [ http_show_settings/3,	% +Options
   33	    http_apply_settings/4	% +Request, +Options
   34	  ]).   35:- use_module(library('http/html_write')).   36:- use_module(library('http/html_head')).   37:- use_module(library('http/http_parameters')).   38:- use_module(library(option)).   39:- use_module(library(lists)).   40:- use_module(library(pairs)).   41:- use_module(library(debug)).   42:- use_module(library(settings)).   43
   44%%	http_show_settings(+Options)// is det
   45%
   46%	Emit an HTML representation of the current settings.  Options:
   47%
   48%	    * edit(+Boolean)
   49%
   50%	    * hide_module(+Boolean)
   51%	    If true, hide module headers from the user.
   52%
   53%	    * module(+ModuleList)
   54%	    If present, only show settings from modules in ModuleList.
   55
   56http_show_settings(Options) -->
   57	{ findall(M-N, current_setting(M:N), List),
   58	  keysort(List, Sorted),
   59	  group_pairs_by_key(Sorted, ByModule)
   60	},
   61	(   { option(edit(true), Options, false),
   62	      option(action(Action), Options, '/http/settings')
   63	    }
   64	->  html(form([ action(Action),
   65			method('GET')
   66		      ],
   67		      table(class(block),
   68			    \settings_table(ByModule, Options))))
   69	;   html([ table(class(block),
   70			 \settings_table(ByModule, Options))
   71		 ])
   72	).
   73
   74settings_table(ByModule, Options) -->
   75	(   {ByModule = [M-List],
   76	    \+ option(hide_module(_), Options)
   77	    }
   78	->  show_module(M, List, [hide_module(true)|Options])
   79	;   show_modules(ByModule, Options)
   80	),
   81	(   { option(edit(true), Options, true) }
   82	->  html(tr(class(buttons),
   83		    td([ colspan(2),
   84			 align(right)
   85		       ],
   86		       [ input([ type(reset) ]),
   87			 input([ type(submit), value('Apply') ])
   88		       ])))
   89	;   []
   90	).
   91
   92
   93show_modules([], _) -->
   94	[].
   95show_modules([M-List|T], Options) -->
   96	show_module(M, List, Options),
   97	show_modules(T, Options).
   98
   99show_module(Module, _Settings, Options) -->
  100	{ option(modules(ListOfModules), Options),
  101	  \+ memberchk(Module,ListOfModules)
  102	}, !.
  103show_module(Module, Settings, Options) -->
  104	show_module_header(Module, Options),
  105	show_settings(Settings, Module, odd, Options).
  106
  107show_module_header(_Module, Options) -->
  108	{ option(hide_module(true), Options, false)}, !.
  109show_module_header(Module, _Options) -->
  110	html(tr(th([colspan(2), class(group)], Module))).
  111
  112show_settings([], _, _, _) -->
  113	[].
  114show_settings([H|T], Module, EO, Options) -->
  115	show_setting(H, Module, EO, Options),
  116	{ negate_odd_even(EO, EO2) },
  117	show_settings(T, Module, EO2, Options).
  118
  119show_setting(H, Module, EO, Options) -->
  120	{ setting_property(Module:H, comment(Comment)),
  121	  setting_property(Module:H, type(Type)),
  122	  setting_title(Module:H, Title),
  123	  setting(Module:H, Value),
  124	  debug(settings, '~w: type=~w', [H, Type])
  125	},
  126	html(tr(class(EO),
  127		[ td([class(comment), title(Title)], Comment),
  128		  td(class(value),
  129		     \show_value(Type, Value, Module:H, Options))
  130		])).
  131
  132setting_title(Setting, Title) :-
  133	setting_property(Setting, File:Line),
  134	integer(Line), !,
  135	file_base_name(File, Base),
  136	format(atom(Title), '~q from ~w:~d', [Setting, Base, Line]).
  137setting_title(Setting, Title) :-
  138	format(atom(Title), '~q', [Setting]).
  139
  140
  141show_value(Type, Value, Id, Options) -->
  142	{ option(edit(true), Options, true) }, !,
  143	input_value(Type, Value, Id).
  144show_value(Type, Value, _, _Options) -->
  145	show_value(Type, Value).
  146
  147%%	show_value(+Type, +Value)// is det.
  148%
  149%	Emit a Value in non-editable representation.
  150
  151show_value(list(Type), Values) --> !,
  152	html(div(class(list), \show_list(Values, Type, odd))).
  153show_value(_, Value) -->
  154	html('~w'-[Value]).
  155
  156show_list([], _, _) -->
  157	[].
  158show_list([H|T], Type, Class) -->
  159	html(div(class(elem_+Class), \show_value(Type, H))),
  160	{ negate_odd_even(Class, NextClass) },
  161	show_list(T, Type, NextClass).
  162
  163
  164%%	input_value(+Type, +Value, +Id)// is det.
  165%
  166%	Emit an form-field for Value.
  167
  168:- multifile
  169	input_item/5.			% input_item(+Type, +Value, +Id)//
  170
  171input_value(Type, Value, Id) -->
  172	{ html_name(Id, Name) },
  173	(   input_item(Type, Value, Name)
  174	->  []
  175	;   builtin_input_item(Type, Value, Name)
  176	).
  177
  178builtin_input_item(boolean, Value, Name) --> !,
  179	builtin_input_item(oneof([true,false]), Value, Name).
  180builtin_input_item(between(L,U), Value, Name) --> !,
  181	html(input([ type(range),
  182		     name(Name),
  183		     min(L), max(U), value(Value)
  184		   ])).
  185builtin_input_item(oneof(List), Value, Name) --> !,
  186	html(select([name(Name)], \oneof(List, Value))).
  187builtin_input_item(atom, Value, Name) --> !,
  188	html(input([name(Name), size(40), value(Value)])).
  189builtin_input_item(_, Value, Name) -->
  190	{ format(string(S), '~q', [Value])
  191	},
  192	html(input([name(Name), size(40), value(S)])).
  193
  194oneof([], _) -->
  195	[].
  196oneof([H|T], Value) -->
  197	(   {H == Value}
  198	->  html([ option([selected(selected),value(H)], H) ])
  199	;   html([ option([                   value(H)], H) ])
  200	),
  201	oneof(T, Value).
  202
  203
  204		 /*******************************
  205		 *	   APPLY SETTINGS	*
  206		 *******************************/
  207
  208%%	http_apply_settings(+Request, +Options)// is det
  209%
  210%	Process  form  data  created   by  http_show_settings//1,  apply
  211%	changes to the settings and create   a  feedback page indicating
  212%	which settings have changed.  Options:
  213%
  214%		* save(Boolean)
  215%		If =true= and some settings have changed, call
  216%		save_settings/0.
  217%
  218%		* save_as(File)
  219%		If some settings have changed, call save_settings(File).
  220%		The option =save_as= overrules =save=.
  221
  222http_apply_settings(Request, Options) -->
  223	{ http_parameters(Request, [],
  224			  [ form_data(Data)
  225			  ]),
  226	  debug(settings, 'Form data: ~p', [Data]),
  227	  phrase(process_settings_form(Data), Changes)
  228	},
  229	report_changed(Changes, Options).
  230
  231
  232report_changed([], _) -->
  233	html(div(class(msg_informational), 'No changes')).
  234report_changed(L, _) -->
  235	{ memberchk(error(_), L) },
  236	report_errors(L).
  237report_changed(L, Options) -->
  238	{ length(L, N),
  239	  forall(member(change(Id, _, Value), L),
  240		 set_setting(Id, Value)),
  241	  (   option(save_as(File), Options)
  242	  ->  save_settings(File)
  243	  ;   option(save(true), Options, true)
  244	  ->  save_settings
  245	  ;   true
  246	  )
  247	},
  248	html(div(class(msg_informational), ['Changed ', N, ' settings'])).
  249
  250report_errors([]) -->
  251	[].
  252report_errors([error(Error)|T]) -->
  253	report_error(Error),
  254	report_errors(T).
  255report_errors([_|T]) -->
  256	report_errors(T).
  257
  258report_error(no_setting(Id)) -->
  259	{ format(string(Name), '~w', [Id]) },
  260	html(div(class(msg_error),
  261		 ['Setting ', Name, ' does not exist.'])).
  262report_error(bad_value(Id, RawValue)) -->
  263	{ format(string(Name), '~w', [Id]) },
  264	html(div(class(msg_error),
  265		 ['Wrong value for ', Name, ': ', RawValue])).
  266
  267
  268%%	process_settings_form(+FormData)//
  269%
  270%	Process the raw form data, producing a list holding terms of the
  271%	form:
  272%
  273%		* error(no_setting(Setting))
  274%		* error(bad_value(Setting, Value))
  275%		* change(Setting, Old, New)
  276
  277process_settings_form([]) -->
  278	[].
  279process_settings_form([Name = Value|T]) -->
  280	(   { html_name(Setting, Name) }
  281	->  process_form_field(Setting, Value)
  282	;   [ error(no_setting(Name)) ]
  283	),
  284	process_settings_form(T).
  285
  286process_form_field(Id, RawValue) -->
  287	(   { setting_property(Id, type(Type)) }
  288	->  (   { catch(convert_setting_text(Type, RawValue, Value), _, fail) }
  289	    ->	{ setting(Id, OldValue) },
  290		(   { Value == OldValue }
  291		->  []
  292		;   [change(Id, OldValue, Value)]
  293		)
  294	    ;	[ error(bad_value(Id, RawValue))]
  295	    )
  296	;   [ error(no_setting(Id)) ]
  297	).
  298
  299
  300
  301		 /*******************************
  302		 *	       UTIL		*
  303		 *******************************/
  304
  305%%	html_name(+Settings, -Name) is det.
  306%%	html_name(-Settings, +Name) is det.
  307%
  308%	Convert between Module:Setting and Name for use in form-fields.
  309
  310html_name(Module:Setting, Name) :-
  311	atomic_list_concat([Module, Setting], ':', Name).
  312
  313
  314%%	negate_odd_even(+OddEven, -EventOdd)
  315
  316negate_odd_even(odd, even).
  317negate_odd_even(even, odd)