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-2018, University of Amsterdam 7 VU University Amsterdam 8 CWI, Amsterdam 9 All rights reserved. 10 11 Redistribution and use in source and binary forms, with or without 12 modification, are permitted provided that the following conditions 13 are met: 14 15 1. Redistributions of source code must retain the above copyright 16 notice, this list of conditions and the following disclaimer. 17 18 2. Redistributions in binary form must reproduce the above copyright 19 notice, this list of conditions and the following disclaimer in 20 the documentation and/or other materials provided with the 21 distribution. 22 23 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 24 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 25 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 26 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 27 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 28 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 29 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 30 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 31 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 32 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 33 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 34 POSSIBILITY OF SUCH DAMAGE. 35*/ 36 37:- module(swi_option, 38 [ option/2, % +Term, +List 39 option/3, % +Term, +List, +Default 40 select_option/3, % +Term, +Options, -RestOpts 41 select_option/4, % +Term, +Options, -RestOpts, +Default 42 merge_options/3, % +New, +Old, -Merged 43 meta_options/3, % :IsMeta, :OptionsIn, -OptionsOut 44 dict_options/2 % ?Dict, ?Options 45 ]). 46:- autoload(library(lists), [selectchk/3]). 47:- autoload(library(error), [must_be/2, domain_error/2]). 48:- autoload(library(pairs), [map_list_to_pairs/3, pairs_values/2]). 49 50:- set_prolog_flag(generate_debug_info, false). 51 52:- meta_predicate 53 meta_options( , , ).
112option(Opt, Options, Default) :- 113 is_dict(Options), 114 !, 115 functor(Opt, Name, 1), 116 ( get_dict(Name, Options, Val) 117 -> true 118 ; Val = Default 119 ), 120 arg(1, Opt, Val). 121option(Opt, Options, Default) :- % make option processing stead-fast 122 functor(Opt, Name, Arity), 123 functor(GenOpt, Name, Arity), 124 ( get_option(GenOpt, Options) 125 -> Opt = GenOpt 126 ; arg(1, Opt, Default) 127 ).
138option(Opt, Options) :- % make option processing stead-fast 139 is_dict(Options), 140 !, 141 functor(Opt, Name, 1), 142 get_dict(Name, Options, Val), 143 arg(1, Opt, Val). 144option(Opt, Options) :- % make option processing stead-fast 145 functor(Opt, Name, Arity), 146 functor(GenOpt, Name, Arity), 147 get_option(GenOpt, Options), 148 !, 149 Opt = GenOpt. 150 151get_option(Opt, Options) :- 152 memberchk(Opt, Options), 153 !. 154get_option(Opt, Options) :- 155 functor(Opt, OptName, 1), 156 arg(1, Opt, OptVal), 157 memberchk(OptName=OptVal, Options), 158 !.
167select_option(Opt, Options0, Options) :- 168 is_dict(Options0), 169 !, 170 functor(Opt, Name, 1), 171 get_dict(Name, Options0, Val), 172 arg(1, Opt, Val), 173 del_dict(Name, Options0, Val, Options). 174select_option(Opt, Options0, Options) :- % stead-fast 175 functor(Opt, Name, Arity), 176 functor(GenOpt, Name, Arity), 177 get_option(GenOpt, Options0, Options), 178 Opt = GenOpt. 179 180get_option(Opt, Options0, Options) :- 181 selectchk(Opt, Options0, Options), 182 !. 183get_option(Opt, Options0, Options) :- 184 functor(Opt, OptName, 1), 185 arg(1, Opt, OptVal), 186 selectchk(OptName=OptVal, Options0, Options).
194select_option(Option, Options, RestOptions, Default) :- 195 is_dict(Options), 196 !, 197 functor(Option, Name, 1), 198 ( del_dict(Name, Options, Val, RestOptions) 199 -> true 200 ; Val = Default, 201 RestOptions = Options 202 ), 203 arg(1, Option, Val). 204select_option(Option, Options, RestOptions, Default) :- 205 functor(Option, Name, Arity), 206 functor(GenOpt, Name, Arity), 207 ( get_option(GenOpt, Options, RestOptions) 208 -> Option = GenOpt 209 ; RestOptions = Options, 210 arg(1, Option, Default) 211 ).
Multi-values options (e.g., proxy(Host, Port)
) are allowed,
where both option-name and arity define the identity of the
option.
224merge_options([], Old, Merged) :- 225 !, 226 canonicalise_options(Old, Merged). 227merge_options(New, [], Merged) :- 228 !, 229 canonicalise_options(New, Merged). 230merge_options(New, Old, Merged) :- 231 canonicalise_options(New, NCanonical), 232 canonicalise_options(Old, OCanonical), 233 sort(NCanonical, NSorted), 234 sort(OCanonical, OSorted), 235 ord_merge(NSorted, OSorted, Merged). 236 237ord_merge([], L, L) :- !. 238ord_merge(L, [], L) :- !. 239ord_merge([NO|TN], [OO|TO], Merged) :- 240 sort_key(NO, NKey), 241 sort_key(OO, OKey), 242 compare(Diff, NKey, OKey), 243 ord_merge(Diff, NO, NKey, OO, OKey, TN, TO, Merged). 244 245ord_merge(=, NO, _, _, _, TN, TO, [NO|T]) :- 246 ord_merge(TN, TO, T). 247ord_merge(<, NO, _, OO, OKey, TN, TO, [NO|T]) :- 248 ( TN = [H|TN2] 249 -> sort_key(H, NKey), 250 compare(Diff, NKey, OKey), 251 ord_merge(Diff, H, NKey, OO, OKey, TN2, TO, T) 252 ; T = [OO|TO] 253 ). 254ord_merge(>, NO, NKey, OO, _, TN, TO, [OO|T]) :- 255 ( TO = [H|TO2] 256 -> sort_key(H, OKey), 257 compare(Diff, NKey, OKey), 258 ord_merge(Diff, NO, NKey, H, OKey, TN, TO2, T) 259 ; T = [NO|TN] 260 ). 261 262sort_key(Option, Name-Arity) :- 263 functor(Option, Name, Arity).
269canonicalise_options(Dict, Out) :- 270 is_dict(Dict), 271 !, 272 dict_pairs(Dict, _, Pairs), 273 canonicalise_options2(Pairs, Out). 274canonicalise_options(In, Out) :- 275 memberchk(_=_, In), % speedup a bit if already ok. 276 !, 277 canonicalise_options2(In, Out). 278canonicalise_options(Options, Options). 279 280canonicalise_options2([], []). 281canonicalise_options2([H0|T0], [H|T]) :- 282 canonicalise_option(H0, H), 283 canonicalise_options2(T0, T). 284 285canonicalise_option(Name=Value, H) :- 286 !, 287 H =.. [Name,Value]. 288canonicalise_option(Name-Value, H) :- 289 !, 290 H =.. [Name,Value]. 291canonicalise_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.
313meta_options(IsMeta, Context:Options0, Options) :- 314 is_dict(Options0), 315 !, 316 dict_pairs(Options0, Class, Pairs0), 317 meta_options(Pairs0, IsMeta, Context, Pairs), 318 dict_pairs(Options, Class, Pairs). 319meta_options(IsMeta, Context:Options0, Options) :- 320 must_be(list, Options0), 321 meta_options(Options0, IsMeta, Context, Options). 322 323meta_options([], _, _, []). 324meta_options([H0|T0], IM, Context, [H|T]) :- 325 meta_option(H0, IM, Context, H), 326 meta_options(T0, IM, Context, T). 327 328meta_option(Name=V0, IM, Context, Name=(M:V)) :- 329 call(IM, Name), 330 !, 331 strip_module(Context:V0, M, V). 332meta_option(Name-V0, IM, Context, Name-(M:V)) :- 333 call(IM, Name), 334 !, 335 strip_module(Context:V0, M, V). 336meta_option(O0, IM, Context, O) :- 337 compound(O0), 338 O0 =.. [Name,V0], 339 call(IM, Name), 340 !, 341 strip_module(Context:V0, M, V), 342 O =.. [Name,M:V]. 343meta_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.
366dict_options(Dict, Options) :- 367 nonvar(Dict), 368 !, 369 dict_pairs(Dict, _, Pairs), 370 canonicalise_options2(Pairs, Options). 371dict_options(Dict, Options) :- 372 canonicalise_options(Options, Options1), 373 map_list_to_pairs(key_name, Options1, Keyed), 374 sort(1, @<, Keyed, UniqueKeyed), 375 pairs_values(UniqueKeyed, Unique), 376 dict_create(Dict, _, Unique). 377 378key_name(Opt, Key) :- 379 functor(Opt, Key, 1), 380 !. 381key_name(Opt, _) :- 382 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.
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.
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.