| Did you know ... | Search Documentation: |
| settings.pl -- Setting management |
This library allows management of configuration settings for Prolog applications. Applications define settings in one or multiple files using the directive setting/4 as illustrated below:
:- use_module(library(settings)). :- setting(version, atom, '1.0', 'Current version'). :- setting(timeout, number, 20, 'Timeout in seconds').
The directive is subject to term_expansion/2, which guarantees proper synchronisation of the database if source-files are reloaded. This implies it is not possible to call setting/4 as a predicate.
Settings are local to a module. This implies they are defined in a two-level namespace. Managing settings per module greatly simplifies assembling large applications from multiple modules that configuration through settings. This settings management library ensures proper access, loading and saving of settings.
setting(:Name, +Type, +Default, +Comment) is detIf a second declaration for a setting is encountered, it is ignored if Type and Default are the same. Otherwise a permission_error is raised.
setting(:Name, ?Value) is nondetsetting(Name, Value) only enumerates the settings of the
current module. All settings can be enumerated using
setting(Module:Name, Value). This predicate is det if Name is
ground.
env(+Name:atom, -Value:number) is det
env(+Name:atom, +Default:number, -Value:number) is det
set_setting(:Name, +Value) is detsettings(changed(Module:Name, Old, New))
Note that modified settings are not automatically persistent. The application should call save_settings/0 to persist the changes.
restore_setting(:Name) is det
set_setting_default(:Name, +Default) is det
load_settings(File) is det
load_settings(File, +Options) is deterror, an error is printed and the setting is ignored.
when load, the setting is loaded anyway, waiting for a
definition.
If possibly changed settings need to be persistent, the application
must call save_settings/0 as part of its shutdown. In simple cases
calling at_halt(save_settings) is sufficient.
save_settings is semidet
save_settings(+File) is semidet
current_setting(?Setting) is nondet
setting_property(+Setting, +Property) is det
list_settings is det
list_settings(+Module) is detcurrent_output. The second form only lists
settings on the matching module.
convert_setting_text(+Type, +Text, -Value)