35
36:- module(http_settings,
37 [ http_show_settings/3, 38 http_apply_settings/4 39 ]). 40:- use_module(library('http/html_write')). 41:- use_module(library('http/html_head')). 42:- use_module(library('http/http_parameters')). 43:- use_module(library(option)). 44:- use_module(library(lists)). 45:- use_module(library(pairs)). 46:- use_module(library(debug)). 47:- use_module(library(settings)). 48
60
61http_show_settings(Options) -->
62 { findall(M-N, current_setting(M:N), List),
63 keysort(List, Sorted),
64 group_pairs_by_key(Sorted, ByModule)
65 },
66 ( { option(edit(true), Options, false),
67 option(action(Action), Options, '/http/settings')
68 }
69 -> html(form([ action(Action),
70 method('GET')
71 ],
72 table(class(block),
73 \settings_table(ByModule, Options))))
74 ; html([ table(class(block),
75 \settings_table(ByModule, Options))
76 ])
77 ).
78
79settings_table(ByModule, Options) -->
80 ( {ByModule = [M-List],
81 \+ option(hide_module(_), Options)
82 }
83 -> show_module(M, List, [hide_module(true)|Options])
84 ; show_modules(ByModule, Options)
85 ),
86 ( { option(edit(true), Options, true) }
87 -> html(tr(class(buttons),
88 td([ colspan(2),
89 align(right)
90 ],
91 [ input([ type(reset) ]),
92 input([ type(submit), value('Apply') ])
93 ])))
94 ; []
95 ).
96
97
98show_modules([], _) -->
99 [].
100show_modules([M-List|T], Options) -->
101 show_module(M, List, Options),
102 show_modules(T, Options).
103
104show_module(Module, _Settings, Options) -->
105 { option(modules(ListOfModules), Options),
106 \+ memberchk(Module,ListOfModules)
107 },
108 !.
109show_module(Module, Settings, Options) -->
110 show_module_header(Module, Options),
111 show_settings(Settings, Module, odd, Options).
112
(_Module, Options) -->
114 { option(hide_module(true), Options, false)},
115 !.
116show_module_header(Module, _Options) -->
117 html(tr(th([colspan(2), class(group)], Module))).
118
119show_settings([], _, _, _) -->
120 [].
121show_settings([H|T], Module, EO, Options) -->
122 show_setting(H, Module, EO, Options),
123 { negate_odd_even(EO, EO2) },
124 show_settings(T, Module, EO2, Options).
125
126show_setting(H, Module, EO, Options) -->
127 { setting_property(Module:H, comment(Comment)),
128 setting_property(Module:H, type(Type)),
129 setting_title(Module:H, Title),
130 setting(Module:H, Value),
131 debug(settings, '~w: type=~w', [H, Type])
132 },
133 html(tr(class(EO),
134 [ td([class(comment), title(Title)], Comment),
135 td(class(value),
136 \show_value(Type, Value, Module:H, Options))
137 ])).
138
139setting_title(Setting, Title) :-
140 setting_property(Setting, File:Line),
141 integer(Line),
142 !,
143 file_base_name(File, Base),
144 format(atom(Title), '~q from ~w:~d', [Setting, Base, Line]).
145setting_title(Setting, Title) :-
146 format(atom(Title), '~q', [Setting]).
147
148
149show_value(Type, Value, Id, Options) -->
150 { option(edit(true), Options, true) },
151 !,
152 input_value(Type, Value, Id).
153show_value(Type, Value, _, _Options) -->
154 show_value(Type, Value).
155
159
160show_value(list(Type), Values) -->
161 !,
162 html(div(class(list), \show_list(Values, Type, odd))).
163show_value(_, Value) -->
164 html('~w'-[Value]).
165
166show_list([], _, _) -->
167 [].
168show_list([H|T], Type, Class) -->
169 html(div(class(elem_+Class), \show_value(Type, H))),
170 { negate_odd_even(Class, NextClass) },
171 show_list(T, Type, NextClass).
172
173
177
178:- multifile
179 input_item/5. 180
181input_value(Type, Value, Id) -->
182 { html_name(Id, Name) },
183 ( input_item(Type, Value, Name)
184 -> []
185 ; builtin_input_item(Type, Value, Name)
186 ).
187
188builtin_input_item(boolean, Value, Name) -->
189 !,
190 builtin_input_item(oneof([true,false]), Value, Name).
191builtin_input_item(between(L,U), Value, Name) -->
192 !,
193 html(input([ type(range),
194 name(Name),
195 min(L), max(U), value(Value)
196 ])).
197builtin_input_item(oneof(List), Value, Name) -->
198 !,
199 html(select([name(Name)], \oneof(List, Value))).
200builtin_input_item(atom, Value, Name) -->
201 !,
202 html(input([name(Name), size(40), value(Value)])).
203builtin_input_item(_, Value, Name) -->
204 { format(string(S), '~q', [Value])
205 },
206 html(input([name(Name), size(40), value(S)])).
207
208oneof([], _) -->
209 [].
210oneof([H|T], Value) -->
211 ( {H == Value}
212 -> html([ option([selected(selected),value(H)], H) ])
213 ; html([ option([ value(H)], H) ])
214 ),
215 oneof(T, Value).
216
217
218 221
235
236http_apply_settings(Request, Options) -->
237 { http_parameters(Request, [],
238 [ form_data(Data)
239 ]),
240 debug(settings, 'Form data: ~p', [Data]),
241 phrase(process_settings_form(Data), Changes)
242 },
243 report_changed(Changes, Options).
244
245
246report_changed([], _) -->
247 html(div(class(msg_informational), 'No changes')).
248report_changed(L, _) -->
249 { memberchk(error(_), L) },
250 report_errors(L).
251report_changed(L, Options) -->
252 { length(L, N),
253 forall(member(change(Id, _, Value), L),
254 set_setting(Id, Value)),
255 ( option(save_as(File), Options)
256 -> save_settings(File)
257 ; option(save(true), Options, true)
258 -> save_settings
259 ; true
260 )
261 },
262 html(div(class(msg_informational), ['Changed ', N, ' settings'])).
263
264report_errors([]) -->
265 [].
266report_errors([error(Error)|T]) -->
267 report_error(Error),
268 report_errors(T).
269report_errors([_|T]) -->
270 report_errors(T).
271
272report_error(no_setting(Id)) -->
273 { format(string(Name), '~w', [Id]) },
274 html(div(class(msg_error),
275 ['Setting ', Name, ' does not exist.'])).
276report_error(bad_value(Id, RawValue)) -->
277 { format(string(Name), '~w', [Id]) },
278 html(div(class(msg_error),
279 ['Wrong value for ', Name, ': ', RawValue])).
280
281
290
291process_settings_form([]) -->
292 [].
293process_settings_form([Name = Value|T]) -->
294 ( { html_name(Setting, Name) }
295 -> process_form_field(Setting, Value)
296 ; [ error(no_setting(Name)) ]
297 ),
298 process_settings_form(T).
299
300process_form_field(Id, RawValue) -->
301 ( { setting_property(Id, type(Type)) }
302 -> ( { catch(convert_setting_text(Type, RawValue, Value), _, fail) }
303 -> { setting(Id, OldValue) },
304 ( { Value == OldValue }
305 -> []
306 ; [change(Id, OldValue, Value)]
307 )
308 ; [ error(bad_value(Id, RawValue))]
309 )
310 ; [ error(no_setting(Id)) ]
311 ).
312
313
314
315 318
323
324html_name(Module:Setting, Name) :-
325 atomic_list_concat([Module, Setting], ':', Name).
326
327
329
330negate_odd_even(odd, even).
331negate_odd_even(even, odd)