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-2024, University of Amsterdam 7 VU University Amsterdam 8 CWI, Amsterdam 9 SWI-Prolog Solutions b.v. 10 All rights reserved. 11 12 Redistribution and use in source and binary forms, with or without 13 modification, are permitted provided that the following conditions 14 are met: 15 16 1. Redistributions of source code must retain the above copyright 17 notice, this list of conditions and the following disclaimer. 18 19 2. Redistributions in binary form must reproduce the above copyright 20 notice, this list of conditions and the following disclaimer in 21 the documentation and/or other materials provided with the 22 distribution. 23 24 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 25 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 26 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 27 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 28 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 29 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 30 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 31 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 32 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 33 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 34 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 35 POSSIBILITY OF SUCH DAMAGE. 36*/ 37 38:- module(swi_option, 39 [ option/2, % +Term, +List 40 option/3, % +Term, +List, +Default 41 select_option/3, % +Term, +Options, -RestOpts 42 select_option/4, % +Term, +Options, -RestOpts, +Default 43 merge_options/3, % +New, +Old, -Merged 44 meta_options/3, % :IsMeta, :OptionsIn, -OptionsOut 45 dict_options/2 % ?Dict, ?Options 46 ]). 47:- autoload(library(lists), [selectchk/3]). 48:- autoload(library(error), [must_be/2, domain_error/2]). 49:- autoload(library(pairs), [map_list_to_pairs/3, pairs_values/2]). 50 51:- set_prolog_flag(generate_debug_info, false). 52 53:- meta_predicate 54 meta_options( , , ).
105option(Opt, Options), is_dict(Options) => 106 functor(Opt, Name, 1), 107 get_dict(Name, Options, Val), 108 arg(1, Opt, Val). 109option(Opt, Options), is_list(Options) => 110 functor(Opt, Name, Arity), 111 functor(GenOpt, Name, Arity), 112 get_option(GenOpt, Options), 113 !, 114 Opt = GenOpt. 115 116get_option(Opt, Options) :- 117 memberchk(Opt, Options), 118 !. 119get_option(Opt, Options) :- 120 functor(Opt, OptName, 1), 121 arg(1, Opt, OptVal), 122 memberchk(OptName=OptVal, Options), 123 !.
?- option(max_depth(D), [x(a), max_depth(20)], 10). D = 20. ?- option(max_depth(D), [x(a)], 10). D = 10.
140option(Opt, Options, Default), is_dict(Options) => 141 functor(Opt, Name, 1), 142 ( get_dict(Name, Options, Val) 143 -> true 144 ; Val = Default 145 ), 146 arg(1, Opt, Val). 147option(Opt, Options, Default), is_list(Options) => 148 functor(Opt, Name, Arity), 149 functor(GenOpt, Name, Arity), 150 ( get_option(GenOpt, Options) 151 -> Opt = GenOpt 152 ; arg(1, Opt, Default) 153 ).
164select_option(Opt, Options0, Options), is_dict(Options0) => 165 functor(Opt, Name, 1), 166 get_dict(Name, Options0, Val), 167 arg(1, Opt, Val), 168 del_dict(Name, Options0, Val, Options). 169select_option(Opt, Options0, Options), is_list(Options0) => 170 functor(Opt, Name, Arity), 171 functor(GenOpt, Name, Arity), 172 get_option(GenOpt, Options0, Options), 173 Opt = GenOpt. 174 175get_option(Opt, Options0, Options) :- 176 selectchk(Opt, Options0, Options), 177 !. 178get_option(Opt, Options0, Options) :- 179 functor(Opt, OptName, 1), 180 arg(1, Opt, OptVal), 181 selectchk(OptName=OptVal, Options0, Options).
189select_option(Option, Options, RestOptions, Default), is_dict(Options) => 190 functor(Option, Name, 1), 191 ( del_dict(Name, Options, Val, RestOptions) 192 -> true 193 ; Val = Default, 194 RestOptions = Options 195 ), 196 arg(1, Option, Val). 197select_option(Option, Options, RestOptions, Default), is_list(Options) => 198 functor(Option, Name, Arity), 199 functor(GenOpt, Name, Arity), 200 ( get_option(GenOpt, Options, RestOptions) 201 -> Option = GenOpt 202 ; RestOptions = Options, 203 arg(1, Option, Default) 204 ).
Multi-values options (e.g., proxy(Host, Port)
) are allowed, where
both option-name and arity define the identity of the option.
217merge_options(NewDict, OldDict, Dict), 218 is_dict(NewDict), is_dict(OldDict) => 219 put_dict(NewDict, OldDict, Dict). 220merge_options(New, OldDict, Dict), 221 is_dict(OldDict) => 222 dict_options(NewDict, New), 223 put_dict(NewDict, OldDict, Dict). 224merge_options(NewDict, OldList, List), 225 is_dict(NewDict) => 226 dict_options(NewDict, NewList), 227 merge_option_lists(NewList, OldList, List). 228merge_options(NewList, OldList, List), 229 is_list(NewList), is_list(OldList) => 230 merge_option_lists(NewList, OldList, List). 231 232merge_option_lists([], Old, Merged) :- 233 !, 234 canonicalise_options(Old, Merged). 235merge_option_lists(New, [], Merged) :- 236 !, 237 canonicalise_options(New, Merged). 238merge_option_lists(New, Old, Merged) :- 239 canonicalise_options(New, NCanonical), 240 canonicalise_options(Old, OCanonical), 241 sort(NCanonical, NSorted), 242 sort(OCanonical, OSorted), 243 ord_merge(NSorted, OSorted, Merged). 244 245ord_merge([], L, L) :- !. 246ord_merge(L, [], L) :- !. 247ord_merge([NO|TN], [OO|TO], Merged) :- 248 sort_key(NO, NKey), 249 sort_key(OO, OKey), 250 compare(Diff, NKey, OKey), 251 ord_merge(Diff, NO, NKey, OO, OKey, TN, TO, Merged). 252 253ord_merge(=, NO, _, _, _, TN, TO, [NO|T]) :- 254 ord_merge(TN, TO, T). 255ord_merge(<, NO, _, OO, OKey, TN, TO, [NO|T]) :- 256 ( TN = [H|TN2] 257 -> sort_key(H, NKey), 258 compare(Diff, NKey, OKey), 259 ord_merge(Diff, H, NKey, OO, OKey, TN2, TO, T) 260 ; T = [OO|TO] 261 ). 262ord_merge(>, NO, NKey, OO, _, TN, TO, [OO|T]) :- 263 ( TO = [H|TO2] 264 -> sort_key(H, OKey), 265 compare(Diff, NKey, OKey), 266 ord_merge(Diff, NO, NKey, H, OKey, TN, TO2, T) 267 ; T = [NO|TN] 268 ). 269 270sort_key(Option, Name-Arity) :- 271 functor(Option, Name, Arity).
277canonicalise_options(Dict, Out) :- 278 is_dict(Dict), 279 !, 280 dict_pairs(Dict, _, Pairs), 281 canonicalise_options2(Pairs, Out). 282canonicalise_options(In, Out) :- 283 memberchk(_=_, In), % speedup a bit if already ok. 284 !, 285 canonicalise_options2(In, Out). 286canonicalise_options(Options, Options). 287 288canonicalise_options2([], []). 289canonicalise_options2([H0|T0], [H|T]) :- 290 canonicalise_option(H0, H), 291 canonicalise_options2(T0, T). 292 293canonicalise_option(Name=Value, H) :- 294 !, 295 H =.. [Name,Value]. 296canonicalise_option(Name-Value, H) :- 297 !, 298 H =.. [Name,Value]. 299canonicalise_option(H, H).
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.
321meta_options(IsMeta, Context:Options0, Options), is_dict(Options0) => 322 dict_pairs(Options0, Class, Pairs0), 323 meta_options(Pairs0, IsMeta, Context, Pairs), 324 dict_pairs(Options, Class, Pairs). 325meta_options(IsMeta, Context:Options0, Options), is_list(Options0) => 326 must_be(list, Options0), 327 meta_options(Options0, IsMeta, Context, Options). 328 329meta_options([], _, _, []). 330meta_options([H0|T0], IM, Context, [H|T]) :- 331 meta_option(H0, IM, Context, H), 332 meta_options(T0, IM, Context, T). 333 334meta_option(Name=V0, IM, Context, Name=(M:V)) :- 335 call(IM, Name), 336 !, 337 strip_module(Context:V0, M, V). 338meta_option(Name-V0, IM, Context, Name-(M:V)) :- 339 call(IM, Name), 340 !, 341 strip_module(Context:V0, M, V). 342meta_option(O0, IM, Context, O) :- 343 compound(O0), 344 O0 =.. [Name,V0], 345 call(IM, Name), 346 !, 347 strip_module(Context:V0, M, V), 348 O =.. [Name,M:V]. 349meta_option(O, _, _, O).
name(V1,V2)
). This is
not allowed in dicts.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.
372dict_options(Dict, Options) :- 373 nonvar(Dict), 374 !, 375 dict_pairs(Dict, _, Pairs), 376 canonicalise_options2(Pairs, Options). 377dict_options(Dict, Options) :- 378 canonicalise_options(Options, Options1), 379 map_list_to_pairs(key_name, Options1, Keyed), 380 sort(1, @<, Keyed, UniqueKeyed), 381 pairs_values(UniqueKeyed, Unique), 382 dict_create(Dict, _, Unique). 383 384key_name(Opt, Key) :- 385 functor(Opt, Key, 1), 386 !. 387key_name(Opt, _) :- 388 domain_error(option, Opt)
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.
This is the preferred style.
This is often used, but deprecated.
SWI-Prolog dicts provide a convenient and efficient alternative to option lists. For this reason, both built-in predicates and predicates that use this library support dicts transparantly.
Processing option lists inside time-critical code (loops) can cause serious overhead. The above mentioned dicts is the preferred mitigation. A more portable alternative 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.
Options typically have exactly one argument. The library does support options with 0 or more than one argument with the following restrictions:
arg(1, Option, Default)
, causing failure without arguments and filling only the first option-argument otherwise.