1/* File: swi/options.pl 2 Author: Roy Ratcliffe 3 Created: Jul 19 2025 4 Purpose: Sociaal-Wetenschappelijke Informatica Options 5 6Copyright (c) 2025, Roy Ratcliffe, Northumberland, United Kingdom 7 8Permission is hereby granted, free of charge, to any person obtaining a 9copy of this software and associated documentation files (the 10"Software"), to deal in the Software without restriction, including 11without limitation the rights to use, copy, modify, merge, publish, 12distribute, sub-license, and/or sell copies of the Software, and to 13permit persons to whom the Software is furnished to do so, subject to 14the following conditions: 15 16 The above copyright notice and this permission notice shall be 17 included in all copies or substantial portions of the Software. 18 19THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS 20OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF 21MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. 22IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY 23CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, 24TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE 25SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. 26 27*/ 28 29:- module(swi_options, 30 [ select_options/4 % +Options,+RestOptions0,-RestOptions,+Defaults 31 ]). 32:- use_module(library(option), [select_option/4]).
Defaults are unbound if not present. The implementation selects an
option's Default from the given list of Defaults using
select_option/4. Option terms must have one variable. This is
because select_option/4's fourth argument is a single argument. It
never unifies with multiple variables even though it succeeds, e.g.
select_option(a(A, B), [], Rest, 1)
unifies A with 1, leaving B
unbound.
There is a naming issue. What to call the incoming list of Option arguments and the Options argument with which the Option terms unify? One possibility: name the Options argument RestOptions0 since they represent the initial set of RestOptions from which Options select. This clashes with select_option/4's naming convention since Options is the argument name for RestOptions0's role in the option-selection process. Nevertheless, this version follows this renamed argument convention.
The predicate is useful for selecting options from a list of options, especially when the options are not known in advance or when they need to be filtered based on certain criteria.
Example:
?- select_options([a(A), b(B)], [a(1), b(2), c(3)], Rest, [a(0), b(0)]). Rest = [c(3)], A = 1, B = 2.
76select_options(Options, RestOptions0, RestOptions, Defaults) :- 77 select_options(Options, RestOptions0, RestOptions, Defaults, _). 78 79select_options([], RestOptions, RestOptions, Defaults, Defaults). 80select_options([Option|Options], RestOptions0, RestOptions, Defaults0, Defaults) :- 81 % Copy the option to avoid side effects on the original option. This is 82 % necessary to ensure that the original option remains unchanged. 83 copy_term(Option, Option1), 84 term_variables(Option1, [Default]), 85 % Use select_option/4 to select the option from the rest of the options. The 86 % selected option is unified with Option1, and the default value is unified 87 % with Default. The RestOptions1 is the remaining options after selection. 88 select_option(Option1, Defaults0, Defaults1, _), 89 select_option(Option, RestOptions0, RestOptions1, Default), 90 select_options(Options, RestOptions1, RestOptions, Defaults1, Defaults)