3
4:- module(flags, [
5 get_bpl_flag/1, 6 remove_bpl_flag/1, 7 add_bpl_flag/1, 8 reset_bpl_flags/0, 9 backup_bpl_flags/0, 10 restore_bpl_flags/0, 11 current_bpl_flags/1 13 ]). 14
16
17:- set_prolog_flag(double_quotes, codes). 18
20
31get_bpl_flag(Flag) :-
32 bpl_flags(Flag).
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
57
58add_bpl_flag(Flag) :-
59 bpl_flags(Flag),
60 61 !.
62
63add_bpl_flag(Flag) :-
64 65 assert(bpl_flags(Flag)).
74remove_bpl_flag(Flag) :-
75 bpl_flags(Flag),
76 77 !,
78 retract(bpl_flags(Flag)).
79
80remove_bpl_flag(_Flag).
81
92backup_bpl_flags :-
93 94 retractall(saved_bpl_flags(_OldSavedFlags)),
95 96 findall(saved_bpl_flags(Flag), bpl_flags(Flag), FlagsToSave),
97 maplist(assert, FlagsToSave).
108restore_bpl_flags :-
109 110 retractall(bpl_flags(_OldFlags)),
111 112 findall(bpl_flags(Flag), saved_bpl_flags(Flag), FlagsToRestore),
113 maplist(assert, FlagsToRestore).
121current_bpl_flags(Flags) :-
122 findall(Flag, bpl_flags(Flag), Flags).
123
124
125
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.
154reset_program_prefix :-
155 default_program_prefix(Prefix),
156 set_bpl_flag(program_prefix(Prefix)).
164reset_lambda_cut :-
165 default_lambda(Lambda),
166 set_bpl_flag(lambda_cut(Lambda)).
174reset_filtering :-
175 default_filtering(Boolean),
176 set_bpl_flag(filtering(Boolean)).
184reset_weak_unification :-
185 default_weak_unification(Algorithm),
186 set_bpl_flag(weak_unification(Algorithm)).
194reset_ext_block_equs :-
195 default_ext_block_equs(Boolean),
196 set_bpl_flag(ext_block_equs(Boolean)).
204reset_fuzzy_logic :-
205 default_fuzzy_logic(TNorm),
206 set_bpl_flag(fuzzy_logic(TNorm)).
214reset_continue :-
215 default_continue(Boolean),
216 set_bpl_flag(continue(Boolean)).
226reset_relation_properties([]) :-
227 !.
228
229reset_relation_properties([RelName|OtherRelNames]) :-
230 231 reset_relation_properties(RelName),
232 reset_relation_properties(OtherRelNames).
233
234reset_relation_properties(RelName) :-
235 236 237 atom(RelName),
238 default_closure(RelName, ClosureProperties),
239 remove_bpl_flag(relation_properties(RelName, _ClosureProperties)),
240 add_bpl_flag(relation_properties(RelName, ClosureProperties)).
248reset_fuzzy_subsets :-
249 retractall(bpl_flags(fuzzy_domain(_DomainName1, _Definition))),
250 retractall(bpl_flags(fuzzy_subsets(_DomainName2, _Subsets))).
251
252
253
265default_program_prefix('none').
276default_lambda(0).
286default_filtering(true).
296default_weak_unification('a3').
306default_ext_block_equs('true').
316default_fuzzy_logic('min').
326default_continue('yes').
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).
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
398:- dynamic bpl_flags/1.
407:- dynamic saved_bpl_flags/1.