1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 2% Bousi-Prolog parser 3 4:- module(parser, [ 5 parse_program/7, % +ProgramFile, +OntologyFile, -Directives, 6 % -Rules, -Equations, -LingTerms, 7 % -Messages 8 parse_query/5 % +ProgramPrefix, +String, -Query, 9 % -LingTerms, -Messages 10 ]). 11 12:- use_module(directives). 13:- use_module(utilities). 14 15:- use_module(library(lists)). 16 17%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 18 19:- set_prolog_flag(double_quotes, codes). 20 21%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 22% Parser predicates for Bousi-Prolog files 23%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
OntologyFile can be '' (an empty string) if no ontology is needed. The five lists returned by this predicate follow an intermediate format intended to be read by 'translator' module in order to build a TPL file.
46parse_program(ProgramFile, OntologyFile, Directives, Rules, Equations,
47 LingTerms, Messages) :-
48
49 % Sets the prefix for the user-defined predicates
50 utilities:simplify_filename(ProgramFile, SimplifiedFilename),
51 program_prefix(OldProgramPrefix),
52 retract(program_prefix(OldProgramPrefix)),
53 assert(program_prefix(SimplifiedFilename)),
54 % Reads and parses program file
55 reset_parser,
56 parse_file(ProgramFile, DirectivesF, RulesF, EquationsF),
57 % Checks if an ontology needs to be loaded
58 (OntologyFile == '' ->
59 DirectivesO = [], RulesO = [], EquationsO = [],
60 (RulesF == [], not((DirectivesF == [], EquationsF == [])) ->
61 add_message_in_file(ProgramFile,
62 'Program have no rules and seems to be an ontology. \c
63 Use \'ld -o\' if you want to load an ontology into a program.',
64 warning)
65 ;
66 true
67 )
68 ;
69 % Reads and parses ontology file
70 parse_file(OntologyFile, DirectivesO, RulesO, EquationsO),
71 (RulesO == [] ->
72 true
73 ;
74 add_message_in_file(OntologyFile,
75 'Ontologies can only contain equations and directives.',
76 error)
77 )
78 ),
79 % Sorts all errors and warnings by file name, line and column
80 messages(UnsortedMessages),
81 sort(UnsortedMessages, Messages),
82 % Joins directives, equations and rules of both files
83 append(DirectivesF, DirectivesO, Directives),
84 append(RulesF, RulesO, Rules),
85 append(EquationsF, EquationsO, Equations),
86 % Gets the linguistic terms found in source code files and removes duplicates
87 linguistic_terms(LingTermsWithDuplicates),
88 list_to_set(LingTermsWithDuplicates, LingTerms).
100parse_file(File, Directives, Rules, Equations) :- 101 % Saves source code filename, which will be used to show errors 102 bpl_filename(OldFile), 103 retract(bpl_filename(OldFile)), 104 assert(bpl_filename(File)), 105 % Opens file and reads its contents 106 read_file_to_codes(File, Codes, []), 107 atom_codes(Atom, Codes), 108 % Parses source code 109 foreign:ext_tokenize(Atom, Tokens), 110 phrase(bousi_prolog_program(Directives, Rules, Equations), Tokens), 111 !, 112 % Restores original filename 113 retract(bpl_filename(File)), 114 assert(bpl_filename(OldFile)). 115 116 117 118%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 119% Parser predicates for Bousi-Prolog queries 120%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
Both the Query and the LingTerms list returned by this predicate follow an intermediate format intended to be read by 'translator' module.
141parse_query(ProgramPrefix, String, Query, LingTerms, Messages) :- 142 % Sets the prefix for user-defined predicates 143 program_prefix(OldProgramPrefix), 144 retract(program_prefix(OldProgramPrefix)), 145 assert(program_prefix(ProgramPrefix)), 146 % Parses query 147 reset_parser, 148 foreign:ext_tokenize(String, Tokens), 149 phrase(query(Query), Tokens), 150 !, 151 % Sorts all errors and warnings by file name, line and column 152 messages(UnsortedMessages), 153 sort(UnsortedMessages, Messages), 154 % Gets the linguistic terms found in the query and removes duplicates 155 linguistic_terms(LingTermsWithDuplicates), 156 list_to_set(LingTermsWithDuplicates, LingTerms). 157 158 159 160%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 161% DCG (Definite Clause Grammar) rules for parsing Bousi-Prolog programs 162%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
175bousi_prolog_program([], [], []) --> 176 % Normal end-of-file 177 [eof(_, _)]. 178 179bousi_prolog_program(Directives, Rules, Equations) --> 180 % Bousi-Prolog equation 181 bpl_equation(Equations1, _), 182 { 183 ! 184 }, 185 bousi_prolog_program(Directives, Rules, Equations2), 186 { 187 append(Equations1, Equations2, Equations) 188 }. 189 190bousi_prolog_program(Directives, Rules, Equations) --> 191 % Bousi-Prolog specific directive 192 % The directive wn_gen_prox_equations generates new proximity equations as well 193 bpl_directive(Directives1, ReplacedDirectives1, Equations1, _), 194 { 195 ! 196 }, 197 bousi_prolog_program(Directives2, Rules, Equations2), 198 { 199 append(Directives1, Directives2, Directives), 200 append(Equations1, Equations2, Equations3), 201 % With the rules already read, generate proximity equations for the directive wn_gen_prox_equations in auto mode 202 add_auto_gen_prox_equations(ReplacedDirectives1, Rules, Equations3, Equations) 203 }. 204 205bousi_prolog_program(Directives, Rules, Equations) --> 206 % Special include/1 directive 207 include_directive(Directives1, Rules1, Equations1, _), 208 { 209 ! 210 }, 211 bousi_prolog_program(Directives2, Rules2, Equations2), 212 { 213 append(Directives1, Directives2, Directives), 214 append(Rules1, Rules2, Rules), 215 append(Equations1, Equations2, Equations) 216 }. 217 218bousi_prolog_program(Directives, Rules, Equations) --> 219 % Prolog directive 220 directive(Directives1, _), 221 { 222 ! 223 }, 224 bousi_prolog_program(Directives2, Rules, Equations), 225 { 226 append(Directives1, Directives2, Directives) 227 }. 228 229bousi_prolog_program(Directives, Rules, Equations) --> 230 % Rule or fact 231 rule(Rules1, [Line, _]), 232 { 233 !, 234 Rules1 = [[RuleContent, _HeadBlockConstraints, _BodyBlockConstraints, _RuleDegreeVars]], 235 check_singleton(RuleContent, Line), 236 check_free_variables(RuleContent, Line, false) 237 }, 238 bousi_prolog_program(Directives, Rules2, Equations), 239 { 240 append(Rules1, Rules2, Rules) 241 }. 242 243bousi_prolog_program(Directives, Rules, Equations) --> 244 % If all of the previous rules fail, there must be a syntax error 245 % in source code; this rule will try to find it and go on parsing 246 bousi_prolog_program_error(Directives, Rules, Equations). 247 248 249%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 250%%% add_auto_gen_prox_equations(+Directives, +Rules, -InEquations, -OutEquations) 251%%% 252%%% If Directives is [:- directive(wn_gen_prox_equations, [Measure, Auto])], then 253%%% return in OutEquations all the equations derived from constants in Rules 254%%% Otherwise, return InEquations 255 256add_auto_gen_prox_equations([:- directive(Directive, [Measure, Auto])], Rules, InEquations, OutEquations) :- 257 Directive==wn_gen_prox_equations, 258 \+ is_list(Auto), 259 !, 260 wn_gen_prox_equations:wn_auto_gen_prox_equations([:- directive(Directive, [Measure, Auto])], Rules, InEquations, OutEquations). 261 262add_auto_gen_prox_equations(_Directives, _Rules, Equations, Equations).
transitivity(yes)
.' is
translated into ':- directive(transitivity, [yes])
.').
A directive, such as wn_gen_prox_equations, can be replaced by the proximity equations it generates
275bpl_directive(Directives, ReplacedDirectives, Equations, [Line, Column]) -->
276 [name(':-', [Line, Column])], term(Term, [], _), [name('.', _)],
277 {
278 parse_expression(Term, ResultTerm),
279 ResultTerm =.. [Name|Arguments],
280 catch((
281 % Checks if specified directive is a valid BPL directive
282 directives:is_directive_valid(Name, Arguments),
283 % Executes the directive
284 directives:directive(Name, Arguments, Equations),
285 (directives:replaced_directive(Name) ->
286 Directives = [],
287 ReplacedDirectives = [:- directive(Name, Arguments)]
288 ;
289 Directives = [:- directive(Name, Arguments)],
290 ReplacedDirectives = [])
291 % (catcher)
292 ), directive_error(ErrorMessage), (
293 % Directive isn't valid
294 add_message(ErrorMessage, Line, Column, error),
295 Directives = []
296 ))
297 }.
310bpl_equation(Equation, [Line, Column]) -->
311 symbol(Sym1, [Line, Column]), [relation(RelOp, _)], symbol(Sym2, _),
312 [name('=', _)], number_(Value, [LineValue, ColumnValue]), [name('.', _)],
313 {
314 ((Value >= 0.0, Value =< 1.0)
315 ->
316 utilities:relation_name(RelOp, RelName),
317 (RelName == sim,
318 flags:get_bpl_flag(lambda_cut(LambdaCut)),
319 LambdaCut > Value
320 ->
321 add_message('Equation not loaded: value is below the lambda cut.',
322 LineValue, ColumnValue, warning),
323 Equation = []
324 ;
325 EqAux =.. [RelName, Sym1, Sym2, Value], Equation = [EqAux]
326 )
327 ;
328 add_message('Equation value is not a number in range [0.0, 1.0].',
329 LineValue, ColumnValue, error),
330 Equation = []
331 )
332 }.
342include_directive(Directives, Rules, Equations, [Line, Column]) -->
343 [name(':-', [Line, Column])], atom_('include', _),
344 [left_parenthesis(_, _)], atom_(QuotedFile, _), [right_parenthesis(_, _)],
345 [name('.', _)],
346 {
347 % Gets the real path of the included file
348 utilities:remove_quotes(QuotedFile, File),
349 (is_absolute_file_name(File) ->
350 RealFile = File
351 ;
352 % Joins the path of the BPL file that is being parsed and the
353 % included filename to get its real path; this is needed if the
354 % BPL file isn't in the current working directory, for example
355 % if '/home/user/pl/a.bpl' contains ':- include('b.bpl').' and
356 % the file is loaded from '/home/user' using 'ld pl/a.bpl', the
357 % real path of the included file isn't 'b.bpl', but 'pl/b.bpl'
358 bpl_filename(CurrentFile),
359 file_directory_name(CurrentFile, CurrentDirectory),
360 concat_atom([CurrentDirectory, '/', File], RealFile)
361 ),
362 % Checks whether the included file exists
363 (exists_file(RealFile) ->
364 % Parses recursively the included file
365 parse_file(RealFile, Directives, Rules, Equations)
366 ;
367 % Included file doesn't exist or path is invalid
368 swritef(Message, 'Included file does not exist: \'%w\'.', [RealFile]),
369 add_message(Message, Line, Column, error),
370 Directives = [], Rules = [], Equations = []
371 )
372 }.
383directive([Directive], [Line, Column]) -->
384 [name(':-', [Line, Column])], term(Term, [], _), [name('.', _)],
385 {
386 parse_expression(Term, ResultTerm),
387 % Checks if this directive needs a special treatment
388 (ResultTerm = op(OpPrio, OpType, OpName) ->
389 (atom(OpName) ->
390 % Directive declares a single operator
391 declare_custom_operator(OpPrio, OpType, [OpName])
392 ;
393 % Directive declares a list of operators
394 declare_custom_operator(OpPrio, OpType, OpName)
395 ),
396 Directive = (:- ResultTerm)
397 ;
398 (ResultTerm = dynamic(Pred/Arity) ->
399 % Directive declares a dynamic predicate, so its name and
400 % arity must be changed from 'pred/2' to 'prefix_pred/3'
401 program_prefix(Prefix),
402 concat_atom([Prefix, '_', Pred], NewPred),
403 translator:expanded_rule_arity(Arity, NewArity),
404 Directive = (:- dynamic(NewPred/NewArity))
405 ;
406 (ResultTerm = discontiguous(Pred/Arity) ->
407 % Directive declares a dynamic predicate, so its name and
408 % arity must be changed from 'pred/2' to 'prefix_pred/3'
409 program_prefix(Prefix),
410 concat_atom([Prefix, '_', Pred], NewPred),
411 translator:expanded_rule_arity(Arity, NewArity),
412 Directive = (:- discontiguous(NewPred/NewArity))
413 ;
414 % No special treatment needed
415 Directive = (:- ResultTerm)
416 )))
417 }.
For example, if the program being loaded is called "prog.bpl",
given the rule "a(X)
:- b(X)
, c, true", the parser will translate
this rule into a list with these two items:
prog_a(X, DG)
:- prog_b(X, D1)
, prog_c(D2)
, true.
441rule([Rule], [Line, Column]) -->
442 basic_prolog_term(HeadWithoutDegreeVar, [Line, Column]),
443 (
444 % Clause is a rule
445 [name(':-', _)],
446 term(Term, [not_allowed_ops([':-'])], _),
447 [name('.', _)],
448 {
449 % Checks if the rule's head references an existing predicate
450 (utilities:builtin(HeadWithoutDegreeVar) ->
451 functor(HeadWithoutDegreeVar, Functor, Arity),
452 swritef(Message, 'No permission to redefine built-in predicate \'%w/%w\'.', [Functor, Arity]),
453 add_message(Message, Line, Column, error)
454 ;
455 true
456 ),
457 % Translates the list of terms and operators returned by term/2
458 % into a real Prolog term
459 parse_expression(Term, BodyWithoutDegreeVars),
460 % Adds the degree variables to rule's body
461 add_degree_variables(BodyWithoutDegreeVars, BodyWithDegreeVars, RuleDegreeVars),
462 % Adds the block constraints variables to rule's body
463 add_block_constraints_variables(BodyWithDegreeVars, Body, BodyConstraintBlockVars)
464 }
465 ;
466 % Clause is a fact
467 [name('.', _)],
468 {
469 % Checks if the rule's head references an existing predicate
470 (utilities:builtin(HeadWithoutDegreeVar) ->
471 functor(HeadWithoutDegreeVar, Functor, Arity),
472 swritef(Message, 'No permission to redefine built-in predicate \'%w/%w\'.', [Functor, Arity]),
473 add_message(Message, Line, Column, error)
474 ;
475 true
476 ),
477 Body = true,
478 RuleDegreeVars = [],
479 BodyConstraintBlockVars = [C, C]
480 }
481 ),
482 {
483 % Adds a degree variable to rule's head
484 add_degree_variables(HeadWithoutDegreeVar, HeadWithDegreeVar, _HeadDegreeVars),
485 % Adds the block constraints variables to rule's body
486 add_block_constraints_variables(HeadWithDegreeVar, Head, HeadConstraintBlockVars),
487 % Builds a list with the parsed rule and the list of degree
488 % variables created while scanning its body
489 Rule = [(Head :- Body), HeadConstraintBlockVars, BodyConstraintBlockVars, RuleDegreeVars]
490 }.
Options is a list that can contain the following items:
not_allowed_ops(+Operators)
: Operators is a list of operators
that can't be used as the main operator in this term.516term(Term, Options, [Line, Column]) --> 517 % Term with a prefix operator (operator can't be '\+' nor 'not' 518 % because negations are handled in basic_prolog_term/2 rule) 519 operator(Operator, [Line, Column]), 520 { 521 % Checks that operator is allowed 522 Operator \== \+, Operator \== not, 523 (member(not_allowed_ops(NotAllowedOps), Options) -> 524 not(member(Operator, NotAllowedOps)) 525 ; 526 true 527 ), 528 % Verifies that operator is defined and it's a prefix one 529 operator_type(_, OpType, Operator), 530 member(OpType, [fx, fy]) 531 }, 532 term(SingleTerm, Options, _), 533 { 534 Term = [exp_operator(Operator, prefix, [Line, Column])|SingleTerm] 535 }. 536 537term(Term, Options, [Line, Column]) --> 538 % Term with an infix operator, or without operator 539 basic_term(FirstTerm, Options, [Line, Column]), 540 remaining_term(RemainingTerm, Options), 541 { 542 append([FirstTerm], RemainingTerm, Term) 543 }. 544 545remaining_term(RemainingTerm, Options) --> 546 % Infix operator 547 operator(Operator, [LineOp, ColumnOp]), 548 { 549 (member(not_allowed_ops(NotAllowedOps), Options) -> 550 not(member(Operator, NotAllowedOps)) 551 ; 552 true 553 ), 554 operator_type(_, OpType, Operator), 555 member(OpType, [xfx, xfy, yfx]) 556 }, 557 term(Term, Options, _), 558 { 559 RemainingTerm = [exp_operator(Operator, infix, [LineOp, ColumnOp])|Term] 560 }. 561 562remaining_term([], _Options) --> 563 % No operator 564 [].
575basic_term(RelName, _Options, [Line, Column]) --> 576 % Single BPL operator 577 [relation(RelOperator, [Line, Column])], 578 { 579 utilities:relation_name(RelOperator, RelName) 580 }. 581 582basic_term(Term, _Options, [Line, Column]) --> 583 % Prolog term 584 basic_prolog_term(Term, [Line, Column]). 585 586basic_term(BPLTerm, Options, [Line, Column]) --> 587 % Bousi-Prolog weak unification or term comparison 588 { 589 not(member(no_comparisons, Options)) 590 }, 591 bpl_comparison(BPLTerm, [Line, Column]).
a(X)
~ b(X)
< 0.5") or term comparison (e.g. "a ~> b =:= 1").600bpl_comparison(BPLTerm, [Line, Column]) --> 601 % Weak unification operator (~) 602 basic_term(BasicTerm1, [no_comparisons], [Line, Column]), 603 [relation('~', _)], 604 basic_term(BasicTerm2, [no_comparisons], _), 605 [name(Operator, _)], number_or_variable(Value, _), 606 { 607 member(Operator, [=, =:=, =\=, =<, >=, >, <]), 608 % A term like "a(X) ~ b(X) >= 0.5" is translated into: 609 % "unify_a1(a(X), b(X), >=, 0.5)" 610 unify_predicate_name(UnifyPredicateName) , 611 BPLTerm =.. [UnifyPredicateName, BasicTerm1, BasicTerm2, Operator, Value] 612 }. 613 614bpl_comparison(BPLTerm, [Line, Column]) --> 615 % Syntactic sugar: "a ~ b" is equivalent to "a ~ b > 0" 616 basic_term(BasicTerm1, [no_comparisons], [Line, Column]), 617 [relation('~', _)], 618 basic_term(BasicTerm2, [no_comparisons], _), 619 { 620 unify_predicate_name(UnifyPredicateName), 621 BPLTerm =.. [UnifyPredicateName, BasicTerm1, BasicTerm2, >, 0] 622 }. 623 624bpl_comparison(BPLTerm, [Line, Column]) --> 625 % Extended BPL operators (~>, <~, ~1~, ~2~, ~3~) 626 basic_term(BasicTerm1, [no_comparisons], [Line, Column]), 627 [relation(RelOperator, _)], 628 basic_term(BasicTerm2, [no_comparisons], _), 629 [name(Operator, _)], number_or_variable(Value, _), 630 { 631 RelOperator \== '~', 632 utilities:relation_name(RelOperator, RelName), 633 utilities:relation_evaluator(RelName, RelEvaluator), 634 member(Operator, [=, =:=, =\=, =<, >=, >, <]), 635 % A term like "a(X) ~2~ b(X) =:= 1.0" is translated into: 636 % "e_frel2(a(X), b(X), _Degree, =:=, 1.0)" 637 BPLTerm =.. [RelEvaluator, BasicTerm1, BasicTerm2, Operator, Value] 638 }. 639 640bpl_comparison(BPLTerm, [Line, Column]) --> 641 % Syntactic sugar: "a · b" is equivalent to "a · b > 0" 642 basic_term(BasicTerm1, [no_comparisons], [Line, Column]), 643 [relation(RelOperator, _)], 644 basic_term(BasicTerm2, [no_comparisons], _), 645 { 646 RelOperator \== '~', 647 utilities:relation_name(RelOperator, RelName), 648 utilities:relation_evaluator(RelName, RelEvaluator), 649 BPLTerm =.. [RelEvaluator, BasicTerm1, BasicTerm2, >, 0] 650 }. 651 652 653unify_predicate_name(UnifyPredicateName) :- 654 flags:get_bpl_flag(weak_unification(Algorithm)), 655 atom_concat('unify_', Algorithm, UnifyPredicateName).
666basic_prolog_term(Number, [Line, Column]) --> 667 % Integer number 668 [integer(Number, [Line, Column])]. 669 670basic_prolog_term(Number, [Line, Column]) --> 671 % Floating point number 672 [float(Number, [Line, Column])]. 673 674basic_prolog_term(Variable, [Line, Column]) --> 675 % Variable 676 [variable(Variable, [Line, Column])]. 677 678basic_prolog_term(HigherOrderTerm, [Line, Column]) --> 679 % Higher-order predicate (includes negated terms) 680 higher_order_prolog_term(HigherOrderTerm, [Line, Column]). 681 682basic_prolog_term(Compound, [Line, Column]) --> 683 % Compound term (functional notation) 684 atom_or_linguistic_term(Atom, [Line, Column]), 685 [left_parenthesis(_, _)], argument_list(Args, _), [right_parenthesis(_, _)], 686 { 687 Compound =.. [Atom|Args] 688 }. 689 690basic_prolog_term(InnerTerm, [Line, Column]) --> 691 % Term in parenthesis 692 [left_parenthesis(_, [Line, Column])], term(Term, [], _), [right_parenthesis(_, _)], 693 { 694 parse_expression(Term, InnerTerm) 695 }. 696 697basic_prolog_term(List, [Line, Column]) --> 698 % Non-empty list 699 [left_bracket(_, [Line, Column])], items(List, _), [right_bracket(_, _)]. 700 701basic_prolog_term(CharCodeList, [Line, Column]) --> 702 % String as a character code list 703 [character_code_list(CharCodeList, [Line, Column])]. 704 705basic_prolog_term(Atom, [Line, Column]) --> 706 % Atom (including empty list) 707 atom_or_linguistic_term(Atom, [Line, Column]).
719bpl_linguistic_term(BPLTerm, [Line, Column]) --> 720 % 1st type: crisp domain ranges 721 % domain#minimum#maximum (e.g., height#20#100) 722 [name(Domain, [Line, Column])], [builder(_, _)], 723 integer_number(Minimum, _), [builder(_, _)], 724 integer_number(Maximum, _), 725 { 726 % Builds the name and the definition of the fuzzy subset 727 % 'height#20#100' is translated into 'height_20_100(between(20, 100))' 728 concat_atom([Domain, '_', Minimum, '_', Maximum], InitialBPLTerm), 729 utilities:simplify_atom(InitialBPLTerm, BPLTerm), 730 NewSubset =.. [BPLTerm, between(Minimum, Maximum)], 731 % Adds the new subset to the list of linguistic terms 732 linguistic_terms(OldLingTerms), 733 retract(linguistic_terms(OldLingTerms)), 734 append(OldLingTerms, [[domain, Domain, NewSubset]], NewLingTerms), 735 assert(linguistic_terms(NewLingTerms)) 736 }. 737 738bpl_linguistic_term(BPLTerm, [Line, Column]) --> 739 % 2nd type: fuzzy domain ranges 740 % modifier#domain#minimum#maximum (e.g., about#speed#100#120) 741 % Valid modifiers: [about] 742 [name(Modifier, [Line, Column])], [builder(_, _)], 743 [name(Domain, _)], [builder(_, _)], 744 integer_number(Minimum, _), [builder(_, _)], 745 integer_number(Maximum, _), 746 { 747 % Builds the name and the definition of the fuzzy subset 748 % 'about#speed#100#120' is translated into 749 % 'about_speed_100_120(about(100, 120))' 750 member(Modifier, [about]), 751 concat_atom([Modifier, '_', Domain, '_', Minimum, '_', Maximum], InitialBPLTerm), 752 utilities:simplify_atom(InitialBPLTerm, BPLTerm), 753 NewSubsetDef =.. [Modifier, Minimum, Maximum], 754 NewSubset =.. [BPLTerm, NewSubsetDef], 755 % Adds the new subset to the list of linguistic terms 756 linguistic_terms(OldLingTerms), 757 retract(linguistic_terms(OldLingTerms)), 758 append(OldLingTerms, [[domain, Domain, NewSubset]], NewLingTerms), 759 assert(linguistic_terms(NewLingTerms)) 760 }. 761 762bpl_linguistic_term(BPLTerm, [Line, Column]) --> 763 % 3rd type: domain points 764 % domain#value (e.g., temperature#38) 765 [name(Domain, [Line, Column])], [builder(_, _)], 766 integer_number(Number, _), 767 { 768 % Builds the name and the definition of the fuzzy subset 769 % 'temperature#38' is translated into 'temperature_38(point(38))' 770 concat_atom([Domain, '_', Number], InitialBPLTerm), 771 utilities:simplify_atom(InitialBPLTerm, BPLTerm), 772 NewSubset =.. [BPLTerm, point(Number)], 773 % Adds the new subset to the list of linguistic terms 774 linguistic_terms(OldLingTerms), 775 retract(linguistic_terms(OldLingTerms)), 776 append(OldLingTerms, [[domain, Domain, NewSubset]], NewLingTerms), 777 assert(linguistic_terms(NewLingTerms)) 778 }. 779 780bpl_linguistic_term(BPLTerm, [Line, Column]) --> 781 % 4th type: fuzzy domain points 782 % modifier#domain#value (e.g., about#age#50) 783 % Valid modifiers: [about] 784 [name(Modifier, [Line, Column])], [builder(_, _)], 785 [name(Domain, _)], [builder(_, _)], 786 integer_number(Value, _), 787 { 788 % Builds the name and the definition of the fuzzy subset 789 % 'about#age#50' is translated into 'about_age_50(about(50))' 790 member(Modifier, [about]), 791 concat_atom([Modifier, '_', Domain, '_', Value], InitialBPLTerm), 792 utilities:simplify_atom(InitialBPLTerm, BPLTerm), 793 NewSubsetDef =.. [Modifier, Value], 794 NewSubset =.. [BPLTerm, NewSubsetDef], 795 % Adds the new subset to the list of linguistic terms 796 linguistic_terms(OldLingTerms), 797 retract(linguistic_terms(OldLingTerms)), 798 append(OldLingTerms, [[domain, Domain, NewSubset]], NewLingTerms), 799 assert(linguistic_terms(NewLingTerms)) 800 }. 801 802 803bpl_linguistic_term(BPLTerm, [Line, Column]) --> 804 % 5th type: compound linguistic terms 805 % modifier#subset (e.g., extremely#small) 806 % Valid modifiers: [very, somewhat, more_or_less, extremely] 807 [name(Modifier, [Line, Column])], [builder(_, _)], 808 [name(Subset, _)], 809 { 810 % Builds the name and the definition of the fuzzy subset 811 % 'extremely#small' is translated into 'extremely_small(extremely(small))' 812 member(Modifier, [very, somewhat, more_or_less, extremely]), 813 concat_atom([Modifier, '_', Subset], InitialBPLTerm), 814 utilities:simplify_atom(InitialBPLTerm, BPLTerm), 815 NewSubsetAux =.. [Modifier, Subset], 816 NewSubset =.. [BPLTerm, NewSubsetAux], 817 % Adds the new subset to the list of linguistic terms 818 linguistic_terms(OldLingTerms), 819 retract(linguistic_terms(OldLingTerms)), 820 append(OldLingTerms, [[subset, Subset, NewSubset]], NewLingTerms), 821 assert(linguistic_terms(NewLingTerms)) 822 }.
Currently, these are the supported higher-order predicates:
Goals can be any kind of term, including compound terms built with control predicates such as ,/2, ;/2 or ->/2. All the higher- order predicates except not/1 and \+/1 are crisp and can either fail or succeed with approximation degree 1.
856higher_order_prolog_term(Compound, [Line, Column]) --> 857 % Negated term 858 atom_(Atom, [Line, Column]), 859 { 860 (Atom == not ; Atom == \+) 861 }, 862 [left_parenthesis(_, _)], 863 term(Term, [not_allowed_ops([','])], _), 864 [right_parenthesis(_, _)], 865 { 866 parse_expression(Term, ResultTermWithoutCtrsAndDegreeVars), 867% add_degree_variables(ResultTermWithoutDegreeVars, ResultTerm, GoalDegreeVars), 868 add_degree_variables(ResultTermWithoutCtrsAndDegreeVars, ResultTermWithoutCtrsVars, GoalDegreeVars), 869 add_block_constraints_variables(ResultTermWithoutCtrsVars, ResultTerm, BlockConstraintsVars), 870 check_free_variables(ResultTerm, Line, true), 871% var(Degree), 872 (flags:get_bpl_flag(weak_unification(a1)) -> 873 Compound = eval_negation(Atom, ResultTerm, GoalDegreeVars, _Degree) 874 ; 875 Compound = eval_negation(Atom, ResultTerm, BlockConstraintsVars, GoalDegreeVars, _Degree) 876 ) 877 }. 878 879higher_order_prolog_term(Compound, [Line, Column]) --> 880 % Higher-order predicates with signature "name(:Goal)" [only facts]: 881 % assert/1, retract/1 882 atom_(Atom, [Line, Column]), 883 { 884 higher_order_predicate(Atom, [atom]) 885 }, 886 [left_parenthesis(_, _)], 887 basic_prolog_term(BasicTermWithoutCtrsAndDegreeVars, _), 888 [right_parenthesis(_, _)], 889 { 890 add_degree_variables(BasicTermWithoutCtrsAndDegreeVars, BasicTermWithoutCtrsVars, _DegreeVars), % WARNING: DegreeVars are ignored 891 add_block_constraints_variables(BasicTermWithoutCtrsVars, BasicTerm, _BlockConstraintsVars), % WARNING: Block constraint variables are ignored 892 Compound =.. [Atom, BasicTerm] 893 }. 894 895higher_order_prolog_term(Compound, [Line, Column]) --> 896 % Higher-order predicates with signature "name(:Goal)": 897 % call/1, once/1, ignore/1, time/1 898 atom_(Atom, [Line, Column]), 899 { 900 higher_order_predicate(Atom, [goal]), Atom \== \+, Atom \== not 901 }, 902 [left_parenthesis(_, _)], 903 term(Term, [not_allowed_ops([','])], _), 904 [right_parenthesis(_, _)], 905 { 906 % Parses the inner term 907 parse_expression(Term, ResultTermWithoutCtrsAndDegreeVars), 908 % Adds the degree variables to the goal 909 add_degree_variables(ResultTermWithoutCtrsAndDegreeVars, ResultTermWithoutCtrsVars, _GoalDegreeVars), % WARNING: DegreeVars are ignored 910 add_block_constraints_variables(ResultTermWithoutCtrsVars, ResultTerm, _BlockConstraintsVars), % WARNING: Block constraint variables are ignored 911 check_free_variables(ResultTerm, Line, true), 912 % Creates the final compound term 913 (Atom == call -> 914 Compound =.. [bpl_call, ResultTerm] 915 ; 916 BPLCall =.. [bpl_call, ResultTerm], 917 Compound =.. [Atom, BPLCall] 918 ) 919 }. 920 921higher_order_prolog_term(Compound, [Line, Column]) --> 922 % Higher-order predicates with signature "name(:Goal, +List)": 923 % apply/2, maplist/2 924 atom_(Atom, [Line, Column]), 925 { 926 higher_order_predicate(Atom, [nongoal, nongoal]) 927 }, 928 [left_parenthesis(_, _)], 929 term(Term1, [not_allowed_ops([','])], _), 930 [comma(_, _)], 931 term(Term2, [not_allowed_ops([','])], _), 932 [right_parenthesis(_, _)], 933 { 934 % Parses the inner terms 935 parse_expression(Term1, ResultTerm1), 936 parse_expression(Term2, ResultTerm2), 937 % Adds the degree variables to the goals 938 check_free_variables(ResultTerm1, Line, true), 939 check_free_variables(ResultTerm2, Line, true), 940 % Creates the final compound term 941 (Atom == apply -> 942 Compound =.. [bpl_apply, ResultTerm1, ResultTerm2] 943 ; (Atom == maplist -> 944 Compound =.. [bpl_maplist, ResultTerm1, ResultTerm2] 945 ; 946 Compound =.. [Atom, ResultTerm1, ResultTerm2] 947 )) 948 }. 949 950higher_order_prolog_term(Compound, [Line, Column]) --> 951 % Higher-order predicates with signature "name(:Condition, :Action)": 952 % forall/2 953 atom_(Atom, [Line, Column]), 954 { 955 higher_order_predicate(Atom, [goal, goal]) 956 }, 957 [left_parenthesis(_, _)], 958 term(Term1, [not_allowed_ops([','])], _), 959 [comma(_, _)], 960 term(Term2, [not_allowed_ops([','])], _), 961 [right_parenthesis(_, _)], 962 { 963 % Parses the inner terms 964 parse_expression(Term1, ResultTerm1WithoutCtrsAndDegreeVars), 965 parse_expression(Term2, ResultTerm2WithoutCtrsAndDegreeVars), 966 % Adds the degree and block constraints variables to the goals 967 add_degree_variables(ResultTerm1WithoutCtrsAndDegreeVars, ResultTerm1WithoutCtrsVars, _DegreeVars1), 968 add_block_constraints_variables(ResultTerm1WithoutCtrsVars, ResultTerm1, _BlockConstraintsVars1), 969 add_degree_variables(ResultTerm2WithoutCtrsAndDegreeVars, ResultTerm2WithoutCtrsVars, _DegreeVars2), 970 add_block_constraints_variables(ResultTerm2WithoutCtrsVars, ResultTerm2, _BlockConstraintsVars2), 971 check_free_variables(ResultTerm1, Line, true), 972 check_free_variables(ResultTerm2, Line, true), 973 % Creates the final compound term 974 BPLCall1 =.. [bpl_call, ResultTerm1], 975 BPLCall2 =.. [bpl_call, ResultTerm2], 976 Compound =.. [Atom, BPLCall1, BPLCall2] 977 }. 978 979higher_order_prolog_term(Compound, [Line, Column]) --> 980 % Higher-order predicates with signature "name(+Template, :Goal, -Bag)": 981 % findall/3, bagof/3, setof/3 982 atom_(Atom, [Line, Column]), 983 { 984 higher_order_predicate(Atom, [nongoal, goal, nongoal]) 985 }, 986 [left_parenthesis(_, _)], 987 term(Term1, [not_allowed_ops([','])], _), 988 [comma(_, _)], 989 term(Term2, [not_allowed_ops([','])], _), 990 [comma(_, _)], 991 term(Term3, [not_allowed_ops([','])], _), 992 [right_parenthesis(_, _)], 993 { 994 % Parses the inner terms 995 parse_expression(Term1, ResultTerm1), 996 parse_expression(Term2, ResultTerm2WithoutCtrsAndDegreeVars), 997 parse_expression(Term3, ResultTerm3), 998 % Adds the degree and block constraints variables to the goals 999 add_degree_variables(ResultTerm2WithoutCtrsAndDegreeVars, ResultTerm2WithoutCtrsVars, GoalDegreeVars), 1000 add_block_constraints_variables(ResultTerm2WithoutCtrsVars, ResultTerm2, BlockConstraintsVars), 1001 check_free_variables(ResultTerm2, Line, true), 1002 % Creates the final compound term 1003 ((Atom == bagof ; Atom == setof) -> 1004 % In order to keep the original behavior of the bagof/3 and 1005 % setof/3 predicates, degree variables must be bound with 1006 % the existencial operator, ^/2 1007 add_call_after_bindings(ResultTerm2, BPLCallWithoutBindings), 1008 append(BlockConstraintsVars, GoalDegreeVars, CtrsAndDegreeVars), 1009 bind_term(CtrsAndDegreeVars, BPLCallWithoutBindings, BPLCall) 1010 ; 1011 % findall/3 binds automatically all free variables, so 1012 % it isn't neccesary to bind them manually 1013 BPLCall =.. [bpl_call, ResultTerm2] 1014 ), 1015 Compound =.. [Atom, ResultTerm1, BPLCall, ResultTerm3] 1016 }. 1017 1018higher_order_prolog_term(Compound, [Line, Column]) --> 1019 % Higher-order predicates with signature "name(:Goal, +Catcher, :Recover)": 1020 % catch/3 1021 atom_(Atom, [Line, Column]), 1022 { 1023 higher_order_predicate(Atom, [goal, nongoal, goal]) 1024 }, 1025 [left_parenthesis(_, _)], 1026 term(Term1, [not_allowed_ops([','])], _), 1027 [comma(_, _)], 1028 term(Term2, [not_allowed_ops([','])], _), 1029 [comma(_, _)], 1030 term(Term3, [not_allowed_ops([','])], _), 1031 [right_parenthesis(_, _)], 1032 { 1033 % Parses the inner terms 1034 parse_expression(Term1, ResultTerm1WithoutCtrsAndDegreeVars), 1035 parse_expression(Term2, ResultTerm2), 1036 parse_expression(Term3, ResultTerm3WithoutCtrsAndDegreeVars), 1037 % Adds the degree and block constraints variables to the goals 1038 add_degree_variables(ResultTerm1WithoutCtrsAndDegreeVars, ResultTerm1WithoutCtrsVars, _DegreeVars1), 1039 add_block_constraints_variables(ResultTerm1WithoutCtrsVars, ResultTerm1, _BlockConstraintsVars1), 1040 add_degree_variables(ResultTerm3WithoutCtrsAndDegreeVars, ResultTerm3WithoutCtrsVars, _DegreeVars3), 1041 add_block_constraints_variables(ResultTerm3WithoutCtrsVars, ResultTerm3, _BlockConstraintsVars3), 1042 check_free_variables(ResultTerm1, Line, true), 1043 check_free_variables(ResultTerm3, Line, true), 1044 % Creates the final compound term 1045 BPLCall1 =.. [bpl_call, ResultTerm1], 1046 BPLCall3 =.. [bpl_call, ResultTerm3], 1047 Compound =.. [Atom, BPLCall1, ResultTerm2, BPLCall3] 1048 }.
1057argument_list(ArgList, [Line, Column]) -->
1058 % First argument
1059 expression(FirstArg, [Line, Column]),
1060 (
1061 % Remaining arguments
1062 [comma(_, _)], argument_list(RemainingArgs, _)
1063 ;
1064 % No more arguments
1065 {
1066 RemainingArgs = []
1067 }
1068 ),
1069 {
1070 parse_expression(FirstArg, ResultFirstArg),
1071 ArgList = [ResultFirstArg|RemainingArgs]
1072 }.
1080items(List, [Line, Column]) -->
1081 % First item
1082 expression(Head, [Line, Column]),
1083 (
1084 % Remaining items ([Head, ...])
1085 [comma(_, _)], items(MoreItems, _)
1086 ;
1087 % Tail sublist ([Head|Tail])
1088 [list_separator(_, _)], expression(Tail, _),
1089 {
1090 parse_expression(Tail, MoreItems)
1091 }
1092 ;
1093 % No more items ([Head])
1094 {
1095 MoreItems = []
1096 }
1097 ),
1098 {
1099 parse_expression(Head, FirstItem),
1100 List = [FirstItem|MoreItems]
1101 }.
1110expression([Exp], [Line, Column]) --> 1111 operator(Exp, [Line, Column]), 1112 { 1113 Exp \== ',' 1114 }. 1115 1116expression(Exp, [Line, Column]) --> 1117 term(Exp, [not_allowed_ops([','])], [Line, Column]).
1127atom_or_linguistic_term(Atom, [Line, Column]) --> 1128 atom_(Atom, [Line, Column]). 1129 1130atom_or_linguistic_term(LingTerm, [Line, Column]) --> 1131 bpl_linguistic_term(LingTerm, [Line, Column]).
1142atom_(Atom, [Line, Column]) --> 1143 [name(Atom, [Line, Column])]. 1144 1145atom_([], [Line, Column]) --> 1146 [left_bracket(_, [Line, Column])], [right_bracket(_, _)].
1155operator(Operator, [Line, Column]) --> 1156 [name(Operator, [Line, Column])], 1157 { 1158 operator_type(_, _, Operator) 1159 }. 1160 1161operator(Operator, [Line, Column]) --> 1162 [comma(Operator, [Line, Column])].
1172symbol(Symbol, [Line, Column]) --> 1173 [name(Symbol, [Line, Column])]. 1174 1175symbol(Symbol, [Line, Column]) --> 1176 bpl_linguistic_term(Symbol, [Line, Column]).
1185integer_number(Number, [Line, Column]) --> 1186 [integer(Number, [Line, Column])]. 1187 1188integer_number(Number, [Line, Column]) --> 1189 [name(Sign, [Line, Column])], [integer(UnsignedNumber, _)], 1190 { 1191 (Sign == '-' -> 1192 Number is -UnsignedNumber 1193 ; (Sign == '+' -> 1194 Number is UnsignedNumber 1195 ; 1196 fail 1197 )) 1198 }.
1207float_number(Number, [Line, Column]) --> 1208 [float(Number, [Line, Column])]. 1209 1210float_number(Number, [Line, Column]) --> 1211 [name(Sign, [Line, Column])], [float(UnsignedNumber, _)], 1212 { 1213 (Sign == '-' -> 1214 Number is -UnsignedNumber 1215 ; (Sign == '+' -> 1216 Number is UnsignedNumber 1217 ; 1218 fail 1219 )) 1220 }.
1231number_(Number, [Line, Column]) --> 1232 integer_number(Number, [Line, Column]). 1233 1234number_(Number, [Line, Column]) --> 1235 float_number(Number, [Line, Column]).
1244number_or_variable(Number, [Line, Column]) --> 1245 number_(Number, [Line, Column]). 1246 1247number_or_variable(Variable, [Line, Column]) --> 1248 [variable(Variable, [Line, Column])]. 1249 1250 1251 1252%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 1253% DCG (Definite Clause Grammar) additional rules for parsing queries 1254%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1264query(Query) -->
1265 term(Term, [not_allowed_ops([':-'])], _),
1266 query_end,
1267 {
1268 parse_expression(Term, ResultTermWithoutCtrsAndDegreeVars),
1269 build_query(ResultTermWithoutCtrsAndDegreeVars, Query)
1270 }.
1280build_query(TermWithoutCtrsAndDegreeVars, Query) :-
1281 add_degree_variables(TermWithoutCtrsAndDegreeVars, ResultTermWithoutCtrsVars, DegreeVars),
1282 add_block_constraints_variables(ResultTermWithoutCtrsVars, ResultTerm, BlockConstraintsVars),
1283 init_ctr_store(BlockConstraintsVars),
1284 Query = [ResultTerm, DegreeVars].
1293init_ctr_store([Cin|_]) :- 1294 flags:get_bpl_flag(weak_unification('a3')), 1295 !, 1296 empty_assoc(Cin). 1297 1298init_ctr_store([Cin|_]) :- 1299 flags:get_bpl_flag(weak_unification('a2')), 1300 !, 1301 Cin=[]. 1302 1303init_ctr_store(_Cin).
1312query_end --> 1313 [name('.', _)], [eof(_, _)]. 1314 1315query_end --> 1316 [eof(_, _)]. 1317 1318 1319 1320%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 1321% DCG (Definite Clause Grammar) additional rules for managing errors 1322%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1336bousi_prolog_program_error(Directives, Rules, Equations) --> 1337 % Syntax error in rule body 1338 basic_prolog_term(_Head, _), [name(':-', _)], 1339 term_error([not_allowed_ops([':-'])], _), 1340 next_statement([LineError, ColumnError]), 1341 { 1342 !, 1343 add_message('Syntax error in rule body.', LineError, ColumnError, error) 1344 }, 1345 bousi_prolog_program(Directives, Rules, Equations). 1346 1347bousi_prolog_program_error(Directives, Rules, Equations) --> 1348 % Syntax error in directive body 1349 [name(':-', _)], term_error([not_allowed_ops([':-'])], _), 1350 next_statement([LineError, ColumnError]), 1351 { 1352 !, 1353 add_message('Syntax error in directive.', LineError, ColumnError, error) 1354 }, 1355 bousi_prolog_program(Directives, Rules, Equations). 1356 1357bousi_prolog_program_error(Directives, Rules, Equations) --> 1358 % Syntax error in fact or rule head 1359 term_error([not_allowed_ops([':-'])], _), 1360 next_statement([LineError, ColumnError]), 1361 { 1362 !, 1363 add_message('Syntax error in fact or rule head.', LineError, ColumnError, error) 1364 }, 1365 bousi_prolog_program(Directives, Rules, Equations). 1366 1367bousi_prolog_program_error(Directives, Rules, Equations) --> 1368 % Unknown syntax error in statement 1369 next_statement([LineError, ColumnError]), 1370 { 1371 !, 1372 add_message('Syntax error in statement.', LineError, ColumnError, error) 1373 }, 1374 bousi_prolog_program(Directives, Rules, Equations). 1375 1376bousi_prolog_program_error([], [], []) --> 1377 % End-of-file (this rule is executed only when 'eof' token has been 1378 % taken from input by next_statement/1 in one of the previous rules) 1379 [].
Options is a list that can only contain the following item:
not_allowed_ops(+Operators)
: Operators is a list of operators
that can't be used as the main operator in this term.1401term_error(Options, [Line, Column]) --> 1402 % Term with prefix operator (must appear before following rule) 1403 operator(Operator, [Line, Column]), 1404 { 1405 (member(not_allowed_ops(NotAllowedOps), Options) -> 1406 not(member(Operator, NotAllowedOps)) 1407 ; 1408 true 1409 ), 1410 operator_type(_, OpType, Operator), 1411 member(OpType, [fx, fy]) 1412 }, 1413 term_error(Options, _). 1414 1415term_error(_, [Line, Column]) --> 1416 % Compound term (functional notation) 1417 atom_(_, [Line, Column]), [left_parenthesis(_, _)], term_error([], _). 1418 1419term_error(Options, [Line, Column]) --> 1420 % Term with infix operator, or without operator 1421 basic_term(_, [], [Line, Column]), remaining_term_error(Options). 1422 1423term_error(_, [Line, Column]) --> 1424 % Term in parenthesis 1425 [left_parenthesis(_, [Line, Column])], term_error([], _). 1426 1427term_error(_, [_Line, _Column]) --> 1428 % Can't go on parsing term, syntax error is around here 1429 []. 1430 1431remaining_term_error(Options) --> 1432 % Infix operator 1433 operator(Operator, _), 1434 { 1435 (member(not_allowed_ops(NotAllowedOps), Options) -> 1436 not(member(Operator, NotAllowedOps)) 1437 ; 1438 true 1439 ), 1440 operator_type(_, OpType, Operator), 1441 member(OpType, [xfx, xfy, yfx]) 1442 }, 1443 term_error(Options, _). 1444 1445remaining_term_error(_) --> 1446 % No operator 1447 [].
1459next_statement([Line, Column]) --> 1460 % There is a period before end-of-file 1461 all_tokens('.', [LineError, ColumnError]), [name('.', [LinePeriod, ColumnPeriod])], 1462 { 1463 ((var(LineError), var(ColumnError)) -> 1464 % There aren't any tokens before period 1465 Line = LinePeriod, Column = ColumnPeriod 1466 ; 1467 % There is at least one token before period 1468 Line = LineError, Column = ColumnError 1469 ) 1470 }. 1471 1472next_statement([Line, Column]) --> 1473 % There are no periods before end-of-file 1474 all_tokens('.', [LineError, ColumnError]), [eof(_, [LineEOF, ColumnEOF])], 1475 { 1476 ((var(LineError), var(ColumnError)) -> 1477 % There aren't any tokens before end-of-file 1478 Line = LineEOF, Column = ColumnEOF 1479 ; 1480 % There is at least one token before end-of-file 1481 Line = LineError, Column = ColumnError 1482 ) 1483 }.
1494all_tokens(EndText, [Line, Column]) --> 1495 [Token], 1496 { 1497 Token =.. [Type, Text, [Line, Column]], 1498 Type \== eof, Text \== EndText 1499 }, 1500 all_tokens(EndText, _). 1501 1502all_tokens(_, [_Line, _Column]) --> 1503 []. 1504 1505 1506 1507%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 1508% Predicates for parsing expressions 1509%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1530parse_expression(Expression, SyntaxTree) :- 1531 catch(( 1532 parse_expression_aux(Expression, SyntaxTree) 1533 % (catcher) 1534 ), parse_error(Message, [Line, Column]), ( 1535 % Operator priority clash (here SyntaxTree can be unified 1536 % with any term, as no TPL file nor query won't be generated) 1537 (add_message(Message, Line, Column, error), SyntaxTree = error) 1538 )), !. 1539 1540parse_expression_aux([Expression], Expression) :- 1541 % The expression just contains a single operand 1542 !. 1543 1544parse_expression_aux(Expression, SyntaxTree) :- 1545 % Looks for the highest operator in Expression 1546 highest_operator(Expression, [Operator, _, _, Index]), 1547 % Splits the "plain" expression list into two sublists 1548 length(LeftExpression, Index), 1549 append(LeftExpression, [exp_operator(Operator, Location, _)|RightExpression], Expression), 1550 (Location == infix -> 1551 % Parses each sublist separately 1552 parse_expression_aux(LeftExpression, LeftSyntaxTree), 1553 parse_expression_aux(RightExpression, RightSyntaxTree), 1554 % Builds the syntax tree 1555 SyntaxTree =.. [Operator, LeftSyntaxTree, RightSyntaxTree] 1556 ; 1557 % Parses each sublist separately 1558 % (for prefix operators there's just 1 sublist) 1559 LeftExpression = [], 1560 parse_expression_aux(RightExpression, SingleSyntaxTree), 1561 % Builds the syntax tree 1562 (((Operator == '-' ; Operator == '+'), number(SingleSyntaxTree)) -> 1563 % This special treatment is needed in order to keep positive 1564 % and negative numbers as atomic (non-compound) terms, which is 1565 % the standard behavior according to ISO Prolog 1566 (Operator == '-' -> 1567 SyntaxTree is -SingleSyntaxTree 1568 ; 1569 SyntaxTree is SingleSyntaxTree 1570 ) 1571 ; 1572 SyntaxTree =.. [Operator, SingleSyntaxTree] 1573 ) 1574 ).
1601highest_operator(Expression, OpInfo) :- 1602 highest_operator_aux(Expression, 0, [_, -1, _, _], OpInfo). 1603 1604highest_operator_aux([], _, OpInfo, OpInfo). 1605 1606highest_operator_aux([Head|Tail], Index, OpInfo, FinalOpInfo) :- 1607 Head \= exp_operator(_, _, _), 1608 !, 1609 % If head item isn't an operator, go on analyzing the expression list 1610 NewIndex is Index + 1, 1611 highest_operator_aux(Tail, NewIndex, OpInfo, FinalOpInfo). 1612 1613highest_operator_aux([Head|Tail], Index, [HighOp, HighPrio, HighType, HighPos], FinalOpInfo) :- 1614 nonvar(Head), 1615 Head = exp_operator(Op, Location, [LineOp, ColumnOp]), 1616 NewIndex is Index + 1, 1617 % Gets the type and precedence of the operator 1618 operator_type(Prio, Type, Op), 1619 (Location == infix -> 1620 member(Type, [xfx, xfy, yfx]) 1621 ; 1622 member(Type, [fx, fy]) 1623 ), 1624 % Checks if the operator is a '+' or '-' and the next term is a number 1625 (((Op == '-' ; Op == '+'), Type == fy, 1626 Tail = [Number|_], number(Number)) -> 1627 % This special treatment is needed in order to ignore the '+' and 1628 % '-' operators that indicates the sign of a number, because 1629 % positive and negative numbers must be atomic (non-compound) terms 1630 % according to the ISO Prolog standard 1631 highest_operator_aux(Tail, NewIndex, [HighOp, HighPrio, HighType, HighPos], 1632 FinalOpInfo) 1633 ; 1634 (Prio > HighPrio -> 1635 % A new highest operator was found 1636 highest_operator_aux(Tail, NewIndex, [Op, Prio, Type, Index], FinalOpInfo) 1637 ; 1638 (Prio =:= HighPrio -> 1639 % If an expression has several operators with the same priority, 1640 % priority clash will happen if the type of one of the operators 1641 % ends with "x" and the next one starts with "x" or "f" 1642 % Examples: - xfy xfy fx yfx yfx -> OK 1643 % - yfx yfx xfy xfy fx -> Priority clash (yfx xfy) 1644 % - xfx yfx fy xfx fx -> Priority clash (yfx fy) 1645 (Type == yfx -> 1646 % Left associative, change highest operator 1647 highest_operator_aux(Tail, NewIndex, [Op, Prio, Type, Index], FinalOpInfo) 1648 ; 1649 (((Type == xfy ; Type == xfx ; Type == fx ; Type == fy), 1650 (HighType == xfy ; HighType == fy)) -> 1651 % Right associative, don't change highest operator 1652 highest_operator_aux(Tail, NewIndex, [HighOp, HighPrio, HighType, HighPos], 1653 FinalOpInfo) 1654 ; 1655 % Operators can't be associated 1656 swritef(ErrorMessage, 'Operator priority clash caused by \'%w\'.', [Op]), 1657 throw(parse_error(ErrorMessage, [LineOp, ColumnOp])) 1658 )) 1659 ; 1660 % Keeps the current highest operator 1661 highest_operator_aux(Tail, NewIndex, [HighOp, HighPrio, HighType, HighPos], 1662 FinalOpInfo) 1663 )) 1664 ). 1665 1666 1667 1668%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 1669% Predicates related with errors and warnings 1670%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1687add_message(Message, Line, Column, Type) :- 1688 % Creates the text of the message 1689 bpl_filename(InputFile), 1690 upcase_atom(Type, UpperType), 1691 (InputFile == '' -> 1692 % InputFile should only be '' if a query is being parsed 1693 swritef(StringMessage, '%w: %w', 1694 [UpperType, Message]) 1695 ; 1696 swritef(StringMessage, '%w: %w:%w:%w: %w', 1697 [UpperType, InputFile, Line, Column, Message]) 1698 ), 1699 string_to_atom(StringMessage, TextMessage), 1700 % Updates the message list 1701 NewMessage = [InputFile, Line, Column, TextMessage, Type], 1702 add_message(NewMessage). 1703 1704add_message(Message, Line, Type) :- 1705 % Creates the text of the message 1706 bpl_filename(InputFile), 1707 upcase_atom(Type, UpperType), 1708 (InputFile == '' -> 1709 % InputFile should only be '' if a query is being parsed 1710 swritef(StringMessage, '%w: %w', 1711 [UpperType, Message]) 1712 ; 1713 swritef(StringMessage, '%w: %w:%w: %w', 1714 [UpperType, InputFile, Line, Message]) 1715 ), 1716 string_to_atom(StringMessage, TextMessage), 1717 % Updates the message list 1718 NewMessage = [InputFile, Line, 0, TextMessage, Type], 1719 add_message(NewMessage).
1730add_message_in_file(File, Message, Type) :-
1731 % Creates the text of the message
1732 upcase_atom(Type, UpperType),
1733 swritef(StringMessage, '%w: %w: %w', [UpperType, File, Message]),
1734 string_to_atom(StringMessage, TextMessage),
1735 % Updates the message list
1736 NewMessage = [File, 0, 0, TextMessage, Type],
1737 add_message(NewMessage).
1746add_message(Message) :- 1747 messages(CurrentMessages), 1748 retract(messages(CurrentMessages)), 1749 assert(messages([Message|CurrentMessages])). 1750 1751 1752 1753%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 1754% Predicates for processing goals and rules 1755%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1769add_degree_variables(Term, Result, DegreeVars) :-
1770 utilities:process_term(Term, Result,
1771 [parser:degree_variable_scanner],
1772 [parser:control_predicate_tester],
1773 [], DegreeVars).
1791add_block_constraints_variables(Term, Term, _BlockConstraintsVars) :- 1792 flags:get_bpl_flag(weak_unification('a1')), 1793 !. 1794 1795add_block_constraints_variables(Term, Result, BlockConstraintsVars) :- 1796 utilities:process_term(Term, Result, 1797 [parser:block_constraints_variables_scanner], 1798 [parser:control_predicate_tester], 1799 [], BlockConstraintsVars).
1814check_singleton(Term, Line) :-
1815 % Extracts and counts all the variables of Term
1816 utilities:process_term(Term, _Result,
1817 [parser:get_variables_scanner],
1818 [],
1819 [], AllVars),
1820 % Gets the name of the variables that have been found only once,
1821 % ignoring the singleton-marked variables (those starting with '_')
1822 findall(Var, (member([Var, Count], AllVars),
1823 atom_chars(Var, [First|_]), First \== '_',
1824 (Count =:= 1)), SingletonVars),
1825 (SingletonVars \== [] ->
1826 % One or more singleton variables were found
1827 swritef(MessageSV, 'Singleton variables: %w', [SingletonVars]),
1828 add_message(MessageSV, Line, warning)
1829 ;
1830 % No singleton variables were found
1831 true
1832 ),
1833 % Gets the name of the singleton-marked variables (those starting with
1834 % '_' that aren't '_' itself) that have been found more than once
1835 findall(Var, (member([Var, Count], AllVars), Var \== '_',
1836 atom_chars(Var, [First|_]), First == '_',
1837 (Count > 1)), SingletonMarkedVars),
1838 (SingletonMarkedVars \== [] ->
1839 % One or more singleton-marked variables were found several times
1840 swritef(MessageSMV, 'Singleton-marked variables appearing more than \c
1841 once: %w', [SingletonMarkedVars]),
1842 add_message(MessageSMV, Line, warning)
1843 ;
1844 % No repeated singleton-marked variables were found
1845 true
1846 ).
1859check_free_variables(Term, _Line, false) :- 1860 var(Term), 1861 !. 1862 1863check_free_variables(Term, _Line, true) :- 1864 (var(Term) ; atomic(Term)), 1865 !. 1866 1867check_free_variables(_Head :- Body, Line, IsGoal) :- 1868 % If Term is a clause, only its body is scanned 1869 !, 1870 check_free_variables(Body, Line, IsGoal). 1871 1872check_free_variables(Term, Line, IsGoal) :- 1873 !, 1874 % Extracts and counts all the variables of Term 1875 % (non-control compound terms are skipped) 1876 utilities:process_term(Term, _Result, 1877 [parser:get_variables_scanner], 1878 [parser:control_predicate_tester], 1879 [], AllVars), 1880 % If at least one variable is found, a warning is generated 1881 (AllVars \== [] -> 1882 findall(Var, member([Var, _Count], AllVars), VarNames), 1883 (IsGoal == true -> 1884 swritef(Message, 'Goals are not allowed to have free variables \c 1885 as subgoals: %w. Program may throw an \c 1886 exception at runtime. Please use call/1 \c 1887 instead.', [VarNames]) 1888 ; 1889 swritef(Message, 'Clauses are not allowed to have free variables \c 1890 as subclauses: %w. Program may throw an \c 1891 exception at runtime. Please use call/1 \c 1892 instead.', [VarNames]) 1893 ), 1894 add_message(Message, Line, warning) 1895 ; 1896 true 1897 ).
For example, given Term = 'pred(X, 1)
', this predicate will
return Result = 'prog_pred(X, 1, DegreeVar)
' (if program_prefix/1
contains 'prog') and OutData = [DegreeVar|InData].
If Term is a call to a predefined predicate (for example,
'append([1], X, [1, 2])
'), Result and OutData will be unified
with Term and InData, respectively.
1925degree_variable_scanner(Term, NewTerm, DegreeVars, NewDegreeVars) :- 1926 nonvar(Term), 1927 not(number(Term)), 1928 !, 1929 Term =.. [Functor|Args], 1930 (utilities:atom_is_variable(Functor) -> 1931 % Term represents a variable, so it can be ignored 1932 NewTerm = Term, 1933 NewDegreeVars = DegreeVars 1934 ; 1935 (Functor == 'eval_negation' -> 1936 % Gets the degree variable of the negation, which must be 1937 % the last argument of the eval_negation term 1938 NewTerm = Term, 1939 append(_, [NewDegreeVar], Args), 1940 % Updates the dynamic degree variable list 1941 NewDegreeVars = [NewDegreeVar|DegreeVars] 1942 ; 1943 ((utilities:builtin(Term) ; utilities:is_quoted(Functor, '\'') ; 1944 Functor == '^') -> 1945 % Term is a call to a predefined predicate or a quoted term, 1946 % so it can be ignored 1947 NewTerm = Term, 1948 NewDegreeVars = DegreeVars 1949 ; 1950 % Adds the degree variable to the scanned term 1951 %var(NewDegreeVar), 1952 append(Args, [NewDegreeVar], NewArgs), 1953 program_prefix(ProgramName), 1954 concat_atom([ProgramName, '_', Functor], NewFunctor), 1955 NewTerm =.. [NewFunctor|NewArgs], 1956 % Updates the dynamic degree variable list 1957 NewDegreeVars = [NewDegreeVar|DegreeVars] 1958 )) 1959 ). 1960 1961degree_variable_scanner(Term, Term, DegreeVars, DegreeVars). 1962 % Term can be ignored because it's a variable or a number
For example, given:
Term = 'prog_pred(X, 1, DegreeVar)
', this
predicate will return
Result = 'prog_pred(X, 1, Cin, Cout, DegreeVar)
', and
OutData = InData ++ [Cin, Cout].
If Term is a call to a predefined predicate (for example,
'append([1], X, [1, 2])
'), Result and OutData will be unified
with Term and InData, respectively.
1991block_constraints_variables_scanner(Term, NewTerm, InData, OutData) :- 1992 nonvar(Term), 1993 not(number(Term)), 1994 !, 1995 Term =.. [Functor|Args], 1996 (utilities:atom_is_variable(Functor) -> 1997 % Term represents a variable, so it can be ignored 1998 NewTerm = Term, 1999 OutData = InData 2000 ; 2001 (Functor == 'eval_negation' -> 2002 % Gets the block constraints variables list of the negation, 2003 % which must be the last but two argument of the eval_negation term :: WARNING: TODO 2004 NewTerm = Term, 2005 append(_, [Ctrs, _, _DegreeVar], Args), 2006 % Updates the dynamic degree variable list 2007 append(InData, Ctrs, OutData) 2008 ; 2009 ((utilities:builtin(Term) ; utilities:is_quoted(Functor, '\'') ; 2010 Functor == '^') -> 2011 % Term is a call to a predefined predicate or a quoted term, 2012 % so it can be ignored 2013 NewTerm = Term, 2014 OutData = InData 2015 ; 2016 % Adds the block constraints variables to the scanned term 2017 % var(Cin), 2018 % var(Cout), 2019 Ctrs = [Cin, _Cout], 2020 append(ArgsWithoutDegreeVar, [NewDegreeVar], Args), 2021 append(ArgsWithoutDegreeVar, Ctrs, NewArgsWithoutDegreeVar), 2022 append(NewArgsWithoutDegreeVar, [NewDegreeVar], NewArgs), 2023 NewTerm =.. [Functor|NewArgs], 2024 % Updates the block constraints variables list 2025 append(InData, Ctrs, OutData), 2026 % Links the last block constraints store in InData with Cin 2027 (InData == [] -> 2028 true % Nothing to link with 2029 ; 2030 append(_,[Cin],InData) 2031 ) 2032 )) 2033 ). 2034 2035block_constraints_variables_scanner(Term, Term, InData, InData). 2036 % Term can be ignored because it's a variable or a number
2051get_variables_scanner(Term, Term, CurrentVars, NewVars) :- 2052 atom(Term), 2053 % Term is an atom; if its first char is uppercase, then it represents 2054 % a variable (variables starting with an underscore character are ignored) 2055 !, 2056 (utilities:atom_is_variable(Term) -> 2057 % Term represents a variable, so it must be added to 2058 % the list of current variables 2059 (member([Term, Count], CurrentVars) -> 2060 % This variable has already been found before 2061 delete(CurrentVars, [Term, Count], CurrentVarsWithoutTerm), 2062 NewCount is Count + 1, 2063 NewVars = [[Term, NewCount]|CurrentVarsWithoutTerm] 2064 ; 2065 % This is the first ocurrence of this variable 2066 NewVars = [[Term, 1]|CurrentVars] 2067 ) 2068 ; 2069 % Term doesn't represent a variable 2070 NewVars = CurrentVars 2071 ). 2072 2073get_variables_scanner(Term, Term, Vars, Vars). 2074 % Term can be ignored because it isn't an atom
2086control_predicate_tester(Term) :- 2087 compound(Term), 2088 !, 2089 functor(Term, Functor, _Arity), 2090 (Functor == ',' ; Functor == ';' ; Functor == '->' ; Functor == '*->'). 2091 2092control_predicate_tester(_Term). 2093 % Tester always succeed for non-compound terms 2094 2095 2096 2097%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 2098% Miscellaneous predicates 2099%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2108declare_custom_operator(_, _, []). 2109 2110declare_custom_operator(Precedence, Type, [Name|MoreOps]) :- 2111 custom_operators(CurrentOpList), 2112 retract(custom_operators(CurrentOpList)), 2113 assert(custom_operators([[Precedence, Type, Name]|CurrentOpList])), 2114 declare_custom_operator(Precedence, Type, MoreOps).
2123operator_type(Precedence, Type, Name) :- 2124 % Checks if the operator is a predefined one 2125 current_op(Precedence, Type, Name), 2126 Name\=='.'. % SWI-Prolog 7.x add the dot as an infix operator for dicts. 2127 2128operator_type(Precedence, Type, Name) :- 2129 % Checks if the operator is a custom operator declared 2130 % by the user with the op/3 directive 2131 custom_operators(CustomOpList), 2132 member([Precedence, Type, Name], CustomOpList).
For example, given Term = (X ^ write(X)
), this predicate will
return ResultTerm = (X ^ bpl_call(write(X))
.
2144add_call_after_bindings(Var ^ Term, Var ^ ResultTerm) :- 2145 add_call_after_bindings(Term, ResultTerm). 2146 2147add_call_after_bindings(Term, bpl_call(Term)).
pred(A, B, C)
', this predicate will return BoundTerm =
'A ^ B ^ pred(A, B, C)
'.2159bind_term([], Term, Term). 2160 2161bind_term([Var|MoreVars], Term, BoundTerm) :- 2162 BoundTerm = Var ^ ContTerm, 2163 bind_term(MoreVars, Term, ContTerm).
2171reset_parser :- 2172 custom_operators(OldOperators), 2173 retract(custom_operators(OldOperators)), 2174 assert(custom_operators([])), 2175 messages(OldMessages), 2176 retract(messages(OldMessages)), 2177 assert(messages([])), 2178 linguistic_terms(OldLingTerms), 2179 retract(linguistic_terms(OldLingTerms)), 2180 assert(linguistic_terms([])). 2181 2182 2183 2184%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 2185% Constant predicates 2186%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2198higher_order_predicate(assert, [atom]). 2199higher_order_predicate(retract, [atom]). 2200higher_order_predicate(call, [goal]). 2201higher_order_predicate(once, [goal]). 2202higher_order_predicate(ignore, [goal]). 2203higher_order_predicate(time, [goal]). 2204higher_order_predicate(apply, [nongoal, nongoal]). 2205higher_order_predicate(maplist, [nongoal, nongoal]). 2206higher_order_predicate(forall, [goal, goal]). 2207higher_order_predicate(findall, [nongoal, goal, nongoal]). 2208higher_order_predicate(bagof, [nongoal, goal, nongoal]). 2209higher_order_predicate(setof, [nongoal, goal, nongoal]). 2210higher_order_predicate(catch, [goal, nongoal, goal]). 2211 2212 2213 2214%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 2215% Dynamic predicates 2216%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2227:- dynamic program_prefix/1. 2228 2229program_prefix('none').
2238:- dynamic bpl_filename/1. 2239 2240bpl_filename('').
2252:- dynamic messages/1. 2253 2254messages([]).
2265:- dynamic custom_operators/1. 2266 2267custom_operators([]).
2281:- dynamic linguistic_terms/1. 2282 2283linguistic_terms([])