SWI-Prolog / swipl-devel

SWI-Prolog Main development repository
http://www.swi-prolog.org
Other
946 stars 171 forks source link

merge_options/3 does not remove duplicates, inconsistency of handling duplicates in options #1004

Open kamahen opened 2 years ago

kamahen commented 2 years ago

merge_options/3 can leave duplicates in the merged list:

?- merge_options([foo(x)], [bar(aaa), foo(y), foo(z), zot(a)], Merged), 
   dict_options(Dict, Merged), 
   select_option(foo(Foo), Merged, Merged2).
Merged = [bar(aaa), foo(x), foo(z), zot(a)],
Dict = _{bar:aaa, foo:x, zot:a},
Foo = x,  % gets the first duplicated option
Merged2 = [bar(aaa), foo(z), zot(a)].

This is a problem if the predicate that uses the merged options uses the last option it finds; it's not a problem if the predicate uses the first option it finds (e.g., using select_option/3).

Unfortunately, get_options() in pl-option.c picks the last option when there are duplicates, so all system predicates have a behavior that's different from select_option/3:

?- numbervars(f(A,B), 1,End, [functor_name(foo), functor_name(bar)]).
A = bar(1),  % gets the last duplicated option
B = bar(2),
End = 3.
JanWielemaker commented 2 years ago

The whole thing needs some rethinking. I was preparing work on scan_options(). Recent discussions made me check the ISO standard, which is explicit in stating that the last option is the one that holds. That would imply we need to change the Prolog library (and accept anyone doing simple-minded memberchk/2 gets it wrong). I'm a little concerned about changing this though. I fear might break more than we would hope :cry:

I do think it is a good idea to expose scan_options(). I'll check the interface and add it to the exports (after renaming of course). This interface is there for many years and seems to hold fine. Al least it supports dicts, optionally checks whether all options are known, does basic type checking and avoids loops.

kamahen commented 2 years ago

Every other options handler that I could easily find (Python, C, bash, library(optparse)) takes the last in case of duplicates. Only library(options) takes the first.

I suggest the following changes to library(option):

I think that select_options/3 takes care of the problem of a predicate processing a few options and then passing the rest to something else, for example read_file_to_codes/3 ... if these use select_option/3, then open/3 can throw an error if it gets something it doesn't like. Alternatively (or in addition):

BTW, merge_options/3 doesn't sort the options if either of its arguments is [] - this should be changed, or the documentation changed.

kamahen commented 2 years ago

One other thing needs to be done with code that uses library(option) ... I've seen code that sets defaults by putting them at the beginning of the options (e.g.: do_something(..., [foo(defaultValue)|Options])). This would need to be changed to use append/3 to put the defaults at the end or -- ideally -- use option/3 or select_option/4 to specify a default value.

kamahen commented 2 years ago

My last comment is backwards -- if the last option is used, then defaults can be put at the beginning, of course.

Of course, option/3 can be used to supply a default; but there are situations where options are passed to another predicate and some default values are desired. One example is archive_open/4, which adds a default close_parent(true) to the options that it passes to archive_open_stream/4.