1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 2% Utility predicates used by other modules 3 4:- module(utilities, [ 5 % Predicates for processing and scanning terms 6 process_term/6, % +Term, -Result, +Scanners, +Testers, 7 % +InData, -OutData 8 % Predicates for retrieving predicate names 9 get_predicates/1, % -PredicateList 10 get_predicates_modules/2,% +ModuleList, -PredicateList 11 % Predicates for simplifying a filename or an atom 12 simplify_filename/2, % +Path, -SimplifiedFilename 13 simplify_atom/2, % +Atom, -SimplifiedAtom) 14 % Miscellaneous list-related predicates 15 write_lines/3, % +List, +Prefix, +Sufix 16 extract_terms/4, % +Prefix, +Arity, +List, -Items 17 ascending_numbers/1, % +List 18 remove_prefixes/3, % +List, -Result, +Prefix 19 remove_program_prefix/2,% +Atom, -Result 20 % Miscellaneous string-related predicates 21 remove_quotes/2, % +Strings, ?FixedStrings 22 is_quoted/2, % +String, ?QuoteChar 23 % Miscellaneous predicates for interacting with files and the OS 24 home_directory/1, % ?HomeDir 25 file_is_newer/2, % +File1, +File2 26 % Other miscellaneous predicates 27 builtin/1, % +Predicate 28 atom_is_variable/1, % +Atom 29 % Bousi-Prolog specific predicates 30 closure_properties/3, % +Properties, ?Closure, ?TNorm 31 relation_name/2, % ?Symbol, ?Name 32 relation_evaluator/2 % ?Relation, ?Evaluator 33% atoms_in_term/2 % +Term, -Atoms 34 ]). 35 36:- use_module(library(lists)). 37:- use_module(library(readutil)). 38:- use_module(library(shell)). 39% Add all modules used by wn module. 40:- use_module(library(ordsets)). 41:- use_module(library(lists)). 42 43%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 44 45:- set_prolog_flag(double_quotes, codes). 46 47checkwnenv(WNDB) :- 48 ( getenv('WNDB', WNDB) 49 -> true 50 ; (current_prolog_flag(windows, true) 51 % Default directories: 52 -> WNDB = 'C:\\WordNet3.0' 53 ; WNDB = '/usr/local/WordNet-3.0'), 54 setenv('WNDB', WNDB) 55 ). 56 57%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 58% Predicates for processing and scanning terms 59%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
The behavior of the process_term/6 predicate is defined by means of the following algorithm:
104process_term(Term, Result, Scanners, Testers, InData, OutData) :- 105 process_term_aux([Term], [Result], Scanners, Testers, InData, OutData). 106 107process_term_aux([], [], _Scanners, _Testers, OutData, OutData). 108 109process_term_aux([Term|MoreTerms], [Result|MoreResults], Scanners, Testers, InData, OutData) :- 110 execute_scanners(Term, FirstResult, Scanners, InData, FirstOutData), 111 ((compound(FirstResult), execute_testers(FirstResult, Testers)) -> 112 FirstResult =.. [Functor|Args], 113 process_term_aux(Args, ResultArgs, Scanners, Testers, FirstOutData, LastOutData), 114 Result =.. [Functor|ResultArgs] 115 ; 116 Result = FirstResult, 117 LastOutData = FirstOutData 118 ), 119 process_term_aux(MoreTerms, MoreResults, Scanners, Testers, LastOutData, OutData).
127execute_testers(_Term, []). 128 129execute_testers(Term, [Tester|MoreTesters]) :- 130 apply(Tester, [Term]), 131 execute_testers(Term, MoreTesters).
143execute_scanners(Term, Term, [], OutData, OutData). 144 145execute_scanners(Term, Result, [Scanner|MoreScanners], InData, OutData) :- 146 apply(Scanner, [Term, NextTerm, InData, NextInData]), 147 execute_scanners(NextTerm, Result, MoreScanners, NextInData, OutData). 148 149 150 151%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 152% Predicates for retrieving predicate names 153%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
162get_predicates(Predicates) :-
163 % Gets the list of SWI-Prolog modules
164 setof(Mod, current_module(Mod), Modules),
165 subtract(Modules, [bousi, bplHelp, bplShell, directivesBpl, evaluator,
166 flags, foreign, parser, translator, utilities],
167 PrologModules),
168 % Retrieves the full list of predicate names
169 get_predicates_modules(PrologModules, UnsortedPredicates),
170 % Sorts predicate names and removes duplicates
171 sort(UnsortedPredicates, Predicates).
181get_predicates_modules([], []). 182 183get_predicates_modules([Module|MoreModules], Predicates) :- 184 setof(Pred, Arity ^ current_predicate(Module:Pred/Arity), ModulePreds), !, 185 get_predicates_modules(MoreModules, MorePredicates), 186 append(ModulePreds, MorePredicates, Predicates). 187 188get_predicates_modules([_Module|MoreModules], MorePredicates) :- 189 % This rule is executed only if the predicates of Module can't 190 % be retrieved; in that case the module is ignored 191 get_predicates_modules(MoreModules, MorePredicates). 192 193 194 195%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 196% Predicates for simplifying a filename or an atom 197%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
208simplify_filename(Path, SimplifiedFilename) :-
209 file_base_name(Path, BaseFileWithExt),
210 file_name_extension(BaseFile, _Extension, BaseFileWithExt),
211 simplify_atom(BaseFile, SimplifiedFilename).
221simplify_atom(Atom, SimplifiedAtom) :-
222 atom_chars(Atom, OriginalChars),
223 simplify_chars(OriginalChars, SimplifiedChars),
224 atom_chars(SimplifiedAtom, SimplifiedChars).
244simplify_chars(OriginalChars, SimplifiedChars) :- 245 simplify_chars_aux(OriginalChars, SimplifiedChars, yes). 246 247simplify_chars_aux([], [], _First). 248 249simplify_chars_aux([Char|MoreChars], [Char|MoreSimplifiedChars], _First) :- 250 % Lowercase letters are always copied to the destination list 251 char_type(Char, lower), !, 252 simplify_chars_aux(MoreChars, MoreSimplifiedChars, no). 253 254simplify_chars_aux([UpperChar|MoreChars], [LowerChar|MoreSimplifiedChars], yes) :- 255 % Uppercase letters are replaced with their lowercase 256 % counterparts if they're the first character of an atom 257 char_type(UpperChar, upper(LowerChar)), !, 258 simplify_chars_aux(MoreChars, MoreSimplifiedChars, no). 259 260simplify_chars_aux([_Char|MoreChars], ['a'|MoreSimplifiedChars], yes) :- 261 % Any character that isn't a letter is replaced with a lowercase letter 262 % (in this case, 'a') when they're the first character of an atom 263 simplify_chars_aux(MoreChars, MoreSimplifiedChars, no). 264 265simplify_chars_aux([Char|MoreChars], [Char|MoreSimplifiedChars], no) :- 266 % Uppercase letters and digits are allowed only if 267 % they're not the first character of an atom 268 (char_type(Char, upper) ; char_type(Char, digit)), !, 269 simplify_chars_aux(MoreChars, MoreSimplifiedChars, no). 270 271simplify_chars_aux([_Char|MoreChars], ['_'|MoreSimplifiedChars], no) :- 272 % Any non-alphanumeric character is replaced with an underscore 273 simplify_chars_aux(MoreChars, MoreSimplifiedChars, no). 274 275 276 277%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 278% Miscellaneous list-related predicates 279%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
287write_lines([], _Prefix, _Sufix). 288 289write_lines([Item], Prefix, Sufix) :- 290 write(Prefix), write(Item), write(Sufix). 291 292write_lines([Item|List], Prefix, Sufix) :- 293 List \== [], 294 write_lines([Item], Prefix, Sufix), nl, 295 write_lines(List, Prefix, Sufix).
For example, given Prefix = 'sim' and Arity = 3, this predicate
will only return "sim(_, _, _)
" terms.
309extract_terms(Prefix, Arity, List, Items) :-
310 atom(Prefix), integer(Arity),
311 functor(Template, Prefix, Arity),
312 findall(Template, member(Template, List), Items).
332ascending_numbers([]). 333 334ascending_numbers([First|Values]) :- 335 ascending_numbers(Values, First). 336 337ascending_numbers([], _Highest). 338 339ascending_numbers([Value|MoreValues], Highest) :- 340 integer(Value), 341 Value >= Highest, 342 ascending_numbers(MoreValues, Value).
For example, given List = ['atom1', 'other', 'atom_ex'] and Prefix = 'atom', this predicate will return Result = ['1', '_ex'].
356remove_prefixes([], [], _Prefix). 357 358remove_prefixes([Atom|MoreAtoms], [AtomNoPrefix|MoreAtomsNoPrefix], Prefix) :- 359 sub_atom(Atom, 0, Len, _, Prefix), !, 360 % Atom begins with Prefix 361 sub_atom(Atom, Len, _, 0, AtomNoPrefix), 362 remove_prefixes(MoreAtoms, MoreAtomsNoPrefix, Prefix). 363 364remove_prefixes([_Atom|MoreAtoms], MoreAtomsNoPrefix, Prefix) :- 365 % Atom doesn't begin with Prefix 366 remove_prefixes(MoreAtoms, MoreAtomsNoPrefix, Prefix).
375remove_program_prefix(Atom, Result) :- 376 parser:program_prefix(Prefix), 377 atom_concat(Prefix, '_', PrefixUS), 378 atom_concat(PrefixUS, Result, Atom), 379 !. 380 381remove_program_prefix(Atom, Atom). 382 383 384%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 385% Miscellaneous string-related predicates 386%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
397remove_quotes(String, FixedString) :- 398 atom(String), 399 is_quoted(String, '\''), 400 sub_atom(String, 1, _, 1, FixedString), !. 401 402remove_quotes(String, FixedString) :- 403 atom(String), 404 is_quoted(String, '\"'), 405 sub_atom(String, 1, _, 1, FixedString), !. 406 407remove_quotes(String, String) :- 408 atom(String). 409 410remove_quotes([], []). 411 412remove_quotes([String|MoreStrings], [FixedString|MoreFixedStrings]) :- 413 remove_quotes(String, FixedString), 414 remove_quotes(MoreStrings, MoreFixedStrings).
422is_quoted(String, QuoteChar) :- 423 sub_atom(String, 0, 1, _, QuoteChar), 424 sub_atom(String, _, 1, 0, QuoteChar). 425 426 427 428%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 429% Miscellaneous predicates for interacting with files and the OS 430%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
440home_directory(HomeDir) :- 441 % Windows home folder 442 current_prolog_flag(windows, true), !, 443 getenv('HOMEDRIVE', HomeDrive), getenv('HOMEPATH', HomePath), 444 concat_atom([HomeDrive, HomePath], HomeDir). 445 446home_directory(HomeDir) :- 447 % Unix/Linux home folder 448 getenv('HOME', HomeDir).
457file_is_newer(File1, File2) :- 458 time_file(File1, ModTime1), 459 time_file(File2, ModTime2), 460 ModTime1 >= ModTime2. 461 462 463 464%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 465% Other miscellaneous predicates 466%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
476builtin(Predicate) :-
477 functor(Predicate, Functor, Arity),
478 not(number(Functor)),
479 current_module(Module),
480 not(member(Module, [test_prolog])), % Needed for running the tests
481 current_predicate(Module:Functor/Arity), !.
490atom_is_variable(Atom) :- 491 atomic(Atom), 492 atom_chars(Atom, [FirstChar|_]), 493 (FirstChar == '_', ! ; char_type(FirstChar, upper)). 494 495 496 497%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 498% Bousi-Prolog specific predicates 499%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
Valid fuzzy relation properties are 'symmetric', 'reflexive' and
'transitive(TNorm)
', where TNorm can be 'yes', 'no', 'min',
'product' or 'luka'.
513closure_properties(Properties, Closure, TNorm) :-
514 is_list(Properties), !,
515 % Extracts closure properties and t-norm name from list; fuzzy
516 % relation properties are specified by a number which is a
517 % combination of one or more of these flags:
518 % 1 - Reflexive
519 % 2 - Symmetric
520 % 4 - Transitive
521 % These are three common fuzzy binary relations:
522 % 3 - Proximity relation (reflexive and symmetric)
523 % 5 - Partial order (reflexive and transitive)
524 % 7 - Similarity relation (reflexive, symmetric and transitive)
525 (member(transitive(TNormName), Properties) ->
526 (TNormName \== no ->
527 NTransitive is 0b100
528 ;
529 NTransitive is 0
530 )
531 ;
532 (member(transitive, Properties) ->
533 NTransitive is 0b100
534 ;
535 NTransitive is 0
536 )
537 ),
538 (member(symmetric, Properties) ->
539 NSymmetric is 0b010
540 ;
541 NSymmetric is 0
542 ),
543 (member(reflexive, Properties) ->
544 NReflexive is 0b001
545 ;
546 NReflexive is 0
547 ),
548 Closure is NTransitive + NSymmetric + NReflexive,
549 % Sets default t-norm if it doesn't appear in properties list
550 (var(TNormName) ->
551 TNormName = yes
552 ;
553 true
554 ),
555 % Gets t-norm identifier
556 (TNormName == product ->
557 TNorm is 2
558 ;
559 (TNormName == luka ->
560 TNorm is 3
561 ;
562 % TNormName == yes / no / min
563 TNorm is 1
564 )).
573relation_name('~', sim). 574relation_name('<~', lEqThan). 575relation_name('~>', gEqThan). 576relation_name('~1~', frel1). 577relation_name('~2~', frel2). 578relation_name('~3~', frel3).
587relation_evaluator(lEqThan, e_lEqThan). 588relation_evaluator(gEqThan, e_gEqThan). 589relation_evaluator(frel1, e_frel1). 590relation_evaluator(frel2, e_frel2). 591relation_evaluator(frel3, e_frel3). 592 593 594%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 595% append_goals(+Goals1,+Goals2,-Goals) Appends the two input 596% goals, returning a concatenated goal and excluding 597% true goals 598%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 599 600append_goals(true, (A,B), C) :- 601 !, 602 append_goals(A,B,C). 603append_goals((A,B), true, C) :- 604 !, 605 append_goals(A,B,C). 606append_goals(true, true, true) :- 607 !. 608append_goals(true, A, A) :- 609 !. 610append_goals(A,true, A) :- 611 !. 612append_goals((A,B), C, E) :- 613 !, 614 append_goals(B, C, D), 615 append_goals(A, D, E). 616append_goals(A, (B,C), (A,D)) :- 617 !, 618 append_goals(B, C, D). 619append_goals(A, B, (A,B)). 620 621append_goals_list([A],A). 622append_goals_list([A,B|Gs],G) :- 623 append_goals(A,B,C), 624 append_goals_list([C|Gs],G). 625 626 627 628%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 629% atoms_in_term(+Term, -Functors) Returns all the atoms 630% in Term 631%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 632 633% atoms_in_term(Term, Functors) :- 634% atoms_in_term(Term, Functors, []). 635 636 637% atoms_in_term(Var) --> 638% { 639% var(Var), 640% ! 641% }, 642% []. 643 644% atoms_in_term(Number) --> 645% { 646% number(Number), 647% ! 648% }, 649% []. 650 651% atoms_in_term(Atom) --> 652% { 653% atom(Atom), 654% ! 655% }, 656% [Atom]. 657 658% atoms_in_term([]) --> 659% !, 660% []. 661 662 663% atoms_in_term(Term) --> 664% { 665% Term =.. [_Functor|Terms] 666% }, 667% atoms_in_term_list(Terms). 668 669% atoms_in_term_list([]) --> 670% []. 671% atoms_in_term_list([Term|Terms]) --> 672% atoms_in_term(Term), 673% atoms_in_term_list(Terms).