% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(settings): Setting management} \label{sec:settings} \begin{tags} \tag{author} Jan Wielemaker \tag{See also} \verb$library(config)$ distributed with XPCE provides an alternative aimed at graphical applications. \end{tags} This library allows management of configuration settings for Prolog applications. Applications define settings in one or multiple files using the directive \predref{setting}{4} as illustrated below: \begin{code} :- use_module(library(settings)). :- setting(version, atom, '1.0', 'Current version'). :- setting(timeout, number, 20, 'Timeout in seconds'). \end{code} The directive is subject to \predref{term_expansion}{2}, which guarantees proper synchronisation of the database if source-files are reloaded. This implies it is \textbf{not} possible to call \predref{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.\vspace{0.7cm} \begin{description} \predicate[det]{setting}{4}{:Name, +Type, +Default, +Comment} Define a setting. \arg{Name} denotes the name of the setting, \arg{Type} its type. \arg{Default} is the value before it is modified. \arg{Default} can refer to environment variables and can use arithmetic expressions as defined by \predref{eval_default}{4}. If a second declaration for a setting is encountered, it is ignored if \arg{Type} and \arg{Default} are the same. Otherwise a permission_error is raised. \begin{arguments} \arg{Name} & \arg{Name} of the setting (an atom) \\ \arg{Type} & \arg{Type} for setting. One of \const{any} or a type defined by \predref{must_be}{2}. \\ \arg{Default} & \arg{Default} value for the setting. \\ \arg{Comment} & Atom containing a (short) descriptive note. \\ \end{arguments} \predicate[nondet]{setting}{2}{:Name, ?Value} True when \arg{Name} is a currently defined setting with \arg{Value}. Note that \verb$setting(Name, Value)$ only enumerates the settings of the current module. All settings can be enumerated using \verb$setting(Module:Name, Value)$. This predicate is \const{det} if \arg{Name} is ground. \begin{tags} \tag{Errors} \verb$existence_error(setting, Name)$ \end{tags} \predicate[det]{env}{2}{+Name:atom, -Value:number} \nodescription \predicate[det]{env}{3}{+Name:atom, +Default:number, -Value:number} Evaluate environment variables on behalf of arithmetic expressions. \predicate[det]{set_setting}{2}{:Name, +Value} Change a setting. Performs existence and type-checking for the setting. If the effective value of the setting is changed it broadcasts the event below. \begin{code} settings(changed(Module:Name, Old, New)) \end{code} Note that modified settings are \textbf{not} automatically persistent. The application should call \predref{save_settings}{0} to persist the changes. \begin{tags} \mtag{Errors}- \verb$existence_error(setting, Name)$ \\- \verb$type_error(Type, Value)$ \end{tags} \predicate[det]{restore_setting}{1}{:Name} Restore the value of setting \arg{Name} to its default. Broadcast a change like \predref{set_setting}{2} if the current value is not the default. \predicate[det]{set_setting_default}{2}{:Name, +Default} Change the default for a setting. The effect is the same as \predref{set_setting}{2}, but the new value is considered the default when saving and restoring a setting. It is intended to change application defaults in a particular context. \predicate[det]{load_settings}{1}{File} \nodescription \predicate[det]{load_settings}{2}{File, +Options} Load local settings from \arg{File}. Succeeds if \arg{File} does not exist, setting the default save-file to \arg{File}. \arg{Options} are: \begin{description} \termitem{undefined}{+Action} Define how to handle settings that are not defined. When \const{error}, an error is printed and the setting is ignored. when \const{load}, the setting is loaded anyway, waiting for a definition. \end{description} If possibly changed settings need to be persistent, the application must call \predref{save_settings}{0} as part of its shutdown. In simple cases calling \verb$at_halt(save_settings)$ is sufficient. \predicate[semidet]{save_settings}{0}{} \nodescription \predicate[semidet]{save_settings}{1}{+File} Save modified settings to \arg{File}. Fails silently if the settings file cannot be written. The \predref{save_settings}{0} only attempts to save the settings file if some setting was modified using \predref{set_setting}{2}. \begin{tags} \tag{Errors} \verb$context_error(settings, no_default_file)$ for \predref{save_settings}{0} if no default location is known. \end{tags} \predicate[nondet]{current_setting}{1}{?Setting} True if \arg{Setting} is a currently defined setting \predicate[det]{setting_property}{2}{+Setting, +Property} \nodescription \predicate[nondet]{setting_property}{2}{?Setting, ?Property} Query currently defined settings. \arg{Property} is one of \begin{description} \termitem{comment}{-Atom} \termitem{type}{-Type} \arg{Type} of the setting. \termitem{default}{-Default} \arg{Default} value. If this is an expression, it is evaluated. \termitem{source}{-File:-Line} Location where the setting is defined. \end{description} \predicate[det]{list_settings}{0}{} \nodescription \predicate[det]{list_settings}{1}{+Module} List settings to \verb$current_output$. The second form only lists settings on the matching module. \begin{tags} \tag{To be done} Compute the required column widths \end{tags} \predicate{convert_setting_text}{3}{+Type, +Text, -Value} Converts from textual form to Prolog \arg{Value}. Used to convert values obtained from the environment. Public to provide support in user-interfaces to this library. \begin{tags} \tag{Errors} \verb$type_error(Type, Value)$ \end{tags} \end{description}