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]). 48:- set_prolog_flag(generate_debug_info, false). 49 50:- meta_predicate 51 meta_options( , , ). 52 53/** <module> Option list processing 54 55The library(option) provides some utilities for processing option lists. 56Option lists are commonly used as an alternative for many arguments. 57Examples of built-in predicates are open/4 and write_term/3. Naming the 58arguments results in more readable code, and the list nature makes it 59easy to extend the list of options accepted by a predicate. Option lists 60come in two styles, both of which are handled by this library. 61 62 $ Name(Value) : 63 This is the preferred style. 64 65 $ Name = Value : 66 This is often used, but deprecated. 67 68Processing options inside time-critical code (loops) can cause serious 69overhead. One possibility is to define a record using library(record) 70and initialise this using make_<record>/2. In addition to providing good 71performance, this also provides type-checking and central declaration of 72defaults. 73 74 == 75 :- record atts(width:integer=100, shape:oneof([box,circle])=box). 76 77 process(Data, Options) :- 78 make_atts(Options, Attributes), 79 action(Data, Attributes). 80 81 action(Data, Attributes) :- 82 atts_shape(Attributes, Shape), 83 ... 84 == 85 86Options typically have exactly one argument. The library does support 87options with 0 or more than one argument with the following 88restrictions: 89 90 - The predicate option/3 and select_option/4, involving default are 91 meaningless. They perform an arg(1, Option, Default), causing 92 failure without arguments and filling only the first option-argument 93 otherwise. 94 - meta_options/3 can only qualify options with exactly one argument. 95 96@tbd We should consider putting many options in an assoc or record 97 with appropriate preprocessing to achieve better performance. 98@see library(record) 99@see Option processing capabilities may be declared using the 100 directive predicate_options/3. 101*/ 102 103%! option(?Option, +OptionList, +Default) is semidet. 104% 105% Get an Option from OptionList. OptionList can use the 106% Name=Value as well as the Name(Value) convention. 107% 108% @param Option Term of the form Name(?Value). 109 110option(Opt, Options, Default) :- 111 is_dict(Options), 112 !, 113 functor(Opt, Name, 1), 114 ( get_dict(Name, Options, Val) 115 -> true 116 ; Val = Default 117 ), 118 arg(1, Opt, Val). 119option(Opt, Options, Default) :- % make option processing stead-fast 120 functor(Opt, Name, Arity), 121 functor(GenOpt, Name, Arity), 122 ( get_option(GenOpt, Options) 123 -> Opt = GenOpt 124 ; arg(1, Opt, Default) 125 ). 126 127 128%! option(?Option, +OptionList) is semidet. 129% 130% Get an Option from OptionList. OptionList can use the Name=Value 131% as well as the Name(Value) convention. Fails silently if the 132% option does not appear in OptionList. 133% 134% @param Option Term of the form Name(?Value). 135 136option(Opt, Options) :- % make option processing stead-fast 137 is_dict(Options), 138 !, 139 functor(Opt, Name, 1), 140 get_dict(Name, Options, Val), 141 arg(1, Opt, Val). 142option(Opt, Options) :- % make option processing stead-fast 143 functor(Opt, Name, Arity), 144 functor(GenOpt, Name, Arity), 145 get_option(GenOpt, Options), 146 !, 147 Opt = GenOpt. 148 149get_option(Opt, Options) :- 150 memberchk(Opt, Options), 151 !. 152get_option(Opt, Options) :- 153 functor(Opt, OptName, 1), 154 arg(1, Opt, OptVal), 155 memberchk(OptName=OptVal, Options), 156 !. 157 158 159%! select_option(?Option, +Options, -RestOptions) is semidet. 160% 161% Get and remove Option from an option list. As option/2, removing 162% the matching option from Options and unifying the remaining 163% options with RestOptions. 164 165select_option(Opt, Options0, Options) :- 166 is_dict(Options0), 167 !, 168 functor(Opt, Name, 1), 169 get_dict(Name, Options0, Val), 170 arg(1, Opt, Val), 171 del_dict(Name, Options0, Val, Options). 172select_option(Opt, Options0, Options) :- % stead-fast 173 functor(Opt, Name, Arity), 174 functor(GenOpt, Name, Arity), 175 get_option(GenOpt, Options0, Options), 176 Opt = GenOpt. 177 178get_option(Opt, Options0, Options) :- 179 selectchk(Opt, Options0, Options), 180 !. 181get_option(Opt, Options0, Options) :- 182 functor(Opt, OptName, 1), 183 arg(1, Opt, OptVal), 184 selectchk(OptName=OptVal, Options0, Options). 185 186%! select_option(?Option, +Options, -RestOptions, +Default) is det. 187% 188% Get and remove Option with default value. As select_option/3, 189% but if Option is not in Options, its value is unified with 190% Default and RestOptions with Options. 191 192select_option(Option, Options, RestOptions, Default) :- 193 is_dict(Options), 194 !, 195 functor(Option, Name, 1), 196 ( del_dict(Name, Options, Val, RestOptions) 197 -> true 198 ; Val = Default, 199 RestOptions = Options 200 ), 201 arg(1, Option, Val). 202select_option(Option, Options, RestOptions, Default) :- 203 functor(Option, Name, Arity), 204 functor(GenOpt, Name, Arity), 205 ( get_option(GenOpt, Options, RestOptions) 206 -> Option = GenOpt 207 ; RestOptions = Options, 208 arg(1, Option, Default) 209 ). 210 211 212%! merge_options(+New, +Old, -Merged) is det. 213% 214% Merge two option lists. Merged is a sorted list of options using 215% the canonical format Name(Value) holding all options from New 216% and Old, after removing conflicting options from Old. 217% 218% Multi-values options (e.g., proxy(Host, Port)) are allowed, 219% where both option-name and arity define the identity of the 220% option. 221 222merge_options([], Old, Merged) :- 223 !, 224 canonicalise_options(Old, Merged). 225merge_options(New, [], Merged) :- 226 !, 227 canonicalise_options(New, Merged). 228merge_options(New, Old, Merged) :- 229 canonicalise_options(New, NCanonical), 230 canonicalise_options(Old, OCanonical), 231 sort(NCanonical, NSorted), 232 sort(OCanonical, OSorted), 233 ord_merge(NSorted, OSorted, Merged). 234 235ord_merge([], L, L) :- !. 236ord_merge(L, [], L) :- !. 237ord_merge([NO|TN], [OO|TO], Merged) :- 238 sort_key(NO, NKey), 239 sort_key(OO, OKey), 240 compare(Diff, NKey, OKey), 241 ord_merge(Diff, NO, NKey, OO, OKey, TN, TO, Merged). 242 243ord_merge(=, NO, _, _, _, TN, TO, [NO|T]) :- 244 ord_merge(TN, TO, T). 245ord_merge(<, NO, _, OO, OKey, TN, TO, [NO|T]) :- 246 ( TN = [H|TN2] 247 -> sort_key(H, NKey), 248 compare(Diff, NKey, OKey), 249 ord_merge(Diff, H, NKey, OO, OKey, TN2, TO, T) 250 ; T = [OO|TO] 251 ). 252ord_merge(>, NO, NKey, OO, _, TN, TO, [OO|T]) :- 253 ( TO = [H|TO2] 254 -> sort_key(H, OKey), 255 compare(Diff, NKey, OKey), 256 ord_merge(Diff, NO, NKey, H, OKey, TN, TO2, T) 257 ; T = [NO|TN] 258 ). 259 260sort_key(Option, Name-Arity) :- 261 functor(Option, Name, Arity). 262 263%! canonicalise_options(+OptionsIn, -OptionsOut) is det. 264% 265% Rewrite option list from possible Name=Value to Name(Value) 266 267canonicalise_options(Dict, Out) :- 268 is_dict(Dict), 269 !, 270 dict_pairs(Dict, _, Pairs), 271 canonicalise_options2(Pairs, Out). 272canonicalise_options(In, Out) :- 273 memberchk(_=_, In), % speedup a bit if already ok. 274 !, 275 canonicalise_options2(In, Out). 276canonicalise_options(Options, Options). 277 278canonicalise_options2([], []). 279canonicalise_options2([H0|T0], [H|T]) :- 280 canonicalise_option(H0, H), 281 canonicalise_options2(T0, T). 282 283canonicalise_option(Name=Value, H) :- 284 !, 285 H =.. [Name,Value]. 286canonicalise_option(Name-Value, H) :- 287 !, 288 H =.. [Name,Value]. 289canonicalise_option(H, H). 290 291 292%! meta_options(+IsMeta, :Options0, -Options) is det. 293% 294% Perform meta-expansion on options that are module-sensitive. 295% Whether an option name is module-sensitive is determined by 296% calling call(IsMeta, Name). Here is an example: 297% 298% == 299% meta_options(is_meta, OptionsIn, Options), 300% ... 301% 302% is_meta(callback). 303% == 304% 305% Meta-options must have exactly one argument. This argument will 306% be qualified. 307% 308% @tbd Should be integrated with declarations from 309% predicate_options/3. 310 311meta_options(IsMeta, Context:Options0, Options) :- 312 is_dict(Options0), 313 !, 314 dict_pairs(Options0, Class, Pairs0), 315 meta_options(Pairs0, IsMeta, Context, Pairs), 316 dict_pairs(Options, Class, Pairs). 317meta_options(IsMeta, Context:Options0, Options) :- 318 must_be(list, Options0), 319 meta_options(Options0, IsMeta, Context, Options). 320 321meta_options([], _, _, []). 322meta_options([H0|T0], IM, Context, [H|T]) :- 323 meta_option(H0, IM, Context, H), 324 meta_options(T0, IM, Context, T). 325 326meta_option(Name=V0, IM, Context, Name=(M:V)) :- 327 call(IM, Name), 328 !, 329 strip_module(Context:V0, M, V). 330meta_option(Name-V0, IM, Context, Name-(M:V)) :- 331 call(IM, Name), 332 !, 333 strip_module(Context:V0, M, V). 334meta_option(O0, IM, Context, O) :- 335 compound(O0), 336 O0 =.. [Name,V0], 337 call(IM, Name), 338 !, 339 strip_module(Context:V0, M, V), 340 O =.. [Name,M:V]. 341meta_option(O, _, _, O). 342 343%! dict_options(?Dict, ?Options) is det. 344% 345% Convert between an option list and a dictionary. One of the 346% arguments must be instantiated. If the option list is created, 347% it is created in canonical form, i.e., using Option(Value) with 348% the Options sorted in the standard order of terms. Note that the 349% conversion is not always possible due to different constraints 350% and conversion may thus lead to (type) errors. 351% 352% - Dict keys can be integers. This is not allowed in canonical 353% option lists. 354% - Options can hold multiple options with the same key. This is 355% not allowed in dicts. 356% - Options can have more than one value (name(V1,V2)). This is 357% not allowed in dicts. 358% 359% Also note that most system predicates and predicates using this 360% library for processing the option argument can both work with 361% classical Prolog options and dicts objects. 362 363dict_options(Dict, Options) :- 364 nonvar(Dict), 365 !, 366 dict_pairs(Dict, _, Pairs), 367 canonicalise_options2(Pairs, Options). 368dict_options(Dict, Options) :- 369 dict_create(Dict, _, Options)