1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    2% System flags handler
    3
    4:- module(flags, [
    5		get_bpl_flag/1,         % ?Flag
    6		remove_bpl_flag/1,      % +Flag
    7		add_bpl_flag/1,         % +Flag
    8		reset_bpl_flags/0,      %
    9		backup_bpl_flags/0,     %
   10		restore_bpl_flags/0,    %
   11		current_bpl_flags/1     % -Flags
   12%		tpl_flags/1
   13   ]).   14
   15%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   16
   17:- set_prolog_flag(double_quotes, codes).   18
   19%:- dynamic tpl_flags/1.
   20
   21%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   22% Predicates for handling system flags
   23%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 get_bpl_flag(?Flag)
Queries current system flags.
   31get_bpl_flag(Flag) :-
   32	bpl_flags(Flag).
 set_bpl_flag(?Flag)
Set a system flag: retract it if it exists already, and assert the new value. Use this predicate if only one clause is expected for the flag. Otherwise, use the pair remove_bpl_flag/1 and add_bpl_flag/1.
   43set_bpl_flag(Flag) :-
   44  Flag =.. [Name|Args],
   45  length(Args,L),
   46  length(OpenArgs,L),
   47  OpenFlag =.. [Name|OpenArgs],
   48	remove_bpl_flag(OpenFlag),
   49	add_bpl_flag(Flag).
   50
   51
   52% add_bpl_flag(+Flag)
   53%
   54%     Adds a new Flag to the current system flags. Does nothing if
   55%     Flag already belongs to the system flags.
   56%
   57
   58add_bpl_flag(Flag) :-
   59	bpl_flags(Flag),
   60	% Flag already exists
   61	!.
   62
   63add_bpl_flag(Flag) :-
   64	% Flag doesn't exist and must be added
   65	assert(bpl_flags(Flag)).
 remove_bpl_flag(+Flag)
Removes a Flag from the current system flags. Does nothing if Flag doesn't belong to the system flags.
   74remove_bpl_flag(Flag) :-
   75	bpl_flags(Flag),
   76	% Flag exists and must be removed
   77	!,
   78	retract(bpl_flags(Flag)).
   79
   80remove_bpl_flag(_Flag).
   81	% Flag doesn't exist
 backup_bpl_flags
Saves a copy of the current system flags that can be later restored with restore_bpl_flags/0.
See also
- restore_bpl_flags/0
   92backup_bpl_flags :-
   93	% Removes previously saved flags
   94	retractall(saved_bpl_flags(_OldSavedFlags)),
   95	% Copies all "bpl_flags(X)" to "saved_bpl_flags(X)"
   96	findall(saved_bpl_flags(Flag), bpl_flags(Flag), FlagsToSave),
   97	maplist(assert, FlagsToSave).
 restore_bpl_flags
Restores the system flags that were previously saved with backup_bpl_flags/0.
See also
- backup_bpl_flags/0
  108restore_bpl_flags :-
  109	% Removes current system flags
  110	retractall(bpl_flags(_OldFlags)),
  111	% Copies all "saved_bpl_flags(X)" to "bpl_flags(X)"
  112	findall(bpl_flags(Flag), saved_bpl_flags(Flag), FlagsToRestore),
  113	maplist(assert, FlagsToRestore).
 current_bpl_flags(-Flags)
Retrieves the current system flags.
  121current_bpl_flags(Flags) :-
  122	findall(Flag, bpl_flags(Flag), Flags).
  123
  124
  125
  126%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  127% Predicates for reseting system flags
  128%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 reset_bpl_flags
Sets the default values for all BPL flags.
  136reset_bpl_flags :-
  137	reset_program_prefix,
  138	reset_lambda_cut,
  139	reset_filtering,
  140	reset_weak_unification,
  141	reset_ext_block_equs,
  142	reset_fuzzy_logic,
  143	reset_continue,
  144	reset_relation_properties([sim, lEqThan, gEqThan, frel1, frel2, frel3]),
  145	reset_fuzzy_subsets.
 reset_program_prefix
Sets a default program name as the prefix of the currently loaded program.
  154reset_program_prefix :-
  155	default_program_prefix(Prefix),
  156	set_bpl_flag(program_prefix(Prefix)).
 reset_lambda_cut(+Lambda)
Sets the default lambda-cut value in BPL flags.
  164reset_lambda_cut :-
  165	default_lambda(Lambda),
  166	set_bpl_flag(lambda_cut(Lambda)).
 reset_filtering(+Boolean)
Sets the default filtering in BPL flags.
  174reset_filtering :-
  175	default_filtering(Boolean),
  176	set_bpl_flag(filtering(Boolean)).
 reset_weak_unification
Sets the default weak unification algorithm in BPL flags.
  184reset_weak_unification :-
  185	default_weak_unification(Algorithm),
  186	set_bpl_flag(weak_unification(Algorithm)).
 reset_ext_block_equs
Sets the default external block equations in BPL flags.
  194reset_ext_block_equs :-
  195	default_ext_block_equs(Boolean),
  196	set_bpl_flag(ext_block_equs(Boolean)).
 reset_fuzzy_logic
Sets the fuzzy logic t-norm flag.
  204reset_fuzzy_logic :-
  205	default_fuzzy_logic(TNorm),
  206	set_bpl_flag(fuzzy_logic(TNorm)).
 reset_continue
Set the main loop to continue.
  214reset_continue :-
  215	default_continue(Boolean),
  216	set_bpl_flag(continue(Boolean)).
 reset_relation_properties(+Relation)
Sets the default closure properties and t-norm in BPL flags for the specified Relation. If Relation is a list, this predicate will be called once for each item.
  226reset_relation_properties([]) :-
  227	!.
  228
  229reset_relation_properties([RelName|OtherRelNames]) :-
  230	% Calls this predicate recursively for each item
  231	reset_relation_properties(RelName),
  232	reset_relation_properties(OtherRelNames).
  233
  234reset_relation_properties(RelName) :-
  235	% Gets default closure properties, converts them into a number
  236	% and stores it in BPL flags along with t-norm identifier
  237	atom(RelName),
  238	default_closure(RelName, ClosureProperties),
  239	remove_bpl_flag(relation_properties(RelName, _ClosureProperties)),
  240	add_bpl_flag(relation_properties(RelName, ClosureProperties)).
 reset_fuzzy_sets
Removes all domains and fuzzy subsets from BPL flags.
  248reset_fuzzy_subsets :-
  249	retractall(bpl_flags(fuzzy_domain(_DomainName1, _Definition))),
  250	retractall(bpl_flags(fuzzy_subsets(_DomainName2, _Subsets))).
  251
  252
  253
  254%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  255% Default values for system flags
  256%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 default_program_prefix(?Prefix)
Unifies Prefix with the default prefix that will be appended to user-defined predicates when no program is loaded.
  265default_program_prefix('none').
 default_lambda(?Value)
Unifies Value with the default lambda-cut value, i.e., the lower bound allowed for the approximation degree of weak unifications. By default, this number is 0, so none of the computations are cut regardless of their approximation degree.
  276default_lambda(0).
 default_filtering(?Value)
Unifies Value with the default filtering value (this value can be either 'true' for enabling filtering, or 'false' for disabling it). By default, this value is 'true'.
  286default_filtering(true).
 default_weak_unification(?Algorithm)
Unifies Algorithm with the default weak unification algoritm. By default, this algorithm is 'a1', and other current possible algorithms are 'a2' and 'a3'.
  296default_weak_unification('a3').
 default_ext_block_equs(?Boolean)
Unifies Boolean with the default external block equations Boolean flag. By default, this value is true, meaning that computing these equations is externally processed.
  306default_ext_block_equs('true').
 default_fuzzy_logic(?TNorm)
Unifies TNorm with the default t-norm for resolution. By default, this value is min, meaning that the used t-norm is goedel.
  316default_fuzzy_logic('min').
 default_continue(?Value)
Unifies Value with the default. By default, this value is 'yes', meaning that the main loop continues. If set to 'no', the main loop stops.
  326default_continue('yes').
 default_closure(?Relation, ?Properties)
Returns a list with the names of the default closure Properties of a certain Relation. By default, a proximity relation is used in weak unifications; partial orders are applied in 'more/less general than' fuzzy relations; and custom fuzzy binary relations are defined as similarity relations.
  338default_closure(SimRelation, [symmetric, reflexive]) :-
  339	member(SimRelation, [sim]).
  340
  341default_closure(GeneralRelation, [reflexive, transitive(TNorm)])  :-
  342	member(GeneralRelation, [gEqThan, lEqThan]),
  343	default_t_norm(GeneralRelation, TNorm).
  344
  345default_closure(CustomRelation, [symmetric, reflexive, transitive(TNorm)])  :-
  346	member(CustomRelation, [frel1, frel2, frel3]),
  347	default_t_norm(CustomRelation, TNorm).
 default_t_norm(?Relation, ?TNorm)
Returns the name of the default TNorm to be used to compute the transitive closure of a certain Relation. 'Minimum' is the default t-norm in all the relations except in the one used in the weak unification process, where no transitivity is applied.
  358default_t_norm(sim, no).
  359default_t_norm('~', min).
  360default_t_norm(gEqThan, min).
  361default_t_norm(lEqThan, min).
  362default_t_norm(frel1, min).
  363default_t_norm(frel2, min).
  364default_t_norm(frel3, min).
  365
  366
  367
  368%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  369% Dynamic predicates
  370%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
Dynamic predicate which stores some flags that affect the behavior of the Bousi-Prolog system. Currently, the following flags are supported:
  398:- dynamic bpl_flags/1.
Dynamic predicate used by backup_bpl_flags/0 and restore_bpl_flags/0 to store a backup copy of the system flags.
  407:- dynamic saved_bpl_flags/1.