
 predicate_options.pl -- Access and analyse predicate options
predicate_options.pl -- Access and analyse predicate options
This module provides the developers interface for the directive
predicate_options/3. This directive allows us to specify that, e.g.,
open/4 processes options using the 4th argument and supports the option
type using the values text and binary. Declaring options that are
processed allows for more reliable handling of predicate options and
simplifies porting applications. This library provides the following
functionality:
Below, we describe some use-cases.
1 ?- [load]. 2 ?- autoload. 3 ?- derive_predicate_options. 4 ?- check_predicate_options.
1 ?- [load]. 2 ?- autoload. 3 ?- derive_predicate_options. 4 ?- derived_predicate_options(module_1). 5 ?- derived_predicate_options(module_2). 6 ?- ...
lock(write),
it may do so using the directive below. This directive raises an
exception when loaded on a Prolog implementation that does not support
this option.
:- current_predicate_option(open/4, 4, lock(write)).
 predicate_options(:PI, +Arg, +Options) is det
 predicate_options(:PI, +Arg, +Options) is det
Below is an example that processes the option header(boolean)
and passes all options to open/4:
:- predicate_options(write_xml_file/3, 3,
                     [ header(boolean),
                       pass_to(open/4, 4)
                     ]).
write_xml_file(File, XMLTerm, Options) :-
    open(File, write, Out, Options),
    (   option(header(true), Options, true)
    ->  write_xml_header(Out)
    ;   true
    ),
    ...
This predicate may only be used as a directive and is processed by expand_term/2. Option processing can be specified at runtime using assert_predicate_options/3, which is intended to support program analysis.
 assert_predicate_options(:PI, +Arg, +Options, ?New) is semidet
 assert_predicate_options(:PI, +Arg, +Options, ?New) is semidetfalse, the predicate becomes semidet and fails
without modifications if modifications are required. current_option_arg(:PI, ?Arg) is nondet
 current_option_arg(:PI, ?Arg) is nondet current_predicate_option(:PI, ?Arg, ?Option) is nondet
 current_predicate_option(:PI, ?Arg, ?Option) is nondet?- current_predicate_option(open/4, 4, type(text)). true.
This predicate is intended to support conditional compilation using if/1 ... endif/0. The predicate current_predicate_options/3 can be used to access the full capabilities of a predicate.
 check_predicate_option(:PI, +Arg, +Option) is det
 check_predicate_option(:PI, +Arg, +Option) is det current_predicate_options(:PI, ?Arg, ?Options) is nondet
 current_predicate_options(:PI, ?Arg, ?Options) is nondet derived_predicate_options(:PI, ?Arg, ?Options) is nondet
 derived_predicate_options(:PI, ?Arg, ?Options) is nondet derived_predicate_options(+Module) is det
 derived_predicate_options(+Module) is detcurrent_output stream. retractall_predicate_options is det
 retractall_predicate_options is det check_predicate_options is det
 check_predicate_options is det derive_predicate_options is det
 derive_predicate_options is det check_predicate_options(:PredicateIndicator) is det
 check_predicate_options(:PredicateIndicator) is det