Chris@0
|
1 /* This file is part of ClioPatria.
|
Chris@0
|
2
|
Chris@0
|
3 Author:
|
Chris@0
|
4 HTTP: http://e-culture.multimedian.nl/
|
Chris@0
|
5 GITWEB: http://gollem.science.uva.nl/git/ClioPatria.git
|
Chris@0
|
6 GIT: git://gollem.science.uva.nl/home/git/ClioPatria.git
|
Chris@0
|
7 GIT: http://gollem.science.uva.nl/home/git/ClioPatria.git
|
Chris@0
|
8 Copyright: 2007, E-Culture/MultimediaN
|
Chris@0
|
9
|
Chris@0
|
10 ClioPatria is free software: you can redistribute it and/or modify
|
Chris@0
|
11 it under the terms of the GNU General Public License as published by
|
Chris@0
|
12 the Free Software Foundation, either version 2 of the License, or
|
Chris@0
|
13 (at your option) any later version.
|
Chris@0
|
14
|
Chris@0
|
15 ClioPatria is distributed in the hope that it will be useful,
|
Chris@0
|
16 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Chris@0
|
17 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Chris@0
|
18 GNU General Public License for more details.
|
Chris@0
|
19
|
Chris@0
|
20 You should have received a copy of the GNU General Public License
|
Chris@0
|
21 along with ClioPatria. If not, see <http://www.gnu.org/licenses/>.
|
Chris@0
|
22 */
|
Chris@0
|
23
|
Chris@0
|
24 :- module(settings,
|
Chris@0
|
25 [ setting/4, % :Name, +Type, +Default, +Comment, +Src
|
Chris@0
|
26 setting/2, % :Name, ?Value
|
Chris@0
|
27 set_setting/2, % :Name, +Value
|
Chris@0
|
28 restore_setting/1, % :Name
|
Chris@0
|
29 load_settings/1, % +File
|
Chris@0
|
30 load_settings/2, % +File, +Options
|
Chris@0
|
31 save_settings/0,
|
Chris@0
|
32 save_settings/1, % +File
|
Chris@0
|
33 current_setting/1, % Module:Name
|
Chris@0
|
34 setting_property/2, % ?Setting, ?Property
|
Chris@0
|
35 list_settings/0,
|
Chris@0
|
36
|
Chris@0
|
37 convert_setting_text/3 % +Type, +Text, -Value
|
Chris@0
|
38 ]).
|
Chris@0
|
39 :- use_module(library(error)).
|
Chris@0
|
40 :- use_module(library(broadcast)).
|
Chris@0
|
41 :- use_module(library(debug)).
|
Chris@0
|
42 :- use_module(library(option)).
|
Chris@0
|
43
|
Chris@0
|
44 /** <module> Setting management
|
Chris@0
|
45
|
Chris@0
|
46 This library allows management of configuration settings for Prolog
|
Chris@0
|
47 applications. Applications define settings in one or multiple files
|
Chris@0
|
48 using the directive setting/4 as illustrated below:
|
Chris@0
|
49
|
Chris@0
|
50 ==
|
Chris@0
|
51 :- use_module(library(setting)).
|
Chris@0
|
52
|
Chris@0
|
53 :- setting(version, atom, '1.0', 'Current version').
|
Chris@0
|
54 :- setting(timeout, number, 20, 'Timeout in seconds').
|
Chris@0
|
55 ==
|
Chris@0
|
56
|
Chris@0
|
57 The directive is subject to term_expansion/2, which guarantees proper
|
Chris@0
|
58 synchronisation of the database if source-files are reloaded. This
|
Chris@0
|
59 implies it is *not* possible to call setting/4 as a predicate.
|
Chris@0
|
60
|
Chris@0
|
61 Settings are local to a module. This implies they are defined in a
|
Chris@0
|
62 two-level namespace. Managing settings per module greatly simplifies
|
Chris@0
|
63 assembling large applications from multiple modules that configuration
|
Chris@0
|
64 through settings. This settings management library ensures proper
|
Chris@0
|
65 access, loading and saving of settings.
|
Chris@0
|
66
|
Chris@0
|
67 @see library(config) distributed with XPCE provides an alternative
|
Chris@0
|
68 aimed at graphical applications.
|
Chris@0
|
69 @author Jan Wielemaker
|
Chris@0
|
70 */
|
Chris@0
|
71
|
Chris@0
|
72 :- dynamic
|
Chris@0
|
73 value/3, % Name, Module, Value
|
Chris@0
|
74 local_file/1. % Path
|
Chris@0
|
75
|
Chris@0
|
76 :- multifile
|
Chris@0
|
77 current_setting/6. % Name, Module, Type, Default, Comment, Source
|
Chris@0
|
78
|
Chris@0
|
79 :- module_transparent
|
Chris@0
|
80 setting(:, +, +, +),
|
Chris@0
|
81 setting(:, ?),
|
Chris@0
|
82 set_setting(:, +),
|
Chris@0
|
83 current_setting(:),
|
Chris@0
|
84 restore_setting(:).
|
Chris@0
|
85
|
Chris@0
|
86 %% setting(Name, Type, Default, Comment) is det.
|
Chris@0
|
87 %
|
Chris@0
|
88 % Define a setting. Name denotes the name of the setting, Type its
|
Chris@0
|
89 % type. Default is the value before it is modified. Default refer
|
Chris@0
|
90 % to environment variables and use arithmetic expressions as
|
Chris@0
|
91 % defined by eval_default/4.
|
Chris@0
|
92 %
|
Chris@0
|
93 % @param Name Name of the setting (an atom)
|
Chris@0
|
94 % @param Type Type for setting. One of =any= or a type defined
|
Chris@0
|
95 % by must_be/2.
|
Chris@0
|
96 % @param Default Default value for the setting.
|
Chris@0
|
97 % @param Comment Atom containing a (short) descriptive note.
|
Chris@0
|
98
|
Chris@0
|
99
|
Chris@0
|
100 setting(_Name, _Type, _Default, _Comment) :-
|
Chris@0
|
101 throw(error(context_error(only_in_directive), _)).
|
Chris@0
|
102
|
Chris@0
|
103 :- multifile
|
Chris@0
|
104 user:term_expansion/2.
|
Chris@0
|
105
|
Chris@0
|
106 user:term_expansion((:- setting(QName, Type, Default, Comment)),
|
Chris@0
|
107 Expanded) :-
|
Chris@0
|
108 prolog_load_context(module, M0),
|
Chris@0
|
109 strip_module(M0:QName, Module, Name),
|
Chris@0
|
110 must_be(atom, Name),
|
Chris@0
|
111 to_atom(Comment, CommentAtom),
|
Chris@0
|
112 eval_default(Default, Module, Type, Value),
|
Chris@0
|
113 check_type(Type, Value),
|
Chris@0
|
114 ( current_setting(Name, Module, _, _, _, OldLoc)
|
Chris@0
|
115 -> format(string(Message),
|
Chris@0
|
116 'Already defined at: ~w', [OldLoc]),
|
Chris@0
|
117 throw(error(permission_error(redefine, setting, Name),
|
Chris@0
|
118 context(Message, _)))
|
Chris@0
|
119 ; source_location(File, Line)
|
Chris@0
|
120 -> Expanded = settings:current_setting(Name, Module, Type, Default,
|
Chris@0
|
121 CommentAtom, File:Line)
|
Chris@0
|
122 ).
|
Chris@0
|
123
|
Chris@0
|
124 to_atom(Atom, Atom) :-
|
Chris@0
|
125 atom(Atom), !.
|
Chris@0
|
126 to_atom(String, Atom) :-
|
Chris@0
|
127 format(atom(Atom), '~s', String).
|
Chris@0
|
128
|
Chris@0
|
129 %% setting(:Name, ?Value) is nondet.
|
Chris@0
|
130 %
|
Chris@0
|
131 % True if Name is a currently defined setting with Value.
|
Chris@0
|
132 %
|
Chris@0
|
133 % @error existence_error(setting, Name)
|
Chris@0
|
134
|
Chris@0
|
135 setting(QName, Value) :-
|
Chris@0
|
136 strip_module(QName, Module, Name),
|
Chris@0
|
137 ( ground(Name)
|
Chris@0
|
138 -> ( value(Name, Module, Value0)
|
Chris@0
|
139 -> Value = Value0
|
Chris@0
|
140 ; current_setting(Name, Module, Type, Default, _, _)
|
Chris@0
|
141 -> eval_default(Default, Module, Type, Value)
|
Chris@0
|
142 ; existence_error(setting, Module:Name)
|
Chris@0
|
143 )
|
Chris@0
|
144 ; current_setting(Name, Module, _, _, _, _),
|
Chris@0
|
145 setting(Module:Name, Value)
|
Chris@0
|
146 ).
|
Chris@0
|
147
|
Chris@0
|
148
|
Chris@0
|
149 %% eval_default(+Default, +Module, +Type, -Value) is det.
|
Chris@0
|
150 %
|
Chris@0
|
151 % Convert the settings default value. The notation allows for some
|
Chris@0
|
152 % `function-style' notations to make the library more generic:
|
Chris@0
|
153 %
|
Chris@0
|
154 % * env(Name)
|
Chris@0
|
155 % Get value from the given environment variable. The value
|
Chris@0
|
156 % is handed to convert_setting_text/3 to convert the
|
Chris@0
|
157 % textual representation into a Prolog term. Raises an
|
Chris@0
|
158 % existence_error of the variable is not defined.
|
Chris@0
|
159 %
|
Chris@0
|
160 % * env(Name, Default)
|
Chris@0
|
161 % As env(Name), but uses the value Default if the variable
|
Chris@0
|
162 % is not defined.
|
Chris@0
|
163 %
|
Chris@0
|
164 % * setting(Name)
|
Chris@0
|
165 % Ask the value of another setting.
|
Chris@0
|
166 %
|
Chris@0
|
167 % * Expression
|
Chris@0
|
168 % If Type is numeric, evaluate the expression. env(Var)
|
Chris@0
|
169 % evaluates to the value of an environment variable.
|
Chris@0
|
170 % If Type is =atom=, concatenate A+B+.... Elements of the
|
Chris@0
|
171 % expression can be env(Name).
|
Chris@0
|
172
|
Chris@0
|
173 :- dynamic
|
Chris@0
|
174 setting_cache/3.
|
Chris@0
|
175 :- volatile
|
Chris@0
|
176 setting_cache/3.
|
Chris@0
|
177
|
Chris@0
|
178 :- multifile
|
Chris@0
|
179 eval_default/3. % +Default, +Type, -Value
|
Chris@0
|
180
|
Chris@0
|
181 eval_default(Default, _, Type, Value) :-
|
Chris@0
|
182 eval_default(Default, Type, Val), !,
|
Chris@0
|
183 Value = Val.
|
Chris@0
|
184 eval_default(Default, _, _, Value) :-
|
Chris@0
|
185 atomic(Default), !,
|
Chris@0
|
186 Value = Default.
|
Chris@0
|
187 eval_default(Default, _, Type, Value) :-
|
Chris@0
|
188 setting_cache(Default, Type, Val), !,
|
Chris@0
|
189 Value = Val.
|
Chris@0
|
190 eval_default(env(Name), _, Type, Value) :- !,
|
Chris@0
|
191 ( getenv(Name, TextValue)
|
Chris@0
|
192 -> convert_setting_text(Type, TextValue, Val),
|
Chris@0
|
193 assert(setting_cache(env(Name), Type, Val)),
|
Chris@0
|
194 Value = Val
|
Chris@0
|
195 ; existence_error(environment_variable, Name)
|
Chris@0
|
196 ).
|
Chris@0
|
197 eval_default(env(Name, Default), _, Type, Value) :- !,
|
Chris@0
|
198 ( getenv(Name, TextValue)
|
Chris@0
|
199 -> convert_setting_text(Type, TextValue, Val)
|
Chris@0
|
200 ; Value = Default
|
Chris@0
|
201 ),
|
Chris@0
|
202 assert(setting_cache(env(Name), Type, Val)),
|
Chris@0
|
203 Value = Val.
|
Chris@0
|
204 eval_default(setting(Name), Module, Type, Value) :- !,
|
Chris@0
|
205 strip_module(Module:Name, M, N),
|
Chris@0
|
206 setting(M:N, Value),
|
Chris@0
|
207 must_be(Type, Value).
|
Chris@0
|
208 eval_default(Expr, _, Type, Value) :-
|
Chris@0
|
209 numeric_type(Type, Basic), !,
|
Chris@0
|
210 Val0 is Expr,
|
Chris@0
|
211 ( Basic == float
|
Chris@0
|
212 -> Val is float(Val0)
|
Chris@0
|
213 ; Basic = integer
|
Chris@0
|
214 -> Val is round(Val0)
|
Chris@0
|
215 ; Val = Val0
|
Chris@0
|
216 ),
|
Chris@0
|
217 assert(setting_cache(Expr, Type, Val)),
|
Chris@0
|
218 Value = Val.
|
Chris@0
|
219 eval_default(A+B, Module, atom, Value) :- !,
|
Chris@0
|
220 phrase(expr_to_list(A+B, Module), L),
|
Chris@0
|
221 concat_atom(L, Val),
|
Chris@0
|
222 assert(setting_cache(A+B, atom, Val)),
|
Chris@0
|
223 Value = Val.
|
Chris@0
|
224 eval_default(List, Module, list(Type), Value) :- !,
|
Chris@0
|
225 eval_list_default(List, Module, Type, Val),
|
Chris@0
|
226 assert(setting_cache(List, list(Type), Val)),
|
Chris@0
|
227 Value = Val.
|
Chris@0
|
228 eval_default(Default, _, _, Default).
|
Chris@0
|
229
|
Chris@0
|
230
|
Chris@0
|
231 %% eval_list_default(+List, +Module, +ElementType, -DefaultList)
|
Chris@0
|
232 %
|
Chris@0
|
233 % Evaluate the default for a list of values.
|
Chris@0
|
234
|
Chris@0
|
235 eval_list_default([], _, _, []).
|
Chris@0
|
236 eval_list_default([H0|T0], Module, Type, [H|T]) :-
|
Chris@0
|
237 eval_default(H0, Module, Type, H),
|
Chris@0
|
238 eval_list_default(T0, Module, Type, T).
|
Chris@0
|
239
|
Chris@0
|
240 %% expr_to_list(+Expression, +Module)// is det.
|
Chris@0
|
241 %
|
Chris@0
|
242 % Process the components to create an atom. Atom concatenation is
|
Chris@0
|
243 % expressed as A+B. Components may refer to envrionment variables.
|
Chris@0
|
244
|
Chris@0
|
245 expr_to_list(A+B, Module) --> !,
|
Chris@0
|
246 expr_to_list(A, Module),
|
Chris@0
|
247 expr_to_list(B, Module).
|
Chris@0
|
248 expr_to_list(env(Name), _) --> !,
|
Chris@0
|
249 ( { getenv(Name, Text) }
|
Chris@0
|
250 -> [Text]
|
Chris@0
|
251 ; { existence_error(environment_variable, Name) }
|
Chris@0
|
252 ).
|
Chris@0
|
253 expr_to_list(env(Name, Default), _) --> !,
|
Chris@0
|
254 ( { getenv(Name, Text) }
|
Chris@0
|
255 -> [Text]
|
Chris@0
|
256 ; [Default]
|
Chris@0
|
257 ).
|
Chris@0
|
258 expr_to_list(setting(Name), Module) --> !,
|
Chris@0
|
259 { strip_module(Module:Name, M, N),
|
Chris@0
|
260 setting(M:N, Value)
|
Chris@0
|
261 },
|
Chris@0
|
262 [ Value ].
|
Chris@0
|
263 expr_to_list(A, _) -->
|
Chris@0
|
264 [A].
|
Chris@0
|
265
|
Chris@0
|
266 %% env(+Name:atom, -Value:number) is det.
|
Chris@0
|
267 %% env(+Name:atom, +Default:number, -Value:number) is det
|
Chris@0
|
268 %
|
Chris@0
|
269 % Evaluate environment variables on behalf of arithmetic
|
Chris@0
|
270 % expressions.
|
Chris@0
|
271
|
Chris@0
|
272 :- arithmetic_function(env/1).
|
Chris@0
|
273 :- arithmetic_function(env/2).
|
Chris@0
|
274
|
Chris@0
|
275 env(Name, Value) :-
|
Chris@0
|
276 ( getenv(Name, Text)
|
Chris@0
|
277 -> convert_setting_text(number, Text, Value)
|
Chris@0
|
278 ; existence_error(environment_variable, Name)
|
Chris@0
|
279 ).
|
Chris@0
|
280 env(Name, Default, Value) :-
|
Chris@0
|
281 ( getenv(Name, Text)
|
Chris@0
|
282 -> convert_setting_text(number, Text, Value)
|
Chris@0
|
283 ; Value = Default
|
Chris@0
|
284 ).
|
Chris@0
|
285
|
Chris@0
|
286
|
Chris@0
|
287 %% numeric_type(+Type, -BaseType)
|
Chris@0
|
288 %
|
Chris@0
|
289 % True if Type is a numeric type and BaseType is the associated
|
Chris@0
|
290 % basic Prolog type. BaseType is one of =integer=, =float= or
|
Chris@0
|
291 % =number=.
|
Chris@0
|
292
|
Chris@0
|
293 numeric_type(integer, integer).
|
Chris@0
|
294 numeric_type(nonneg, integer).
|
Chris@0
|
295 numeric_type(float, float).
|
Chris@0
|
296 numeric_type(between(L,_), Type) :-
|
Chris@0
|
297 ( integer(L) -> Type = integer ; Type = float ).
|
Chris@0
|
298
|
Chris@0
|
299
|
Chris@0
|
300 %% set_setting(:Name, +Value) is det.
|
Chris@0
|
301 %
|
Chris@0
|
302 % Change a setting. Performs existence and type-checking for the
|
Chris@0
|
303 % setting. If the effective value of the setting is changed it
|
Chris@0
|
304 % broadcasts the event below.
|
Chris@0
|
305 %
|
Chris@0
|
306 % settings(changed(Module:Name, Old, New))
|
Chris@0
|
307 %
|
Chris@0
|
308 % @error existence_error(setting, Name)
|
Chris@0
|
309 % @error type_error(Type, Value)
|
Chris@0
|
310
|
Chris@0
|
311 set_setting(QName, Value) :-
|
Chris@0
|
312 strip_module(QName, Module, Name),
|
Chris@0
|
313 must_be(atom, Name),
|
Chris@0
|
314 ( current_setting(Name, Module, Type, Default0, _Comment, _Src),
|
Chris@0
|
315 eval_default(Default0, Module, Type, Default)
|
Chris@0
|
316 -> ( Value == Default
|
Chris@0
|
317 -> retract_setting(Module:Name)
|
Chris@0
|
318 ; value(Name, Module, Value)
|
Chris@0
|
319 -> true
|
Chris@0
|
320 ; check_type(Type, Value)
|
Chris@0
|
321 -> setting(Module:Name, Old),
|
Chris@0
|
322 retract_setting(Module:Name),
|
Chris@0
|
323 assert_setting(Module:Name, Value),
|
Chris@0
|
324 broadcast(settings(changed(Module:Name, Old, Value)))
|
Chris@0
|
325 )
|
Chris@0
|
326 ; existence_error(setting, Name)
|
Chris@0
|
327 ).
|
Chris@0
|
328
|
Chris@0
|
329 retract_setting(Module:Name) :-
|
Chris@0
|
330 retractall(value(Name, Module, _)).
|
Chris@0
|
331
|
Chris@0
|
332 assert_setting(Module:Name, Value) :-
|
Chris@0
|
333 assert(value(Name, Module, Value)).
|
Chris@0
|
334
|
Chris@0
|
335 %% restore_setting(:Name) is det.
|
Chris@0
|
336 %
|
Chris@0
|
337 % Restore the value of setting Name to its default. Broadcast a
|
Chris@0
|
338 % change like set_setting/2 if the current value is not the
|
Chris@0
|
339 % default.
|
Chris@0
|
340
|
Chris@0
|
341 restore_setting(QName) :-
|
Chris@0
|
342 strip_module(QName, Module, Name),
|
Chris@0
|
343 must_be(atom, Name),
|
Chris@0
|
344 ( value(Name, Module, Old)
|
Chris@0
|
345 -> retract_setting(Module:Name),
|
Chris@0
|
346 setting(Module:Name, Value),
|
Chris@0
|
347 ( Old \== Value
|
Chris@0
|
348 -> broadcast(settings(changed(Module:Name, Old, Value)))
|
Chris@0
|
349 ; true
|
Chris@0
|
350 )
|
Chris@0
|
351 ; true
|
Chris@0
|
352 ).
|
Chris@0
|
353
|
Chris@0
|
354
|
Chris@0
|
355 /*******************************
|
Chris@0
|
356 * TYPES *
|
Chris@0
|
357 *******************************/
|
Chris@0
|
358
|
Chris@0
|
359 %% check_type(+Type, +Term)
|
Chris@0
|
360 %
|
Chris@0
|
361 % Type checking for settings. Currently simply forwarded to
|
Chris@0
|
362 % must_be/2.
|
Chris@0
|
363
|
Chris@0
|
364 check_type(Type, Term) :-
|
Chris@0
|
365 must_be(Type, Term).
|
Chris@0
|
366
|
Chris@0
|
367
|
Chris@0
|
368 /*******************************
|
Chris@0
|
369 * FILE *
|
Chris@0
|
370 *******************************/
|
Chris@0
|
371
|
Chris@0
|
372 %% load_settings(File) is det.
|
Chris@0
|
373 %% load_settings(File, +Options) is det.
|
Chris@0
|
374 %
|
Chris@0
|
375 % Load local settings from File. Succeeds if File does not exist,
|
Chris@0
|
376 % setting the default save-file to File. Options are:
|
Chris@0
|
377 %
|
Chris@0
|
378 % * undefined(+Action)
|
Chris@0
|
379 % Define how to handle settings that are not defined. When
|
Chris@0
|
380 % =error=, an error is printed and the setting is ignored.
|
Chris@0
|
381 % when =load=, the setting is loaded anyway, waiting for a
|
Chris@0
|
382 % definition.
|
Chris@0
|
383
|
Chris@0
|
384 load_settings(File) :-
|
Chris@0
|
385 load_settings(File, []).
|
Chris@0
|
386
|
Chris@0
|
387 load_settings(File, Options) :-
|
Chris@0
|
388 absolute_file_name(File, Path,
|
Chris@0
|
389 [ access(read),
|
Chris@0
|
390 file_errors(fail)
|
Chris@0
|
391 ]), !,
|
Chris@0
|
392 assert(local_file(Path)),
|
Chris@0
|
393 open(Path, read, In, [encoding(utf8)]),
|
Chris@0
|
394 read_setting(In, T0),
|
Chris@0
|
395 call_cleanup(load_settings(T0, In, Options), close(In)).
|
Chris@0
|
396 load_settings(File, _) :-
|
Chris@0
|
397 absolute_file_name(File, Path,
|
Chris@0
|
398 [ access(write),
|
Chris@0
|
399 file_errors(fail)
|
Chris@0
|
400 ]), !,
|
Chris@0
|
401 assert(local_file(Path)).
|
Chris@0
|
402 load_settings(_, _).
|
Chris@0
|
403
|
Chris@0
|
404 load_settings(end_of_file, _, _) :- !.
|
Chris@0
|
405 load_settings(Setting, In, Options) :-
|
Chris@0
|
406 catch(store_setting(Setting, Options), E,
|
Chris@0
|
407 print_message(warning, E)),
|
Chris@0
|
408 read_setting(In, Next),
|
Chris@0
|
409 load_settings(Next, In, Options).
|
Chris@0
|
410
|
Chris@0
|
411 read_setting(In, Term) :-
|
Chris@0
|
412 read_term(In, Term,
|
Chris@0
|
413 [ errors(dec10)
|
Chris@0
|
414 ]).
|
Chris@0
|
415
|
Chris@0
|
416 %% store_setting(Term, +Options)
|
Chris@0
|
417 %
|
Chris@0
|
418 % Store setting loaded from file in the Prolog database.
|
Chris@0
|
419
|
Chris@0
|
420 store_setting(setting(Module:Name, Value), _) :-
|
Chris@0
|
421 current_setting(Name, Module, Type, Default0, _Commentm, _Src), !,
|
Chris@0
|
422 eval_default(Default0, Module, Type, Default),
|
Chris@0
|
423 ( Value == Default
|
Chris@0
|
424 -> true
|
Chris@0
|
425 ; check_type(Type, Value),
|
Chris@0
|
426 assert(value(Name, Module, Value)),
|
Chris@0
|
427 broadcast(settings(changed(Module:Name, Default, Value)))
|
Chris@0
|
428 ).
|
Chris@0
|
429 store_setting(setting(Module:Name, Value), Options) :-
|
Chris@0
|
430 ( option(undefined(load), Options, load)
|
Chris@0
|
431 -> assert(value(Name, Module, Value))
|
Chris@0
|
432 ; existence_error(setting, Module:Name)
|
Chris@0
|
433 ).
|
Chris@0
|
434 store_setting(Term, _) :-
|
Chris@0
|
435 type_error(setting, Term).
|
Chris@0
|
436
|
Chris@0
|
437 %% save_settings is det.
|
Chris@0
|
438 %% save_settings(+File) is det.
|
Chris@0
|
439 %
|
Chris@0
|
440 % Save modified settings to File.
|
Chris@0
|
441
|
Chris@0
|
442 save_settings :-
|
Chris@0
|
443 local_file(File), !,
|
Chris@0
|
444 save_settings(File).
|
Chris@0
|
445
|
Chris@0
|
446 save_settings(File) :-
|
Chris@0
|
447 absolute_file_name(File, Path,
|
Chris@0
|
448 [ access(write)
|
Chris@0
|
449 ]), !,
|
Chris@0
|
450 open(Path, write, Out,
|
Chris@0
|
451 [ encoding(utf8),
|
Chris@0
|
452 bom(true)
|
Chris@0
|
453 ]),
|
Chris@0
|
454 write_setting_header(Out),
|
Chris@0
|
455 forall(current_setting(Name, Module, _, _, _, _),
|
Chris@0
|
456 save_setting(Out, Module:Name)),
|
Chris@0
|
457 close(Out).
|
Chris@0
|
458
|
Chris@0
|
459
|
Chris@0
|
460 write_setting_header(Out) :-
|
Chris@0
|
461 get_time(Now),
|
Chris@0
|
462 format_time(string(Date), '%+', Now),
|
Chris@0
|
463 format(Out, '/* Saved settings~n', []),
|
Chris@0
|
464 format(Out, ' Date: ~w~n', [Date]),
|
Chris@0
|
465 format(Out, '*/~n~n', []).
|
Chris@0
|
466
|
Chris@0
|
467 save_setting(Out, Module:Name) :-
|
Chris@0
|
468 current_setting(Name, Module, Type, Default, Comment, _Src),
|
Chris@0
|
469 ( value(Name, Module, Value),
|
Chris@0
|
470 \+ ( eval_default(Default, Module, Type, DefValue),
|
Chris@0
|
471 debug(setting, '~w <-> ~w~n', [DefValue, Value]),
|
Chris@0
|
472 DefValue =@= Value
|
Chris@0
|
473 )
|
Chris@0
|
474 -> format(Out, '~n% ~w~n', [Comment]),
|
Chris@0
|
475 format(Out, 'setting(~q:~q, ~q).~n', [Module, Name, Value])
|
Chris@0
|
476 ; true
|
Chris@0
|
477 ).
|
Chris@0
|
478
|
Chris@0
|
479 %% current_setting(?Setting) is nondet.
|
Chris@0
|
480 %
|
Chris@0
|
481 % True if Setting is a currently defined setting
|
Chris@0
|
482
|
Chris@0
|
483 current_setting(Setting) :-
|
Chris@0
|
484 ground(Setting), !,
|
Chris@0
|
485 strip_module(Setting, Module, Name),
|
Chris@0
|
486 current_setting(Name, Module, _, _, _, _).
|
Chris@0
|
487 current_setting(Module:Name) :-
|
Chris@0
|
488 current_setting(Name, Module, _, _, _, _).
|
Chris@0
|
489
|
Chris@0
|
490 %% setting_property(+Setting, +Property) is det.
|
Chris@0
|
491 %% setting_property(?Setting, ?Property) is nondet.
|
Chris@0
|
492 %
|
Chris@0
|
493 % Query currently defined settings. Property is one of
|
Chris@0
|
494 %
|
Chris@0
|
495 % * comment(-Atom)
|
Chris@0
|
496 % * type(-Type)
|
Chris@0
|
497 % Type of the setting.
|
Chris@0
|
498 % * default(-Default)
|
Chris@0
|
499 % Default value. If this is an expression, it is
|
Chris@0
|
500 % evaluated.
|
Chris@0
|
501
|
Chris@0
|
502 setting_property(Setting, Property) :-
|
Chris@0
|
503 ground(Setting), !,
|
Chris@0
|
504 Setting = Module:Name,
|
Chris@0
|
505 current_setting(Name, Module, Type, Default, Comment, _Src), !,
|
Chris@0
|
506 setting_property(Property, Module, Type, Default, Comment).
|
Chris@0
|
507 setting_property(Setting, Property) :-
|
Chris@0
|
508 Setting = Module:Name,
|
Chris@0
|
509 current_setting(Name, Module, Type, Default, Comment, _Src),
|
Chris@0
|
510 setting_property(Property, Module, Type, Default, Comment).
|
Chris@0
|
511
|
Chris@0
|
512 setting_property(type(Type), _, Type, _, _).
|
Chris@0
|
513 setting_property(default(Default), M, Type, Default0, _) :-
|
Chris@0
|
514 eval_default(Default0, M, Type, Default).
|
Chris@0
|
515 setting_property(comment(Comment), _, _, _, Comment).
|
Chris@0
|
516
|
Chris@0
|
517 %% list_settings
|
Chris@0
|
518 %
|
Chris@0
|
519 % List settings to =current_output=.
|
Chris@0
|
520
|
Chris@0
|
521 list_settings :-
|
Chris@0
|
522 format('~`=t~72|~n'),
|
Chris@0
|
523 format('~w~t~20| ~w~w~t~40| ~w~n', ['Name', 'Value (*=modified)', '', 'Comment']),
|
Chris@0
|
524 format('~`=t~72|~n'),
|
Chris@0
|
525 forall(current_setting(Setting),
|
Chris@0
|
526 list_setting(Setting)).
|
Chris@0
|
527
|
Chris@0
|
528 list_setting(Module:Name) :-
|
Chris@0
|
529 current_setting(Name, Module, Type, Default0, Comment, _Src),
|
Chris@0
|
530 eval_default(Default0, Module, Type, Default),
|
Chris@0
|
531 setting(Module:Name, Value),
|
Chris@0
|
532 ( Value \== Default
|
Chris@0
|
533 -> Modified = (*)
|
Chris@0
|
534 ; Modified = ''
|
Chris@0
|
535 ),
|
Chris@0
|
536 format('~w~t~20| ~q~w~t~40| ~w~n', [Module:Name, Value, Modified, Comment]).
|
Chris@0
|
537
|
Chris@0
|
538
|
Chris@0
|
539 /*******************************
|
Chris@0
|
540 * TYPES *
|
Chris@0
|
541 *******************************/
|
Chris@0
|
542
|
Chris@0
|
543 %% convert_setting_text(+Type, +Text, -Value)
|
Chris@0
|
544 %
|
Chris@0
|
545 % Converts from textual form to Prolog Value. Used to convert
|
Chris@0
|
546 % values obtained from the environment. Public to provide support
|
Chris@0
|
547 % in user-interfaces to this library.
|
Chris@0
|
548 %
|
Chris@0
|
549 % @error type_error(Type, Value)
|
Chris@0
|
550
|
Chris@0
|
551 :- multifile
|
Chris@0
|
552 convert_text/3. % +Type, +Text, -Value
|
Chris@0
|
553
|
Chris@0
|
554 convert_setting_text(Type, Text, Value) :-
|
Chris@0
|
555 convert_text(Type, Text, Value), !.
|
Chris@0
|
556 convert_setting_text(atom, Value, Value) :- !,
|
Chris@0
|
557 must_be(atom, Value).
|
Chris@0
|
558 convert_setting_text(boolean, Value, Value) :- !,
|
Chris@0
|
559 must_be(boolean, Value).
|
Chris@0
|
560 convert_setting_text(integer, Atom, Number) :- !,
|
Chris@0
|
561 term_to_atom(Term, Atom),
|
Chris@0
|
562 Number is round(Term).
|
Chris@0
|
563 convert_setting_text(float, Atom, Number) :- !,
|
Chris@0
|
564 term_to_atom(Term, Atom),
|
Chris@0
|
565 Number is float(Term).
|
Chris@0
|
566 convert_setting_text(between(L,U), Atom, Number) :- !,
|
Chris@0
|
567 ( integer(L)
|
Chris@0
|
568 -> convert_setting_text(integer, Atom, Number)
|
Chris@0
|
569 ; convert_setting_text(float, Atom, Number)
|
Chris@0
|
570 ),
|
Chris@0
|
571 must_be(between(L,U), Number).
|
Chris@0
|
572 convert_setting_text(Type, Atom, Term) :-
|
Chris@0
|
573 term_to_atom(Term, Atom),
|
Chris@0
|
574 must_be(Type, Term).
|
Chris@0
|
575
|
Chris@0
|
576
|