diff --git a/boot/messages.pl b/boot/messages.pl index 134a470469..acd26c32c2 100644 --- a/boot/messages.pl +++ b/boot/messages.pl @@ -786,6 +786,8 @@ ]. prolog_message(untable(PI)) --> [ 'Reconsult: removed tabling for ~p'-[PI] ]. +prolog_message(unknown_option(Set, Opt)) --> + [ 'Unknown ~w option: ~p'-[Set, Opt] ]. /******************************* diff --git a/man/overview.doc b/man/overview.doc index 5e308e28b8..761649e547 100644 --- a/man/overview.doc +++ b/man/overview.doc @@ -2442,6 +2442,19 @@ application modules or for a specific module. It is strongly advised to keep the \const{error} default and use dynamic/1 and/or multifile/1 to specify possible non-existence of a predicate. + \prologflagitem{unknown_option}{ignore,warning,error}{rw} +Determines the behaviour if a predicate that processes an option list +is passed an option that is not understood by the predicate. The ISO +standard dictates raising a \const{domain_error} exception. This is +considered impractical as it makes it hard to write portable code if +different Prolog systems support different options and it makes it +hard to write predicates that process options and pass some of the +options to one predicate and others to some other predicate. For +example, a predicate reading a file to a list of terms must distribute +options to open/4 and read_term/3. SWI-Prolog has always ignored +unknown options unless in ISO mode (see the \prologflag{iso} flag). +This flag provides full control over how options are processed. + \prologflagitem{unload_foreign_libraries}{bool}{rw} If \const{true} (default \const{false}), unload all loaded foreign libraries. Default is \const{false} because modern OSes reclaim the diff --git a/src/ATOMS b/src/ATOMS index 89884f1a09..bec5b8f92e 100644 --- a/src/ATOMS +++ b/src/ATOMS @@ -935,6 +935,7 @@ A uninstantiation_error "uninstantiation_error" A unique "unique" A univ "=.." A unknown "unknown" +A unknown_option "unknown_option" A unlimited "unlimited" A unload "unload" A unlock "unlock" @@ -1308,6 +1309,7 @@ F type_error 2 F undefinterc 4 F unify_determined 2 F uninstantiation_error 1 +F unknown_option 2 F unwind 1 F var 1 F waiting 1 diff --git a/src/SWI-Prolog.h b/src/SWI-Prolog.h index 1cdbddee41..1daa688a59 100644 --- a/src/SWI-Prolog.h +++ b/src/SWI-Prolog.h @@ -1178,7 +1178,12 @@ typedef enum #define OPT_TYPE_MASK 0xff #define OPT_INF 0x100 /* allow 'inf' */ -#define OPT_ALL 0x1 /* flags */ +#define OPT_UNKNOWN_DEFAULT 0x0 /* Default (from flag) */ +#define OPT_UNKNOWN_ERROR 0x1 /* Unknown Prolog flags raise error */ +#define OPT_UNKNOWN_IGNORE 0x2 /* Unknown Prolog flags are ignored */ +#define OPT_UNKNOWN_WARNING 0x3 /* Unknown Prolog flags warn */ +#define OPT_UNKNOWN_MASK 0x3 +#define OPT_ALL OPT_UNKNOWN_ERROR /* Compatibility; deprecated */ typedef struct { atom_t name; /* Name of option */ diff --git a/src/Tests/core/test_scan_options.pl b/src/Tests/core/test_scan_options.pl index 9009486f99..6dad9fb6e2 100644 --- a/src/Tests/core/test_scan_options.pl +++ b/src/Tests/core/test_scan_options.pl @@ -61,8 +61,6 @@ numbervars(x(_,X,X), 0, End, [unlikely(true)]). test(bad_value_type, error(type_error(bool, 42))) :- numbervars(x(_,X,X), 0, _, [singletons(42)]). -test(bad_type, error(type_error(option, unlikely))) :- - numbervars(x(_,X,X), 0, _, [unlikely]). test(bad_type, error(type_error(option, f(a,b)))) :- numbervars(x(_,X,X), 0, _, [f(a,b)]). test(bad_type, error(type_error(option, 1.3))) :- diff --git a/src/os/pl-option.c b/src/os/pl-option.c index d7ea14f35d..da05a61f1f 100644 --- a/src/os/pl-option.c +++ b/src/os/pl-option.c @@ -3,7 +3,7 @@ Author: Jan Wielemaker E-mail: J.Wielemaker@vu.nl WWW: http://www.swi-prolog.org - Copyright (c) 2011-2022, University of Amsterdam + Copyright (c) 2011-2024, University of Amsterdam VU University Amsterdam SWI-Prolog Solutions b.v. All rights reserved. @@ -43,6 +43,7 @@ Option list (or dict) processing. See PL_scan_options() for details. - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */ #define MAXOPTIONS 64 +#define HAS_OPT_MODE(f,m) (((f)&OPT_UNKNOWN_MASK) == (m)) typedef union { int *b; /* boolean value */ @@ -157,7 +158,8 @@ typedef struct dictopt_ctx int flags; } dictopt_ctx; -#define dict_option(key, value, last, closure) LDFUNC(dict_option, key, value, last, closure) +#define dict_option(key, value, last, closure) \ + LDFUNC(dict_option, key, value, last, closure) static int dict_option(DECL_LD term_t key, term_t value, int last, void *closure) @@ -177,14 +179,23 @@ dict_option(DECL_LD term_t key, term_t value, int last, void *closure) } } - if ( (ctx->flags&OPT_ALL) ) + if ( !HAS_OPT_MODE(ctx->flags, OPT_UNKNOWN_IGNORE) ) { term_t kv; - int rc = ( (kv=PL_new_term_ref()) && - PL_cons_functor(kv, FUNCTOR_colon2, key, value) && - PL_domain_error(ctx->opttype, kv) - ); - (void)rc; - return -1; + + if ( !((kv=PL_new_term_ref()) && + PL_cons_functor(kv, FUNCTOR_colon2, key, value)) ) + return -1; + + if ( HAS_OPT_MODE(ctx->flags, OPT_UNKNOWN_ERROR) ) + { if ( !PL_domain_error(ctx->opttype, kv) ) + return -1; + return -1; + } + if ( !printMessage(ATOM_warning, + PL_FUNCTOR, FUNCTOR_unknown_option2, + PL_CHARS, ctx->opttype, + PL_TERM, kv) ) + return -1; } return 0; /* unprocessed key */ @@ -217,7 +228,7 @@ dict_options(DECL_LD term_t dict, int flags, const char *opttype, ctx.flags = flags; ctx.opttype = opttype; - return _PL_for_dict(dict, dict_option, &ctx, 0) == 0 ? true : false; + return _PL_for_dict(dict, dict_option, &ctx, 0) == 0; } #define vscan_options(list, flags, name, specs, args) \ @@ -235,8 +246,8 @@ vscan_options(DECL_LD term_t options, int flags, const char *opttype, int count = 0; (void)opttype; - if ( truePrologFlag(PLFLAG_ISO) ) - flags |= OPT_ALL; + if ( flags == OPT_UNKNOWN_DEFAULT ) + flags = LD->prolog_flag.unknown_option; for( n=0, s = specs; s->name; s++, n++ ) { if ( n >= MAXOPTIONS ) @@ -272,13 +283,11 @@ vscan_options(DECL_LD term_t options, int flags, const char *opttype, _PL_get_arg(2, head, val); } else if ( arity == 1 ) { _PL_get_arg(1, head, val); - } else if ( arity == 0 ) + } else if ( arity == 0 && !truePrologFlag(PLFLAG_ISO) ) { implicit_true = true; } else { goto itemerror; } - } else if ( PL_is_variable(head) ) - { return PL_error(NULL, 0, NULL, ERR_INSTANTIATION); } else { itemerror: return PL_error(NULL, 0, NULL, ERR_TYPE, ATOM_option, head); @@ -301,10 +310,14 @@ vscan_options(DECL_LD term_t options, int flags, const char *opttype, } } - if ( !s->name && (implicit_true || (flags & OPT_ALL)) ) - { if ( implicit_true ) - goto itemerror; - return PL_domain_error(opttype, head); + if ( !s->name && !HAS_OPT_MODE(flags, OPT_UNKNOWN_IGNORE) ) + { if ( HAS_OPT_MODE(flags, OPT_UNKNOWN_ERROR) ) + return PL_domain_error(opttype, head); + if ( !printMessage(ATOM_warning, + PL_FUNCTOR, FUNCTOR_unknown_option2, + PL_CHARS, opttype, + PL_TERM, head) ) + return false; } } diff --git a/src/os/pl-prologflag.c b/src/os/pl-prologflag.c index d24bdf1e5a..ee09038c29 100644 --- a/src/os/pl-prologflag.c +++ b/src/os/pl-prologflag.c @@ -487,7 +487,7 @@ setRationalSyntax(atom_t a, unsigned int *flagp) -static int +static bool setUnknown(term_t value, atom_t a, Module m) { unsigned int flags = m->flags & ~(UNKNOWN_MASK); @@ -523,6 +523,22 @@ setUnknown(term_t value, atom_t a, Module m) } +static bool +setUnknownOption(term_t value, atom_t a) +{ GET_LD + + if ( a == ATOM_ignore ) + { LD->prolog_flag.unknown_option = OPT_UNKNOWN_IGNORE; + } else if ( a == ATOM_warning ) + { LD->prolog_flag.unknown_option = OPT_UNKNOWN_WARNING; + } else if ( a == ATOM_error ) + { LD->prolog_flag.unknown_option = OPT_UNKNOWN_ERROR; + } else + return PL_domain_error("unknown_option", value); + + return true; +} + static int checkOnError(term_t value, atom_t a, atom_t key) { if ( a == ATOM_print || a == ATOM_halt || a == ATOM_status ) @@ -1123,6 +1139,8 @@ set_prolog_flag_unlocked(DECL_LD Module m, atom_t k, term_t value, unsigned shor { rval = setRationalSyntax(a, &m->flags); } else if ( k == ATOM_unknown ) { rval = setUnknown(value, a, m); + } else if ( k == ATOM_unknown_option ) + { rval = setUnknownOption(value, a); } else if ( k == ATOM_on_error || k == ATOM_on_warning ) { rval = checkOnError(value, a, k); } else if ( k == ATOM_write_attributes ) @@ -1980,6 +1998,8 @@ initPrologFlags(void) setPrologFlag("portable_vmi", FT_BOOL, true, PLFLAG_PORTABLE_VMI); setPrologFlag("traditional", FT_BOOL|FF_READONLY, GD->options.traditional, 0); setPrologFlag("unknown", FT_ATOM, "error"); + setPrologFlag("unknown_option", FT_ATOM, "ignore"); + LD->prolog_flag.unknown_option = OPT_UNKNOWN_IGNORE; setPrologFlag("debug", FT_BOOL, false, 0); setPrologFlag("debug_on_interrupt", FT_BOOL, truePrologFlag(PLFLAG_DEBUG_ON_INTERRUPT), diff --git a/src/pl-global.h b/src/pl-global.h index 48c1c51996..51ad58efbf 100644 --- a/src/pl-global.h +++ b/src/pl-global.h @@ -709,6 +709,7 @@ struct PL_local_data int write_attributes; /* how to write attvars? */ occurs_check_t occurs_check; /* Unify and occurs check */ access_level_t access_level; /* Current access level */ + unsigned int unknown_option; /* OPT_UNKNOWN_* */ } prolog_flag; struct diff --git a/src/pl-thread.c b/src/pl-thread.c index 76225d2191..663fc20211 100644 --- a/src/pl-thread.c +++ b/src/pl-thread.c @@ -2199,6 +2199,7 @@ copy_local_data(PL_local_data_t *ldnew, PL_local_data_t *ldold, ldnew->prolog_flag.mask = ldold->prolog_flag.mask; ldnew->prolog_flag.occurs_check = ldold->prolog_flag.occurs_check; ldnew->prolog_flag.access_level = ldold->prolog_flag.access_level; + ldnew->prolog_flag.unknown_option = ldold->prolog_flag.unknown_option; #ifdef O_BIGNUM ldnew->arith.rat = ldold->arith.rat; #endif