% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(option): Option list processing} \label{sec:option} \begin{tags} \mtag{See also}- \file{library(record)} \\- Option processing capabilities may be declared using the directive \predref{predicate_options}{3}. \tag{To be done} We should consider putting many options in an assoc or record with appropriate preprocessing to achieve better performance. \end{tags} The \file{library(option)} provides some utilities for processing option lists. Option lists are commonly used as an alternative for many arguments. Examples of built-in predicates are \predref{open}{4} and \predref{write_term}{3}. Naming the arguments results in more readable code, and the list nature makes it easy to extend the list of options accepted by a predicate. Option lists come in two styles, both of which are handled by this library. \begin{description} \item[Name(Value)] This is the preferred style. \item[Name = Value] This is often used, but deprecated. \end{description} Processing options inside time-critical code (loops) can cause serious overhead. One possibility is to define a record using \file{library(record)} and initialise this using make_$<$record\predref{\Sgt}{2}. In addition to providing good performance, this also provides type-checking and central declaration of defaults. \begin{code} :- record atts(width:integer=100, shape:oneof([box,circle])=box). process(Data, Options) :- make_atts(Options, Attributes), action(Data, Attributes). action(Data, Attributes) :- atts_shape(Attributes, Shape), ... \end{code} Options typically have exactly one argument. The library does support options with 0 or more than one argument with the following restrictions: \begin{itemize} \item The predicate \predref{option}{3} and \predref{select_option}{4}, involving default are meaningless. They perform an \verb$arg(1, Option, Default)$, causing failure without arguments and filling only the first option-argument otherwise. \item \predref{meta_options}{3} can only qualify options with exactly one argument. \end{itemize} \vspace{0.7cm} \begin{description} \predicate[semidet]{option}{3}{?Option, +OptionList, +Default} Get an \arg{Option} from \arg{OptionList}. \arg{OptionList} can use the Name=Value as well as the Name(Value) convention. \begin{arguments} \arg{Option} & Term of the form Name(?Value). \\ \end{arguments} \predicate[semidet]{option}{2}{?Option, +OptionList} Get an \arg{Option} from \arg{OptionList}. \arg{OptionList} can use the Name=Value as well as the Name(Value) convention. Fails silently if the option does not appear in \arg{OptionList}. \begin{arguments} \arg{Option} & Term of the form Name(?Value). \\ \end{arguments} \predicate[semidet]{select_option}{3}{?Option, +Options, -RestOptions} Get and remove \arg{Option} from an option list. As \predref{option}{2}, removing the matching option from \arg{Options} and unifying the remaining options with \arg{RestOptions}. \predicate[det]{select_option}{4}{?Option, +Options, -RestOptions, +Default} Get and remove \arg{Option} with default value. As \predref{select_option}{3}, but if \arg{Option} is not in \arg{Options}, its value is unified with \arg{Default} and \arg{RestOptions} with \arg{Options}. \predicate[det]{merge_options}{3}{+New, +Old, -Merged} Merge two option lists. \arg{Merged} is a sorted list of options using the canonical format Name(Value) holding all options from \arg{New} and \arg{Old}, after removing conflicting options from \arg{Old}. Multi-values options (e.g., \verb$proxy(Host, Port)$) are allowed, where both option-name and arity define the identity of the option. \predicate[det]{meta_options}{3}{+IsMeta, :Options0, -Options} Perform meta-expansion on options that are module-sensitive. Whether an option name is module-sensitive is determined by calling \verb$call(IsMeta, Name)$. Here is an example: \begin{code} meta_options(is_meta, OptionsIn, Options), ... is_meta(callback). \end{code} Meta-options must have exactly one argument. This argument will be qualified. \begin{tags} \tag{To be done} Should be integrated with declarations from \predref{predicate_options}{3}. \end{tags} \predicate[det]{dict_options}{2}{?Dict, ?Options} Convert between an option list and a dictionary. One of the arguments must be instantiated. If the option list is created, it is created in canonical form, i.e., using Option(Value) with the \arg{Options} sorted in the standard order of terms. Note that the conversion is not always possible due to different constraints and conversion may thus lead to (type) errors. \begin{itemize} \item \arg{Dict} keys can be integers. This is not allowed in canonical option lists. \item \arg{Options} can hold multiple options with the same key. This is not allowed in dicts. This predicate removes all but the first option on the same key. \item \arg{Options} can have more than one value (\verb$name(V1,V2)$). This is not allowed in dicts. \end{itemize} Also note that most system predicates and predicates using this library for processing the option argument can both work with classical Prolog options and dicts objects. \end{description}