View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2003-2016, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(swi_option,
   37          [ option/2,                   % +Term, +List
   38            option/3,                   % +Term, +List, +Default
   39            select_option/3,            % +Term, +Options, -RestOpts
   40            select_option/4,            % +Term, +Options, -RestOpts, +Default
   41            merge_options/3,            % +New, +Old, -Merged
   42            meta_options/3,             % :IsMeta, :OptionsIn, -OptionsOut
   43            dict_options/2              % ?Dict, ?Options
   44          ]).   45:- use_module(library(lists)).   46:- use_module(library(error)).   47:- set_prolog_flag(generate_debug_info, false).   48
   49:- meta_predicate
   50    meta_options(1, :, -).

Option list processing

The 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 open/4 and 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.

Name(Value)
This is the preferred style.
Name = Value
This is often used, but deprecated.

Processing options inside time-critical code (loops) can cause serious overhead. One possibility is to define a record using library(record) and initialise this using make_<record>/2. In addition to providing good performance, this also provides type-checking and central declaration of defaults.

:- 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),
        ...

Options typically have exactly one argument. The library does support options with 0 or more than one argument with the following restrictions:

See also
- library(record)
-
Option processing capabilities may be declared using the directive predicate_options/3. */
To be done
- We should consider putting many options in an assoc or record with appropriate preprocessing to achieve better performance.
 option(?Option, +OptionList, +Default) is semidet
Get an Option from OptionList. OptionList can use the Name=Value as well as the Name(Value) convention.
Arguments:
Option- Term of the form Name(?Value).
  109option(Opt, Options, Default) :-
  110    is_dict(Options),
  111    !,
  112    functor(Opt, Name, 1),
  113    (   get_dict(Name, Options, Val)
  114    ->  true
  115    ;   Val = Default
  116    ),
  117    arg(1, Opt, Val).
  118option(Opt, Options, Default) :-        % make option processing stead-fast
  119    functor(Opt, Name, Arity),
  120    functor(GenOpt, Name, Arity),
  121    (   get_option(GenOpt, Options)
  122    ->  Opt = GenOpt
  123    ;   arg(1, Opt, Default)
  124    ).
 option(?Option, +OptionList) is semidet
Get an Option from OptionList. OptionList can use the Name=Value as well as the Name(Value) convention. Fails silently if the option does not appear in OptionList.
Arguments:
Option- Term of the form Name(?Value).
  135option(Opt, Options) :-                 % make option processing stead-fast
  136    is_dict(Options),
  137    !,
  138    functor(Opt, Name, 1),
  139    get_dict(Name, Options, Val),
  140    arg(1, Opt, Val).
  141option(Opt, Options) :-                 % make option processing stead-fast
  142    functor(Opt, Name, Arity),
  143    functor(GenOpt, Name, Arity),
  144    get_option(GenOpt, Options),
  145    !,
  146    Opt = GenOpt.
  147
  148get_option(Opt, Options) :-
  149    memberchk(Opt, Options),
  150    !.
  151get_option(Opt, Options) :-
  152    functor(Opt, OptName, 1),
  153    arg(1, Opt, OptVal),
  154    memberchk(OptName=OptVal, Options),
  155    !.
 select_option(?Option, +Options, -RestOptions) is semidet
Get and remove Option from an option list. As option/2, removing the matching option from Options and unifying the remaining options with RestOptions.
  164select_option(Opt, Options0, Options) :-
  165    is_dict(Options0),
  166    !,
  167    functor(Opt, Name, 1),
  168    get_dict(Name, Options0, Val),
  169    arg(1, Opt, Val),
  170    del_dict(Name, Options0, Val, Options).
  171select_option(Opt, Options0, Options) :-        % stead-fast
  172    functor(Opt, Name, Arity),
  173    functor(GenOpt, Name, Arity),
  174    get_option(GenOpt, Options0, Options),
  175    Opt = GenOpt.
  176
  177get_option(Opt, Options0, Options) :-
  178    selectchk(Opt, Options0, Options),
  179    !.
  180get_option(Opt, Options0, Options) :-
  181    functor(Opt, OptName, 1),
  182    arg(1, Opt, OptVal),
  183    selectchk(OptName=OptVal, Options0, Options).
 select_option(?Option, +Options, -RestOptions, +Default) is det
Get and remove Option with default value. As select_option/3, but if Option is not in Options, its value is unified with Default and RestOptions with Options.
  191select_option(Option, Options, RestOptions, Default) :-
  192    is_dict(Options),
  193    !,
  194    functor(Option, Name, 1),
  195    (   get_dict(Name, Options, Val)
  196    ->  true
  197    ;   Val = Default
  198    ),
  199    arg(1, Option, Val),
  200    del_dict(Name, Options, _, RestOptions).
  201select_option(Option, Options, RestOptions, Default) :-
  202    functor(Option, Name, Arity),
  203    functor(GenOpt, Name, Arity),
  204    (   get_option(GenOpt, Options, RestOptions)
  205    ->  Option = GenOpt
  206    ;   RestOptions = Options,
  207        arg(1, Option, Default)
  208    ).
 merge_options(+New, +Old, -Merged) is det
Merge two option lists. Merged is a sorted list of options using the canonical format Name(Value) holding all options from New and Old, after removing conflicting options from Old.

Multi-values options (e.g., proxy(Host, Port)) are allowed, where both option-name and arity define the identity of the option.

  221merge_options([], Old, Merged) :-
  222    !,
  223    canonicalise_options(Old, Merged).
  224merge_options(New, [], Merged) :-
  225    !,
  226    canonicalise_options(New, Merged).
  227merge_options(New, Old, Merged) :-
  228    canonicalise_options(New, NCanonical),
  229    canonicalise_options(Old, OCanonical),
  230    sort(NCanonical, NSorted),
  231    sort(OCanonical, OSorted),
  232    ord_merge(NSorted, OSorted, Merged).
  233
  234ord_merge([], L, L) :- !.
  235ord_merge(L, [], L) :- !.
  236ord_merge([NO|TN], [OO|TO], Merged) :-
  237    sort_key(NO, NKey),
  238    sort_key(OO, OKey),
  239    compare(Diff, NKey, OKey),
  240    ord_merge(Diff, NO, NKey, OO, OKey, TN, TO, Merged).
  241
  242ord_merge(=, NO, _, _, _, TN, TO, [NO|T]) :-
  243    ord_merge(TN, TO, T).
  244ord_merge(<, NO, _, OO, OKey, TN, TO, [NO|T]) :-
  245    (   TN = [H|TN2]
  246    ->  sort_key(H, NKey),
  247        compare(Diff, NKey, OKey),
  248        ord_merge(Diff, H, NKey, OO, OKey, TN2, TO, T)
  249    ;   T = [OO|TO]
  250    ).
  251ord_merge(>, NO, NKey, OO, _, TN, TO, [OO|T]) :-
  252    (   TO = [H|TO2]
  253    ->  sort_key(H, OKey),
  254        compare(Diff, NKey, OKey),
  255        ord_merge(Diff, NO, NKey, H, OKey, TN, TO2, T)
  256    ;   T = [NO|TN]
  257    ).
  258
  259sort_key(Option, Name-Arity) :-
  260    functor(Option, Name, Arity).
 canonicalise_options(+OptionsIn, -OptionsOut) is det
Rewrite option list from possible Name=Value to Name(Value)
  266canonicalise_options(Dict, Out) :-
  267    is_dict(Dict),
  268    !,
  269    dict_pairs(Dict, _, Pairs),
  270    canonicalise_options2(Pairs, Out).
  271canonicalise_options(In, Out) :-
  272    memberchk(_=_, In),            % speedup a bit if already ok.
  273    !,
  274    canonicalise_options2(In, Out).
  275canonicalise_options(Options, Options).
  276
  277canonicalise_options2([], []).
  278canonicalise_options2([H0|T0], [H|T]) :-
  279    canonicalise_option(H0, H),
  280    canonicalise_options2(T0, T).
  281
  282canonicalise_option(Name=Value, H) :-
  283    !,
  284    H =.. [Name,Value].
  285canonicalise_option(Name-Value, H) :-
  286    !,
  287    H =.. [Name,Value].
  288canonicalise_option(H, H).
 meta_options(+IsMeta, :Options0, -Options) is det
Perform meta-expansion on options that are module-sensitive. Whether an option name is module-sensitive is determined by calling call(IsMeta, Name). Here is an example:
        meta_options(is_meta, OptionsIn, Options),
        ...

is_meta(callback).

Meta-options must have exactly one argument. This argument will be qualified.

To be done
- Should be integrated with declarations from predicate_options/3.
  310meta_options(IsMeta, Context:Options0, Options) :-
  311    is_dict(Options0),
  312    !,
  313    dict_pairs(Options0, Class, Pairs0),
  314    meta_options(Pairs0, IsMeta, Context, Pairs),
  315    dict_pairs(Options, Class, Pairs).
  316meta_options(IsMeta, Context:Options0, Options) :-
  317    must_be(list, Options0),
  318    meta_options(Options0, IsMeta, Context, Options).
  319
  320meta_options([], _, _, []).
  321meta_options([H0|T0], IM, Context, [H|T]) :-
  322    meta_option(H0, IM, Context, H),
  323    meta_options(T0, IM, Context, T).
  324
  325meta_option(Name=V0, IM, Context, Name=(M:V)) :-
  326    call(IM, Name),
  327    !,
  328    strip_module(Context:V0, M, V).
  329meta_option(Name-V0, IM, Context, Name-(M:V)) :-
  330    call(IM, Name),
  331    !,
  332    strip_module(Context:V0, M, V).
  333meta_option(O0, IM, Context, O) :-
  334    compound(O0),
  335    O0 =.. [Name,V0],
  336    call(IM, Name),
  337    !,
  338    strip_module(Context:V0, M, V),
  339    O =.. [Name,M:V].
  340meta_option(O, _, _, O).
 dict_options(?Dict, ?Options) is det
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 Options sorted in the standard order of terms. Note that the conversion is not always possible due to different constraints and convertion may thus lead to (type) errors.

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.

  362dict_options(Dict, Options) :-
  363    nonvar(Dict),
  364    !,
  365    dict_pairs(Dict, _, Pairs),
  366    canonicalise_options2(Pairs, Options).
  367dict_options(Dict, Options) :-
  368    dict_create(Dict, _, Options)