75
76:- module(le_input,
77 [document/3, text_to_logic/2,
78 predicate_decl/4, showErrors/2,
79 op(1000,xfy,user:and), 80 op(800,fx,user:resolve), 81 op(800,fx,user:answer), 82 op(800,fx,user:répondre), 83 op(850,xfx,user:with), 84 op(850,xfx,user:avec), 85 op(800,fx,user:risposta), 86 op(850,xfx,user:con), 87 op(800,fx,user:responde), 88 89 op(850,xfx,user:of), 90 91 92 op(950, xfx, ::), 93 op(1200, fx, #),
94 op(1150, fx, pred),
95 op(1150, fx, show),
96 op(1150, fx, abducible),
97 dictionary/3, meta_dictionary/3, dict/3, meta_dict/3,
98 parsed/0, source_lang/1, including/0, 99 this_capsule/1, unpack_tokens/2, clean_comments/2,
100 query_/2, extract_constant/4, spaces/3, name_as_atom/2, process_types_or_names/4,
101 matches_name/4, matches_type/4, delete_underscore/2, add_determiner/2, proper_det/2,
102 portray_clause_ind/1, order_templates/2, process_types_dict/2,
103 assertall/1,asserted/1,
104 update_file/3, myDeclaredModule/1, conditions/6, op_stop/1
105 ]). 106
107:- multifile sandbox:safe_primitive/1. 108
109:- use_module('./tokenize/prolog/tokenize.pl'). 110
111:- if(current_module(swish)).
112:- use_module('le_swish.pl'). 113:- else. 114:- use_module('le_local.pl'). 115:- endif. 116
117:- if(exists_source(library(r/r_call))). 118:- use_module(library(r/r_call)). 119:- endif. 120:- use_module('reasoner.pl'). 121:- use_module(library(prolog_stack)). 122:- table addExp//2, mulExp//2. 123:- thread_local text_size/1, error_notice/4, dict/3, meta_dict/3, example/2, local_dict/3, local_meta_dict/3,
124 last_nl_parsed/1, kbname/1, happens/2, initiates/3, terminates/3, is_type/1, is_/2, is_a/2,
125 predicates/1, events/1, fluents/1, metapredicates/1, parsed/0, source_lang/1, including/0. 126:- discontiguous statement/3, declaration/4, _:example/2, _:query/2, _:is_/2.
127
131text_to_logic(String_, Translation) :-
132 133 ((sub_atom(String_,_,1,0,NL), memberchk(NL,['\n','\r']) ) -> String=String_ ; atom_concat(String_,'\n',String)),
134 tokenize(String, Tokens, [cased(true), spaces(true), numbers(true)]),
135 retractall(last_nl_parsed(_)), asserta(last_nl_parsed(1)), 136 unpack_tokens(Tokens, UTokens),
137 clean_comments(UTokens, CTokens), !,
138 139 phrase(document(Translation), CTokens).
140 141 142 143 144 145 146
148document(Translation, In, Rest) :-
149 (parsed -> retractall(parsed); true),
150 (including -> retract(including); true),
151 (source_lang(_L) -> retractall(source_lang(_)) ; true),
152 phrase(header(Settings), In, AfterHeader), !, 153 phrase(content(Content), AfterHeader, Rest), 154 append(Settings, Content, Translation), !,
155 156 assertz(parsed).
157
(Settings, In, Next) :-
161 length(In, TextSize), 162 phrase(settings(DictEntries, Settings_), In, Next),
163 fix_settings(Settings_, Settings2),
164 RulesforErrors = [(text_size(TextSize))|Settings2], 165 included_files(Settings2, RestoredDictEntries, CollectedRules),
166 append(Settings2, CollectedRules, Settings),
167 append(DictEntries, RestoredDictEntries, AllDictEntries),
168 order_templates(AllDictEntries, OrderedEntries),
169 process_types_dict(OrderedEntries, Types),
170 171 append(OrderedEntries, RulesforErrors, SomeRules),
172 append(SomeRules, Types, MRules),
173 174 assertall(MRules), !. 175header(_, Rest, _) :-
176 asserterror('LE error in the header ', Rest),
177 fail.
178
179fix_settings(Settings_, Settings3) :-
180 181 ( member(target(_), Settings_) -> Settings1 = Settings_ ; Settings1 = [target(taxlog)|Settings_] ), !, 182 183 184 findall(Pred, filtered_dictionary(Pred), PH),
185 filter_repeats(PH, PredefHeaders),
186 187 ( member(predicates(Templates), Settings1) ->
188 ( append(Previous, [predicates(Templates)|Rest], Settings1), 189 append(Templates, PredefHeaders, AllTemplates), append(Previous, Rest, IncompleteSettings),
190 Settings2 = [predicates(AllTemplates)|IncompleteSettings] )
191 ; Settings2 = [predicates(PredefHeaders)|Settings1]
192 ),
193 Settings3 = [query(null, true), example(null, []), abducible(true,true)|Settings2]. 194
195filter_repeats([], []) :- !.
196filter_repeats([H|R], RR) :- member(H,R), !, filter_repeats(R, RR).
197filter_repeats([H|R], [H|RR]) :- filter_repeats(R, RR).
198
199fix_dictionary(Dict, Dict).
200
201included_files(Settings2, RestoredDictEntries, CollectedRules) :-
202 member(in_files(ModuleNames), Settings2), 203 204 assertz(including), !, 205 load_all_files(ModuleNames, RestoredDictEntries, CollectedRules).
206 207included_files(_, [], []).
208
212load_all_files([], [], []).
213load_all_files([Name|R], AllDictEntries, AllRules) :-
214 215 split_module_name(Name, File, URL),
216 217 concat(File, "-prolog", Part1), concat(Part1, ".pl", Filename),
218 (URL\=''->atomic_list_concat([File,'-prolog', '+', URL], NewName); atomic_list_concat([File,'-prolog'], NewName)),
219 220 load_file_module(Filename, NewName, true), !,
221 222 (NewName:local_dict(_,_,_) -> findall(dict(A,B,C), NewName:local_dict(A,B,C), ListDict) ; ListDict = []),
223 (NewName:local_meta_dict(_,_,_) -> findall(meta_dict(A,B,C), NewName:local_meta_dict(A,B,C), ListMetaDict); ListMetaDict = []),
224 append(ListDict, ListMetaDict, DictEntries),
225 226 227 findall(if(H,B), (member(dict(E, _,_), DictEntries), E\=[], H=..E, clause(NewName:H, B)), Rules),
228 findall(Pred, (member(dict(E,_,_), ListDict), E\=[], Pred=..E), ListOfPred),
229 findall(MPred, (member(dict(ME,_,_), ListMetaDict), ME\=[], MPred=..ME), ListOfMPred),
230 append([predicates(ListOfPred), metapredicates(ListOfMPred)], Rules, TheseRules), 231 232 233 234 235 print_message(informational, "Loaded ~w"-[Filename]),
236 load_all_files(R, RDict, NextRules),
237 append(RDict, DictEntries, AllDictEntries),
238 append(TheseRules, NextRules, AllRules).
239load_all_files([Filename|_], [], []) :-
240 print_message(informational, "Failed to load file ~w"-[Filename]), fail.
241
243process_types_dict(Dictionary, Type_entries) :-
244 findall(Word,
245 ( (member(dict([_|GoalElements], Types, _), Dictionary);
246 member(meta_dict([_|GoalElements], Types, _), Dictionary)),
247 member((_Name-Type), Types),
248 process_types_or_names([Type], GoalElements, Types, TypeWords),
249 concat_atom(TypeWords, '_', Word), Word\=''), Templates),
250 (Templates\=[] -> setof(is_type(Ty), member(Ty, Templates), Type_entries) ; Type_entries = []).
251
253process_types_or_names([], _, _, []) :- !.
254:- if(exists_source(library(r/r_call))). 255process_types_or_names([Word|RestWords], Elements, Types, [the, chart|RestPrintWords] ) :-
256 nonvar(Word), Word = plot_command(RExecuteCommand),
257 copy_term(RExecuteCommand,RExecuteCommandForDisplay),
258 RExecuteCommandForDisplay, 259 <- png("image.png"), RExecuteCommand, 260 <- graphics.off(), r_swish:r_download("image.png"), 261 process_types_or_names(RestWords, Elements, Types, RestPrintWords).
262:- endif. 263process_types_or_names([Word|RestWords], Elements, Types, PrintExpression ) :-
264 atom(Word), concat_atom(WordList, '_', Word), !,
265 process_types_or_names(RestWords, Elements, Types, RestPrintWords),
266 append(WordList, RestPrintWords, PrintExpression).
267process_types_or_names([Word|RestWords], Elements, Types, PrintExpression ) :-
268 var(Word), matches_name(Word, Elements, Types, Name), !,
269 process_types_or_names(RestWords, Elements, Types, RestPrintWords),
270 tokenize_atom(Name, NameWords), delete_underscore(NameWords, CNameWords),
271 add_determiner(CNameWords, PrintName), append(['*'|PrintName], ['*'|RestPrintWords], PrintExpression).
272process_types_or_names([Word|RestWords], Elements, Types, [PrintWord|RestPrintWords] ) :-
273 matches_type(Word, Elements, Types, date),
274 ((nonvar(Word), number(Word)) -> unparse_time(Word, PrintWord); PrintWord = Word), !,
275 process_types_or_names(RestWords, Elements, Types, RestPrintWords).
276process_types_or_names([Word|RestWords], Elements, Types, [PrintWord|RestPrintWords] ) :-
277 matches_type(Word, Elements, Types, day),
278 ((nonvar(Word), number(Word)) -> unparse_time(Word, PrintWord); PrintWord = Word), !,
279 process_types_or_names(RestWords, Elements, Types, RestPrintWords).
280process_types_or_names([Word|RestWords], Elements, Types, Output) :-
281 compound(Word),
282 translate_goal_into_LE(Word, PrintWord), !, 283 process_types_or_names(RestWords, Elements, Types, RestPrintWords),
284 append(PrintWord, RestPrintWords, Output).
285process_types_or_names([Word|RestWords], Elements, Types, [Word|RestPrintWords] ) :-
286 process_types_or_names(RestWords, Elements, Types, RestPrintWords).
287
288
291order_templates(NonOrdered, Ordered) :-
292 predsort(compare_templates, NonOrdered, Ordered).
293
294compare_templates(<, meta_dict(_,_,_), dict(_,_,_)).
295
296compare_templates(=, dict(_,_,T1), dict(_,_,T2)) :- T1 =@= T2.
297compare_templates(<, dict(_,_,T1), dict(_,_,T2)) :- length(T1, N1), length(T2, N2), N1>N2.
298compare_templates(<, dict(_,_,T1), dict(_,_,T2)) :- length(T1, N), length(T2, N), template_before(T1, T2).
299
300compare_templates(>, Dict1, Dict2) :- not(compare_templates(=, Dict1, Dict2)), not(compare_templates(<, Dict1, Dict2)).
301
302compare_templates(=, meta_dict(_,_,T1), meta_dict(_,_,T2)) :- T1 =@= T2.
303compare_templates(<, meta_dict(_,_,T1), meta_dict(_,_,T2)) :- length(T1, N1), length(T2, N2), N1>N2.
304compare_templates(<, meta_dict(_,_,T1), meta_dict(_,_,T2)) :- length(T1, N), length(T2, N), template_before(T1, T2).
305
306template_before([H1], [H2]) :- H1 =@= H2.
307template_before([H1|_R1], [H2|_R2]) :- nonvar(H1), var(H2).
308template_before([H1|_R1], [H2|_R2]) :- H1 @> H2.
309template_before([H1|R1], [H2|R2]) :- H1=@=H2, template_before(R1, R2).
310
311
314settings(AllR, AllS) -->
315 spaces_or_newlines(_), declaration(Rules,Setting), settings(RRules, RS),
316 {append(Setting, RS, AllS), append(Rules, RRules, AllR)}, !.
317settings([], [], Stay, Stay) :- !,
318 ( phrase(rules_previous(_), Stay, _) ;
319 phrase(ontology_, Stay, _) ;
320 phrase(scenario_, Stay, _) ;
321 phrase(query_, Stay, _) ;
322 phrase(the_plots_are_, Stay, _) ).
323 324settings(_, _, Rest, _) :-
325 asserterror('LE error in the declarations on or before ', Rest),
326 fail.
327settings([], [], Stay, Stay).
328
331content(T) --> 332 spaces_or_newlines(_), rules_previous(Kbname), 333 kbase_content(S), 334 content(R), {append([kbname(Kbname)|S], R, T)}, !.
335content(T) --> 336 spaces_or_newlines(_), ontology_content(S), 337 content(R), {append(S, R, T)}, !.
339content(T) --> 340 spaces_or_newlines(_), annexes_content(S), 341 content(R), {append(S, R, T)}, !.
342content(T) --> 343 spaces_or_newlines(_), scenario_content(S), 344 content(R), {append(S, R, T)}, !.
345content(T) --> 346 spaces_or_newlines(_), query_content(S), content(R), {append(S, R, T)}, !.
347content([]) --> spaces_or_newlines(_).
348content(_, Rest, _) :-
349 asserterror('LE error in the content ', Rest),
350 fail.
351
353kbase_content(T) -->
354 spaces_or_newlines(_), statement(S), kbase_content(R),
355 {append(S, R, T)}, !.
356kbase_content([]) -->
357 spaces_or_newlines(_), [].
358kbase_content(_, Rest, _) :-
359 asserterror('LE error in a knowledge base ', Rest),
360 fail.
361
364declaration([], [target(Language)]) --> 365 spaces(_), [the], spaces(_), [target], spaces(_), [language], spaces(_), [is], spaces(_), colon_or_not_,
366 spaces(_), [Language], spaces(_), period, !, {assertz(source_lang(en))}.
368declaration([], [target(Language)]) --> 369 spaces(_), [la], spaces(_), [langue], spaces(_), [cible], spaces(_), [est], spaces(_), colon_or_not_,
370 spaces(_), [Language], spaces(_), period, !, {assertz(source_lang(fr))}.
372declaration([], [target(Language)]) --> 373 spaces(_), [il], spaces(_), [linguaggio], spaces(_), [destinazione], spaces(_), [è], spaces(_), colon_or_not_,
374 spaces(_), [Language], spaces(_), period, !, {assertz(source_lang(it))}.
376declaration([], [target(Language)]) --> 377 spaces(_), [el], spaces(_), [lenguaje], spaces(_), [objetivo], spaces(_), [es], spaces(_), colon_or_not_,
378 spaces(_), [Language], spaces(_), period, !, {assertz(source_lang(es))}.
379
381declaration(Rules, [metapredicates(MetaTemplates)]) -->
382 meta_predicate_previous, list_of_meta_predicates_decl(Rules, MetaTemplates), !.
384declaration(Rules, [predicates(Templates)]) -->
385 predicate_previous, list_of_predicates_decl(Rules, Templates), !.
387declaration(Rules, [events(EventTypes)]) -->
388 event_predicate_previous, list_of_predicates_decl(Rules, EventTypes), !.
390declaration(Rules, [fluents(Fluents)]) -->
391 fluent_predicate_previous, list_of_predicates_decl(Rules, Fluents), !.
393declaration([kbname(KBName)], [in_files(Files)]) -->
394 files_to_include_previous(KBName), list_of_files(Files), !.
396declaration(_, _, Rest, _) :-
397 asserterror('LE error in a declaration on or before ', Rest),
398 fail.
399
400colon_or_not_ --> [':'], spaces(_).
401colon_or_not_ --> [].
402
403meta_predicate_previous -->
404 spaces(_), [the], spaces(_), [metapredicates], spaces(_), [are], spaces(_), [':'], spaces_or_newlines(_).
405meta_predicate_previous -->
406 spaces(_), [the], spaces(_), [meta], spaces(_), [predicates], spaces(_), [are], spaces(_), [':'], spaces_or_newlines(_).
407meta_predicate_previous -->
408 spaces(_), [the], spaces(_), [meta], spaces(_), ['-'], spaces(_), [predicates], spaces(_), [are], spaces(_), [':'], spaces_or_newlines(_).
410meta_predicate_previous -->
411 spaces(_), [les], spaces(_), ['méta'], spaces(_), ['modèles'], spaces(_), [sont], spaces(_), [':'], spaces_or_newlines(_).
413meta_predicate_previous -->
414 spaces(_), [i], spaces(_), [meta], spaces(_), [modelli], spaces(_), [sono], spaces(_), [':'], spaces_or_newlines(_).
416meta_predicate_previous -->
417 spaces(_), [los], spaces(_), [meta], spaces(_), [predicados], spaces(_), [son], spaces(_), [':'], spaces_or_newlines(_).
418
419predicate_previous -->
420 spaces(_), [the], spaces(_), [predicates], spaces(_), [are], spaces(_), [':'], spaces_or_newlines(_).
421predicate_previous -->
422 spaces(_), [the], spaces(_), [templates], spaces(_), [are], spaces(_), [':'], spaces_or_newlines(_).
423predicate_previous -->
424 spaces(_), [the], spaces(_), [timeless], spaces(_), [predicates], spaces(_), [are], spaces(_), [':'], spaces_or_newlines(_).
426predicate_previous -->
427 spaces(_), [les], spaces(_), ['modèles'], spaces(_), [sont], spaces(_), [':'], spaces_or_newlines(_).
429predicate_previous -->
430 spaces(_), [i], spaces(_), [modelli], spaces(_), [sono], spaces(_), [':'], spaces_or_newlines(_).
432predicate_previous -->
433 spaces(_), [los], spaces(_), [predicados], spaces(_), [son], spaces(_), [':'], spaces_or_newlines(_).
434
435event_predicate_previous -->
436 spaces(_), [the], spaces(_), [event], spaces(_), [predicates], spaces(_), [are], spaces(_), [':'], spaces_or_newlines(_).
437
438fluent_predicate_previous -->
439 spaces(_), [the], spaces(_), [fluents], spaces(_), [are], spaces(_), [':'], spaces_or_newlines(_).
440fluent_predicate_previous -->
441 spaces(_), [the], spaces(_), [time], ['-'], [varying], spaces(_), [predicates], spaces(_), [are], spaces(_), [':'], spaces_or_newlines(_).
442
443the_plots_are_ --> spaces(_), [the], spaces(_), [plots], spaces(_), [are], spaces(_), [':'], spaces_or_newlines(_).
444
445files_to_include_previous(KBName) -->
446 spaces_or_newlines(_), [the], spaces(_), ['knowledge'], spaces(_), [base], extract_constant([includes], NameWords), [includes],
447 spaces(_), [these], spaces(_), [files], spaces(_), [':'], !, spaces_or_newlines(_), {name_as_atom(NameWords, KBName)}.
448
450list_of_predicates_decl([], []) --> spaces_or_newlines(_), next_section, !.
451list_of_predicates_decl([Ru|Rin], [F|Rout]) --> spaces_or_newlines(_), predicate_decl(Ru,F), comma_or_period, list_of_predicates_decl(Rin, Rout), !.
452list_of_predicates_decl(_, _, Rest, _) :-
453 asserterror('LE error found in a template declaration ', Rest),
454 fail.
455
457list_of_meta_predicates_decl([], []) --> spaces_or_newlines(_), next_section, !.
458list_of_meta_predicates_decl([Ru|Rin], [F|Rout]) -->
459 spaces_or_newlines(_), meta_predicate_decl(Ru,F), comma_or_period, list_of_meta_predicates_decl(Rin, Rout).
460list_of_meta_predicates_decl(_, _, Rest, _) :-
461 asserterror('LE error found in the declaration of a meta template ', Rest),
462 fail.
463
465list_of_files([]) --> spaces_or_newlines(_), next_section, !.
466list_of_files([Filename|Rout]) --> spaces_or_newlines(_), extract_string([Filename]),
467 {print_message(informational, "list_of_files: filename ~w "-[Filename])},
468 list_of_files(Rout), !.
469 470list_of_files(_, Rest, _) :-
471 asserterror('LE error found in a file to include ', Rest),
472 fail.
473
476next_section(StopHere, StopHere) :-
477 phrase(meta_predicate_previous, StopHere, _), !. 478
479next_section(StopHere, StopHere) :-
480 phrase(predicate_previous, StopHere, _), !. 481
482next_section(StopHere, StopHere) :-
483 phrase(event_predicate_previous, StopHere, _), !. 484
485next_section(StopHere, StopHere) :-
486 phrase(fluent_predicate_previous, StopHere, _), !. 487
488next_section(StopHere, StopHere) :-
489 phrase(files_to_include_previous(_), StopHere, _), !.
490
491next_section(StopHere, StopHere) :-
492 phrase(ontology_, StopHere, _), !.
493
494next_section(StopHere, StopHere) :-
495 phrase(rules_previous(_), StopHere, _), !. 496
497next_section(StopHere, StopHere) :-
498 phrase(scenario_, StopHere, _), !. 499
500next_section(StopHere, StopHere) :-
501 phrase(query_, StopHere, _). 502
503next_section(StopHere, StopHere) :-
504 phrase(the_plots_are_, StopHere, _), !.
505
507predicate_decl(dict([Predicate|Arguments],TypesAndNames, Template), Relation) -->
508 spaces(_), template_decl(RawTemplate),
509 {build_template(RawTemplate, Predicate, Arguments, TypesAndNames, Template),
510 Relation =.. [Predicate|Arguments]}, !.
514predicate_decl(_, _, Rest, _) :-
515 asserterror('LE error found in a declaration ', Rest),
516 fail.
517
519meta_predicate_decl(meta_dict([Predicate|Arguments],TypesAndNames, Template), Relation) -->
520 spaces(_), template_decl(RawTemplate),
521 {build_template(RawTemplate, Predicate, Arguments, TypesAndNames, Template),
522 Relation =.. [Predicate|Arguments]}.
523meta_predicate_decl(_, _, Rest, _) :-
524 asserterror('LE error found in a meta template declaration ', Rest),
525 fail.
526
527rules_previous(default) -->
528 spaces_or_newlines(_), [the], spaces(_), [rules], spaces(_), [are], spaces(_), [':'], spaces_or_newlines(_), !.
529rules_previous(KBName) -->
530 spaces_or_newlines(_), [the], spaces(_), ['knowledge'], spaces(_), [base], extract_constant([includes], NameWords), [includes], spaces(_), [':'], !, spaces_or_newlines(_),
531 {name_as_atom(NameWords, KBName)}.
532rules_previous(default) --> 533 spaces_or_newlines(_), [the], spaces(_), ['knowledge'], spaces(_), [base], spaces(_), [includes], spaces(_), [':'], spaces_or_newlines(_).
535rules_previous(KBName) -->
536 spaces_or_newlines(_), [la], spaces(_), [base], spaces(_), [di], spaces(_), [conoscenza], spaces(_), extract_constant([include], NameWords), [include], spaces(_), [':'], !, spaces_or_newlines(_),
537 {name_as_atom(NameWords, KBName)}.
539rules_previous(KBName) -->
540 spaces_or_newlines(_), [la], spaces(_), [base], spaces(_), [de], spaces(_), [connaissances], spaces(_), [dont], spaces(_), [le], spaces(_), [nom], spaces(_), [est], extract_constant([comprend], NameWords), [comprend], spaces(_), [':'], !, spaces_or_newlines(_),
541 {name_as_atom(NameWords, KBName)}.
543rules_previous(KBName) -->
544 spaces_or_newlines(_), [la], spaces(_), [base], spaces(_), [de], spaces(_), [conocimiento], extract_constant([incluye], NameWords), [incluye], spaces(_), [':'], !, spaces_or_newlines(_),
545 {name_as_atom(NameWords, KBName)}.
546
549scenario_content(Scenario) --> 550 scenario_, extract_constant([is, es, est, è], NameWords), is_colon_, newline, 551 552 spaces(_), assumptions_(Assumptions), !, 553 554 {name_as_atom(NameWords, Name), Scenario = [example( Name, [scenario(Assumptions, true)])]}.
555
556scenario_content(_, Rest, _) :-
557 asserterror('LE error found around this scenario expression: ', Rest), fail.
558
561ontology_content(Ontology) --> 562 ontology_previous(_Name), kbase_content(Ontology), !.
563 564
565ontology_content(_, Rest, _) :-
566 asserterror('LE error found around this ontology expression: ', Rest), fail.
567
569ontology_previous(default) -->
570 spaces_or_newlines(_), ss_([the, ontology, is, :]), spaces_or_newlines(_).
571ontology_previous(KBName) -->
572 ontology_, [named], spaces(_), [','], extract_constant([',', is, es, est, 'è'], NameWords), [','], spaces(_), is_colon_, spaces_or_newlines(_), 573 {name_as_atom(NameWords, KBName)}.
574
577annexes_content(Annexes) --> 578 annexes_previous(_Name), kbase_content(Annexes), !.
579 580
581annexes_content(_, Rest, _) :-
582 asserterror('LE error found around this annexes expression: ', Rest), fail.
583
585annexes_previous(default) -->
586 spaces_or_newlines(_), ss_([the, annexes, to, the, contract, are, :]), spaces_or_newlines(_).
587
588
592query_content(Query) -->
593 query_, extract_constant([is, es, est, è], NameWords), is_colon_, spaces_or_newlines(_),
594 query_header(Ind0, Map1),
595 conditions(Ind0, Map1, _, Conds), !, period, 596 {name_as_atom(NameWords, Name), Query = [query(Name, Conds)]}.
597
598query_content(_, Rest, _) :-
599 asserterror('LE error found around this expression: ', Rest), fail.
600
601plot_content(PlotList) -->
602 the_plots_are_, plot_statement_list(PlotList).
603
604plot_statement_list([Statement | StatementRest]) -->
605 plot_statement(Statement), plot_statement_list(StatementRest).
606plot_statement_list([]) --> [].
607
608plot_statement(Statement) --> spaces_or_newlines(_), currentLine(L),
609 literal_([], Map1, Head), plot_body(Body, Map1, _), period,
610 {Statement = [if(L, Head, Body)]}.
611
612concat_body_with_comma([A | B], (A, BB)) :-
613 concat_body_with_comma(B, BB).
614concat_body_with_comma([A], A).
615
616plot_body_prefix -->
617 newline, spaces(_), if_, !.
618plot_body_prefix -->
619 if_, newline_or_nothing, spaces(_).
620
621plot_body(Body, Map1, MapN) -->
622 plot_body_prefix, !,
623 plot_body_clause_list(ChartVar, 0, UsedVarList, PlotCommandList, CondList, Map1, MapN),
624 {
625 626 atomics_to_string(PlotCommandList, '\n', PlotCommandListStr),
627 pad_name_var(_Names, UsedVarList, ParamList, MapN),
628 629 630 ChartAssignCommand = (ChartVar = plot_command(r_execute(ParamList,PlotCommandListStr,_))),
631 append(CondList, [ChartAssignCommand], TermList),
632 concat_body_with_comma(TermList, Body)
633 634 }.
635
636plot_body_clause_list(ChartVar, DataFrameCount, UsedVarList, PlotCommandList, CondList, Map1, MapN) -->
637 plot_body_clause(ChartVar, UsedVarHead, PlotCommandHead, CondHead, DataFrameCount, Map1, Map2),
638 {NextCount is DataFrameCount + 1},
639 newline, spaces(_), operator(_Op), spaces(_), plot_body_clause_list(ChartVar, NextCount, UsedVarTail, PlotCommandTail, CondTail, Map2, MapN),
640 {
641 append(UsedVarHead, UsedVarTail, UsedVarList),
642 append(PlotCommandHead, PlotCommandTail, PlotCommandList),
643 append(CondHead, CondTail, CondList)
644 }.
645
646plot_body_clause_list(ChartVar, DataFrameCount, UsedVarList, PlotCommandList, CondList, Map1, MapN) --> plot_body_clause(ChartVar, UsedVarList, PlotCommandList, CondList, DataFrameCount, Map1, MapN).
647
650plot_body_clause(_, [], [], [Cond], _Count, Map1, MapN) --> condition(Cond, _Ind, Map1, MapN).
651plot_body_clause(ChartVar, UsedVarList, [PlotCommand], [], _Count, Map1, MapN) --> chart(ChartVar, UsedVarList, PlotCommand, Map1, MapN).
652plot_body_clause(_, [], [PlotCommand], [], _Count, Map1, MapN) --> straightLine(PlotCommand, Map1, MapN).
653plot_body_clause(_, [], [PlotCommand], [], _Count, Map1, MapN) --> legend(PlotCommand, Map1, MapN).
654plot_body_clause(_, [], [PlotCommand], [DataFrameCommand], Count, Map1, MapN) --> line(DataFrameCommand, PlotCommand, Count, Map1, MapN).
655plot_body_clause(_, [], [PlotCommand], [DataFrameCommand], Count, Map1, MapN) --> points(DataFrameCommand, PlotCommand, Count, Map1, MapN).
656plot_body_clause(_, [], [PlotCommand], [DataFrameCommand], Count, Map1, MapN) --> verticalLines(DataFrameCommand, PlotCommand, Count, Map1, MapN).
657
658
659chart(ChartVar, UsedVarList, Command, Map1, MapN) -->
660 variable_invocation([has], _Name, ChartVar, Map1, MapN), spaces(_),
661 [has], spaces(_), chart_with_list(UsedVarList, Arguments, Map1, MapN), !,
662 {
663 664 atomic_list_concat(Arguments, ',', Atom),
665 format(string(Command), 'plot(NULL, ~w)', [Atom])
666 }.
667
668legend(Command, Map1, MapN) -->
669 variable_invocation([displays], _Name, _Var, Map1, MapN), spaces(_), displays_, legend_, [at], spaces(_), [Position], spaces(_), legend_with_list(Arguments), !,
670 {
671 atom_string(Position, PositionAtom),
672 atomic_list_concat(Arguments, ',', Atom),
673 format(string(Command), 'legend("~w",~w)', [PositionAtom, Atom])
674 }.
675
676straightLine(Command, Map1, MapN) -->
677 variable_invocation([displays], _Name, _Var, Map1, MapN), spaces(_), displays_, a_straight_line_, line_with_list(Arguments), !,
678 {atomic_list_concat(Arguments, ',', Atom), format(string(Command), 'abline(~w)', [Atom]) }.
679
680verticalLines(DataFrameCommand, PlotCommand, Count, Map1, Map2) -->
681 variable_invocation([displays], _Name, _Var, Map1, Map2), spaces(_), displays_, extract_names(NameX, NameY),
682 from_, literal_(Map2, MapN, Cond),
683 as_vertical_lines_, line_with_list(Arguments), !,
684 {
685 atomic_concat('verticalLines', Count, DataFrameName),
686 make_data_frame_command(Cond, MapN, DataFrameName, [NameX, NameY], DataFrameCommand),
687 atomic_list_concat(Arguments, ',', Atom), format(string(PlotCommand), 'points(~w$~w,~w$~w,type="h",~w)', [DataFrameName, NameX, DataFrameName, NameY, Atom])
688 }.
689
690
691points(DataFrameCommand, PlotCommand, Count, Map1, Map2) -->
692 variable_invocation([displays], _Name, _Var, Map1, Map2), spaces(_), displays_, extract_names(NameX, NameY),
693 from_, literal_(Map2, MapN, Cond),
694 as_points_, line_with_list(Arguments), !,
695 {
696 atomic_concat('points', Count, DataFrameName),
697 make_data_frame_command(Cond, MapN, DataFrameName, [NameX, NameY], DataFrameCommand),
698 atomic_list_concat(Arguments, ',', Atom), format(string(PlotCommand), 'points(~w$~w,~w$~w,~w)',
699 [DataFrameName, NameX, DataFrameName, NameY, Atom])
700 }.
701
702line(DataFrameCommand, PlotCommand, Count, Map1, Map2) -->
703 variable_invocation([displays], _Name, _Var, Map1, Map2), spaces(_), displays_, extract_names(NameX, NameY),
704 from_, literal_(Map2, MapN, Cond), 705 as_a_line_, line_with_list(Arguments),
706 {
707 atomic_concat('line', Count, DataFrameName),
708 make_data_frame_command(Cond, MapN, DataFrameName, [NameX, NameY], DataFrameCommand),
709 710 711 atomic_list_concat(Arguments, ',', Atom), format(string(PlotCommand), '~w <- ~w[order(~w$~w),]\n lines(~w$~w,~w$~w,~w)',
712 [DataFrameName, DataFrameName, DataFrameName, NameX, DataFrameName, NameX, DataFrameName, NameY, Atom])
713 }.
714
(NameX, NameY) -->
716 variable_invocation_name_extraction([and], NameX), [and], variable_invocation_name_extraction([], NameY).
717 718
719make_data_frame_command(Cond, MapN, DataFrameName, Names, DataFrameCommand) :-
720 pad_name_var(Names, _VarList, ParamList, MapN),
721 DataFrameCommand = r_data_frame(DataFrameName, ParamList, Cond).
722
723pad_name_var([], [], [], _MapN).
724pad_name_var([Name | XT], [Var | YT], [Name=Var | ZT], MapN) :-
725 consult_map(Var, Name, MapN, MapN),
726 pad_name_var(XT, YT, ZT, MapN).
727
729chart_with_list(VarList, [Argument|ArgumentRest], Map1, MapN) -->
730 chart_with(VarHead, Argument, Map1, MapN), spaces_or_newlines(_), [and], spaces(_), chart_with_list(VarTail, ArgumentRest, Map1, MapN),
731 {append(VarHead, VarTail, VarList)}.
732chart_with_list(VarList, [Argument], Map1, MapN) --> chart_with(VarList, Argument, Map1, MapN).
733
735line_with_list(Arguments) --> spaces_or_newlines(_), [with], spaces(_), line_with_tail(Arguments).
736line_with_list([]) --> [].
737line_with_tail([H|T]) --> line_with(H), spaces_or_newlines(_), [and], spaces(_), line_with_tail(T).
738line_with_tail([H]) --> line_with(H).
739
741legend_with_list(Arguments) --> spaces_or_newlines(_), [with], spaces(_), legend_with_tail(Arguments).
742legend_with_tail([H|T]) --> legend_with(H), spaces_or_newlines(_), [and], spaces(_), legend_with_tail(T).
743legend_with_tail([H]) --> legend_with(H).
744
745listOfStringToSingleString(SList, Result) :-
746 maplist(wrap_with_quotes, SList, SWrappedList),
747 atomic_list_concat(SWrappedList, ',', Result).
748
749wrap_with_quotes(In, Out) :-
750 number(In), format(string(Out), '~w', [In]).
751wrap_with_quotes(In, Out) :-
752 not(number(In)), format(string(Out), '"~w"', [In]).
753
754legend_with(Argument) --> a_colour_of_, ['['], extract_list([']'], List, [], []), [']'], spaces(_),
755 {listOfStringToSingleString(List, ListStr), format(string(Argument), 'col=c(~w)', [ListStr]) }.
756
757legend_with(Argument) --> a_plotting_character_of_, ['['], extract_list([']'], List, [], []), [']'], spaces(_),
758 {listOfStringToSingleString(List, ListStr), format(string(Argument), 'pch=c(~w)', [ListStr]) }.
759
760legend_with(Argument) --> a_character_expansion_factor_of_, [X], spaces(_),
761 {number(X), term_to_atom(cex=X, Argument) }.
762
763legend_with(Argument) --> a_text_of_, ['['], extract_list([']'], List, [], []), [']'], spaces(_),
764 {listOfStringToSingleString(List, ListStr),
765 766 format(string(Argument), 'legend=c(~w)', [ListStr]) }.
767
768legend_with(Argument) --> a_line_type_of_, ['['], extract_list([']'], List, [], []), [']'], spaces(_),
769 {listOfStringToSingleString(List, ListStr),
770 771 format(string(Argument), 'lty=c(~w)', [ListStr]) }.
772
773legend_with(Argument) --> a_box_type_of_, [X], spaces(_),
774 {atom_string(X, XString), term_to_atom(bty=XString, Argument) }.
775
776line_with(Argument) --> a_colour_of_, [X], spaces(_),
777 {atom_string(X, XAtom), term_to_atom(col=XAtom, Argument) }.
778
779line_with(Argument) --> a_height_of_, [X], spaces(_),
780 {number(X), term_to_atom(h=X, Argument) }.
781
782line_with(Argument) --> a_width_of_, [X], spaces(_),
783 {number(X), term_to_atom(lwd=X, Argument) }.
784
785line_with(Argument) --> a_plotting_character_of_, [X], spaces(_),
786 {number(X), term_to_atom(pch=X, Argument)}.
787
788line_with(Argument) --> a_character_expansion_factor_of_, [X], spaces(_),
789 {number(X), term_to_atom(cex=X, Argument)}.
790
791chart_with([UsedVar], Argument, Map1, MapN) -->
792 variable_invocation([as], Name, UsedVar, Map1, MapN), as_title_,
793 {format(string(Argument), 'main=~w', [Name])}.
794chart_with([], Argument, _, _) --> extract_constant([], NameWords), as_title_, !,
795 {name_as_atom(NameWords, Title), term_to_atom(main=Title, Argument)}.
796chart_with([], Argument, _, _) --> extract_constant([], NameWords), as_x_axis_label_, !,
797 {name_as_atom(NameWords, Label), term_to_atom(xlab=Label, Argument) }.
798chart_with([], Argument, _, _) --> extract_constant([], NameWords), as_y_axis_label_, !,
799 {name_as_atom(NameWords, Label), term_to_atom(ylab=Label, Argument) }.
800chart_with([], Argument, _, _) --> x_axis_limits_(X, Y), !,
801 {term_to_atom(xlim=c(X,Y), Argument)}.
802chart_with([], Argument, _, _) --> y_axis_limits_(X, Y), !,
803 {term_to_atom(ylim=c(X,Y), Argument)}.
804
805
806displays_ --> [displays], spaces(_).
807
808from_ --> spaces_or_newlines(_), [from], spaces(_).
809
810as_a_line_ --> spaces_or_newlines(_), [as], spaces(_), [a], spaces(_), [line], spaces(_).
811as_points_ --> spaces_or_newlines(_), [as], spaces(_), [points], spaces(_).
812a_straight_line_ --> [a], spaces(_), [straight], spaces(_), [line], spaces(_).
813as_vertical_lines_ --> spaces_or_newlines(_), [as], spaces(_), [vertical], spaces(_), [lines], spaces(_).
814legend_ --> [legend], spaces(_).
815
816a_colour_of_ --> [a], spaces(_), [color], spaces(_), [of], spaces(_).
817a_colour_of_ --> [a], spaces(_), [colour], spaces(_), [of], spaces(_).
818a_height_of_ --> [a], spaces(_), [height], spaces(_), [of], spaces(_).
819a_width_of_ --> [a], spaces(_), [width], spaces(_), [of], spaces(_).
820a_plotting_character_of_ --> [a], spaces(_), [plotting], spaces(_), [character], spaces(_), [of], spaces(_).
821a_character_expansion_factor_of_ --> [a], spaces(_), [character], spaces(_), [expansion], spaces(_), [factor], spaces(_), [of], spaces(_).
822a_text_of_ --> [a], spaces(_), [text], spaces(_), [of], spaces(_).
823a_line_type_of_ --> [a], spaces(_), [line], spaces(_), [type], spaces(_), [of], spaces(_).
824a_box_type_of_ --> [a], spaces(_), [box], spaces(_), [type], spaces(_), [of], spaces(_).
825
831
834statement(Statement) -->
835 it_must_not_be_true_that_, 836 newline, spaces(Ind), !, conditions(Ind, [], _MapN, Conditions), spaces_or_newlines(_), period,
837 {(Conditions = [] -> Statement = [if(empty, true)];
838 (Statement = [if(empty, Conditions)]))}, !.
839
846statement(Statement) -->
847 it_becomes_the_case_that_, spaces_or_newlines(_),
848 literal_([], Map1, holds(Fluent, _)), spaces_or_newlines(_),
849 when_, spaces_or_newlines(_),
850 literal_(Map1, Map2, happens(Event, T)), spaces_or_newlines(_),
851 body_(Body, [map(T, '_change_time')|Map2],_), period,
852 {(Body = [] -> Statement = [if(initiates(Event, Fluent, T), true)];
853 (Statement = [if(initiates(Event, Fluent, T), Body)]))}, !.
854
860statement(Statement) -->
861 it_becomes_not_the_case_that_, spaces_or_newlines(_),
862 literal_([], Map1, holds(Fluent, _)), spaces_or_newlines(_),
863 when_, spaces_or_newlines(_),
864 literal_(Map1, Map2, happens(Event, T)), spaces_or_newlines(_),
865 body_(Body, [map(T, '_change_time')|Map2],_), period,
866 {(Body = [] -> Statement = [if(terminates(Event, Fluent, T), true)];
867 (Statement = [if(terminates(Event, Fluent, T), Body)] 868 ))}, !.
869
873statement(Statement) -->
874 it_is_illegal_that_, spaces_or_newlines(_),
875 literal_([], Map1, happens(Event, T)), body_(Body, Map1, _), period,
876 {(Body = [] -> Statement = [if(it_is_illegal(Event, T), true)];
877 Statement = [if(it_is_illegal(Event, T), Body)])},!.
878
880statement(Statement) -->
881 it_is_unknown_whether_, spaces_or_newlines(_),
882 literal_([], Map1, Abducible), body_(Body, Map1, _), period,
883 {(Body = [] -> Statement = [abducible(Abducible, true)];
884 Statement = [abducible(Abducible, Body)])},!.
885
887statement(Statement) --> currentLine(L),
888 literal_([], Map1, Head), body_(Body, Map1, _), period,
889 {(Body = [] -> Statement = [if(L, Head, true)]; Statement = [if(L, Head, Body)])}.
890
892statement(_, Rest, _) :-
893 asserterror('LE error found around this statement: ', Rest), fail.
894
895list_of_facts([F|R1]) --> literal_([], _,F), rest_list_of_facts(R1).
896
897rest_list_of_facts(L1) --> comma, spaces_or_newlines(_), list_of_facts(L1).
898rest_list_of_facts([]) --> [].
899
901assumptions_([A|R]) -->
902 spaces_or_newlines(_), rule_([], _, A), 903 assumptions_(R). 904assumptions_([]) --> 905 spaces_or_newlines(_).
906
907rule_(InMap, InMap, Rule) -->
908 it_is_unknown_whether_, spaces_or_newlines(_),
909 literal_([], Map1, Abducible), body_(Body, Map1, _), period,
910 {(Body = [] -> Rule = (abducible(Abducible, true):-true); Rule = (abducible(Abducible, Body):-true))},!.
911
912rule_(InMap, OutMap, Rule) -->
913 literal_(InMap, Map1, Head), body_(Body, Map1, OutMap), period,
914 915 {(Body = [] -> Rule = (Head :-true); Rule = (Head :- Body))}.
916
917rule_(M, M, _, Rest, _) :-
918 asserterror('LE error found in an assumption, near to ', Rest), fail.
919
924body_([], Map, Map) --> spaces_or_newlines(_).
925body_(Conditions, Map1, MapN) -->
926 newline, spaces(Ind), if_, !, conditions(Ind, Map1, MapN, Conditions), spaces_or_newlines(_).
927body_(Conditions, Map1, MapN) -->
928 if_, newline_or_nothing, spaces(Ind), conditions(Ind, Map1, MapN, Conditions), spaces_or_newlines(_).
929
930newline_or_nothing --> newline.
931newline_or_nothing --> [].
932
937literal_(Map1, MapN, FinalLiteral) --> 938 at_time(T, Map1, Map2), comma, possible_instance(PossibleTemplate),
939 { PossibleTemplate \=[], 940 match_template(PossibleTemplate, Map2, MapN, Literal),
941 (fluents(Fluents) -> true; Fluents = []),
942 (events(Events) -> true; Events = []),
943 (lists:member(Literal, Events) -> FinalLiteral = happens(Literal, T)
944 ; (lists:member(Literal, Fluents) -> FinalLiteral = holds(Literal, T)
945 ; FinalLiteral = Literal))}, !. 946
947literal_(Map1, MapN, FinalLiteral) --> 948 possible_instance(PossibleTemplate), comma, at_time(T, Map1, Map2),
949 { PossibleTemplate \=[], 950 match_template(PossibleTemplate, Map2, MapN, Literal),
951 (fluents(Fluents) -> true; Fluents = []),
952 (events(Events) -> true; Events = []),
953 (lists:member(Literal, Events) -> FinalLiteral = happens(Literal, T)
954 ; (lists:member(Literal, Fluents) -> FinalLiteral = holds(Literal, T)
955 ; FinalLiteral = Literal))}, !. 956
957literal_(Map1, MapN, FinalLiteral) -->
958 possible_instance(PossibleTemplate), 959 { PossibleTemplate \=[], 960 match_template(PossibleTemplate, Map1, MapN, Literal),
961 (fluents(Fluents) -> true; Fluents = []),
962 (events(Events) -> true; Events = []),
963 (consult_map(Time, '_change_time', Map1, _MapF) -> T=Time; true),
964 (lists:member(Literal, Events) -> FinalLiteral = happens(Literal, T)
965 ; (lists:member(Literal, Fluents) -> FinalLiteral = holds(Literal, T)
966 ; (FinalLiteral = Literal)))
967 968 }, !. 969
975literal_(M, M, _, Rest, _) :-
976 asserterror('LE error found in a literal ', Rest), fail.
977
979conditions(Ind0, Map1, MapN, Conds) -->
980 list_of_conds_with_ind(Ind0, Map1, MapN, Errors, ListConds),
981 {Errors=[] -> ri(Conds, ListConds); (assert_error_os(Errors), fail)}. 982conditions(_, Map, Map, _, Rest, _) :-
983 asserterror('LE indentation error ', Rest), fail.
984
987list_of_conds_with_ind(Ind0, Map1, MapN, [], [Cond|Conditions]) -->
988 condition(Cond, Ind0, Map1, Map2),
989 more_conds(Ind0, Ind0,_, Map2, MapN, Conditions).
990list_of_conds_with_ind(_, M, M, [error('Error in condition at', LineNumber, Tokens)], [], Rest, _) :-
991 once( nth1(N,Rest,newline(NextLine)) ), LineNumber is NextLine-2,
992 RelevantN is N-1,
993 length(Relevant,RelevantN), append(Relevant,_,Rest),
994 findall(Token, (member(T,Relevant), (T=newline(_) -> Token='\n' ; Token=T)), Tokens).
995
996more_conds(Ind0, _, Ind3, Map1, MapN, [ind(Ind2), Op, Cond2|RestMapped]) -->
997 newline, spaces(Ind2), {Ind0 =< Ind2}, 998 operator(Op), condition(Cond2, Ind2, Map1, Map2),
999 1000 more_conds(Ind0, Ind2, Ind3, Map2, MapN, RestMapped).
1001more_conds(_, Ind, Ind, Map, Map, [], L, L).
1002
1005term_(StopWords, Term, Map1, MapN) -->
1006 (variable(StopWords, Term, Map1, MapN), !); (constant(StopWords, Term, Map1, MapN), !); (list_(Term, Map1, MapN), !); (expression(Term, Map1), !). 1007
1009list_(List, Map1, MapN) -->
1010 spaces(_), bracket_open_, !, extract_list([']'], List, Map1, MapN), bracket_close.
1012compound_(V1/V2, Map1, MapN) -->
1013 term_(['/'], V1, Map1, Map2), ['/'], term_([], V2, Map2, MapN).
1014
1018
1025condition(FinalExpression, _, Map1, MapN) -->
1026 variable([is], Set, Map1, Map2), is_a_set_of_, term_([], Term, Map2, Map3), !, 1027 newline, spaces(Ind2), where_, conditions(Ind2, Map3, Map4, Goals),
1028 modifiers(setof(Term,Goals,Set), Map4, MapN, FinalExpression).
1029
1031condition(FinalExpression, _, Map1, MapN) -->
1032 for_all_cases_in_which_, newline, !,
1033 spaces(Ind2), conditions(Ind2, Map1, Map2, Conds), spaces_or_newlines(_),
1034 it_is_the_case_that_, newline,
1035 spaces(Ind3), conditions(Ind3, Map2, Map3, Goals),
1036 modifiers(forall(Conds,Goals), Map3, MapN, FinalExpression).
1037
1039condition(FinalExpression, _, Map1, MapN) -->
1040 variable([is], Value, Map1, Map2), is_the_sum_of_each_, extract_variable([such], [], NameWords, [], _), such_that_, !,
1041 { name_predicate(NameWords, Name), update_map(Each, Name, Map2, Map3) }, newline,
1042 spaces(Ind), conditions(Ind, Map3, Map4, Conds),
1043 modifiers(aggregate_all(sum(Each),Conds,Value), Map4, MapN, FinalExpression).
1044
1048condition(not(Conds), _, Map1, MapN) -->
1050 spaces(_), not_, newline, 1051 spaces(Ind), conditions(Ind, Map1, MapN, Conds), !.
1052
1053condition(Cond, _, Map1, MapN) -->
1054 literal_(Map1, MapN, Cond), !.
1055
1057condition(_, _Ind, Map, Map, Rest, _) :-
1058 asserterror('LE error found at a condition ', Rest), fail.
1059
1062modifiers(MainExpression, Map1, MapN, on(MainExpression, Var) ) -->
1063 newline, spaces(_), at_, variable([], Var, Map1, MapN). 1064modifiers(MainExpression, Map, Map, MainExpression) --> [].
1065
1067variable(StopWords, Var, Map1, MapN) --> variable_declaration(StopWords, Var, Map1, MapN).
1068variable(StopWords, Var, Map1, MapN) --> variable_invocation(StopWords, _Name, Var, Map1, MapN).
1069variable_declaration(StopWords, Var, Map1, MapN) -->
1070 spaces(_), indef_determiner, extract_variable(StopWords, [], NameWords, [], _), 1071 { NameWords\=[], name_predicate(NameWords, Name), update_map(Var, Name, Map1, MapN) }.
1072variable_invocation(StopWords, Name, Var, Map1, MapN) -->
1073 variable_invocation_name_extraction(StopWords, Name),
1074 { consult_map(Var, Name, Map1, MapN) }.
(StopWords, Name) -->
1079 spaces(_), def_determiner, extract_variable(StopWords, [], NameWords, [], _),
1080 { NameWords\=[], name_predicate(NameWords, Name) }.
1081variable_invocation_name_extraction(StopWords, Name) -->
1082 spaces(_), extract_variable(StopWords, [], NameWords, [], _),
1083 { NameWords\=[], name_predicate(NameWords, Name) }.
1084
1086constant(StopWords, Number, Map, Map) -->
1087 1088 extract_constant(StopWords, [Number]).
1089
1091prolog_literal_(Prolog, Map1, MapN) -->
1092 predicate_name_(Predicate), parentesis_open_, extract_list([], Arguments, Map1, MapN), parentesis_close_,
1093 {Prolog =.. [Predicate|Arguments]}.
1094
1095predicate_name_(Module:Predicate) -->
1096 [Module], colon_, extract_constant([], NameWords), { name_predicate(NameWords, Predicate) }, !.
1097predicate_name_(Predicate) --> extract_constant([], NameWords), { name_predicate(NameWords, Predicate) }.
1098
1099at_time(T, Map1, MapN) --> spaces_or_newlines(_), at_, term_([], T, Map1, MapN), spaces_or_newlines(_).
1100
1101spaces(N) --> [' '], !, spaces(M), {N is M + 1}.
1103spaces(N) --> ['\t'], !, spaces(M), {N is M + 4}. 1104spaces(0) --> [].
1105
1106spaces_or_newlines(N) --> [' '], !, spaces_or_newlines(M), {N is M + 1}.
1107spaces_or_newlines(N) --> ['\t'], !, spaces_or_newlines(M), {N is M + 4}. 1108spaces_or_newlines(N) --> newline, !, spaces_or_newlines(M), {N is M + 1}. 1109spaces_or_newlines(0) --> [].
1110
1111newline --> [newline(_Next)].
1112
1113one_or_many_newlines --> newline, spaces(_), one_or_many_newlines, !.
1114one_or_many_newlines --> [].
1115
1116if_ --> [if], spaces_or_newlines(_). 1117if_ --> [se], spaces_or_newlines(_). 1118if_ --> [si], spaces_or_newlines(_). 1119
1120period --> ['.'].
1121comma --> [','].
1122colon_ --> [':'], spaces(_).
1123
1124comma_or_period --> period, !.
1125comma_or_period --> comma.
1126
1127and_ --> [and].
1128and_ --> [e]. 1129and_ --> [et]. 1130and_ --> [y]. 1131
1132or_ --> [or].
1133or_ --> [o]. 1134or_ --> [ou]. 1135
1136not_ --> [it], spaces(_), [is], spaces(_), [not], spaces(_), [the], spaces(_), [case], spaces(_), [that], spaces(_).
1137not_ --> [non], spaces(_), [risulta], spaces(_), [che], spaces(_). 1138not_ --> [ce], spaces(_), [n],[A],[est], spaces(_), [pas], spaces(_), [le], spaces(_), [cas], spaces(_), [que], spaces(_), {atom_string(A, "'")}. 1139not_ --> [no], spaces(_), [es], spaces(_), [el], spaces(_), [caso], spaces(_), [que], spaces(_). 1140
1141is_the_sum_of_each_ --> [is], spaces(_), [the], spaces(_), [sum], spaces(_), [of], spaces(_), [each], spaces(_) .
1142is_the_sum_of_each_ --> [è], spaces(_), [la], spaces(_), [somma], spaces(_), [di], spaces(_), [ogni], spaces(_). 1143is_the_sum_of_each_ --> [es], spaces(_), [la], spaces(_), [suma], spaces(_), [de], spaces(_), [cada], spaces(_). 1144is_the_sum_of_each_ --> [est], spaces(_), [la], spaces(_), [somme], spaces(_), [de], spaces(_), [chaque], spaces(_). 1145
1146such_that_ --> [such], spaces(_), [that], spaces(_).
1147such_that_ --> [tale], spaces(_), [che], spaces(_). 1148such_that_ --> [tel], spaces(_), [que], spaces(_). 1149such_that_ --> [tal], spaces(_), [que], spaces(_). 1150
1151at_ --> [at], spaces(_).
1152at_ --> [a], spaces(_). 1153
1154minus_ --> ['-'], spaces(_).
1155
1156plus_ --> ['+'], spaces(_).
1157
1158divide_ --> ['/'], spaces(_).
1159
1160times_ --> ['*'], spaces(_).
1161
1162bracket_open_ --> [A], spaces(_), {atom_string(A, "[")}.
1163bracket_close --> [A], spaces(_), {atom_string(A, "]")}.
1164
1165parenthesis_open_ --> ['('], spaces(_).
1166parenthesis_close_ --> [A], spaces(_), {atom_string(A, ")")}.
1167
1168this_information_ --> [this], spaces(_), [information], spaces(_).
1169
1170has_been_recorded_ --> [has], spaces(_), [been], spaces(_), [recorded], spaces(_).
1171
1172for_all_cases_in_which_ --> spaces_or_newlines(_), [for], spaces(_), [all], spaces(_), [cases], spaces(_), [in], spaces(_), [which], spaces(_).
1173for_all_cases_in_which_ --> spaces_or_newlines(_), [pour], spaces(_), [tous], spaces(_), [les], spaces(_), [cas], spaces(_), [o],[Ă¹], spaces(_). 1174for_all_cases_in_which_ --> spaces_or_newlines(_), [per], spaces(_), [tutti], spaces(_), [i], spaces(_), [casi], spaces(_), [in], spaces(_), [cui], spaces(_). 1175for_all_cases_in_which_ --> spaces_or_newlines(_), [en], spaces(_), [todos], spaces(_), [los], spaces(_), [casos], spaces(_), [en], spaces(_), [los], spaces(_), [que], spaces(_). 1176for_all_cases_in_which_ --> spaces_or_newlines(_), [en], spaces(_), [cualquier], spaces(_), [caso], spaces(_), [en], spaces(_), [el], spaces(_), [que], spaces(_). 1177
1178it_is_the_case_that_ --> [it], spaces(_), [is], spaces(_), [the], spaces(_), [case], spaces(_), [that], spaces(_).
1179it_is_the_case_that_ --> [es], spaces(_), [el], spaces(_), [caso], spaces(_), [que], spaces(_). 1180it_is_the_case_that_ --> [es], spaces(_), [también], spaces(_), [el], spaces(_), [caso], spaces(_), [que], spaces(_). 1181it_is_the_case_that_ --> [c], [A], [est], spaces(_), [le], spaces(_), [cas], spaces(_), [que], spaces(_), {atom_string(A, "'")}. 1182it_is_the_case_that_ --> [è], spaces(_), [provato], spaces(_), [che], spaces(_). 1183
1184is_a_set_of_ --> [is], spaces(_), [a], spaces(_), [set], spaces(_), [of], spaces(_).
1185is_a_set_of_ --> [es], spaces(_), [un], spaces(_), [conjunto], spaces(_), [de], spaces(_). 1186is_a_set_of_ --> [est], spaces(_), [un], spaces(_), [ensemble], spaces(_), [de], spaces(_). 1187is_a_set_of_ --> [est], spaces(_), [un], spaces(_), [ensemble], spaces(_), [de], spaces(_). 1188
1189where_ --> [where], spaces(_).
1190where_ --> [en], spaces(_), [donde], spaces(_). 1191where_ --> ['oĂ¹'], spaces(_). 1192where_ --> [dove], spaces(_). 1193where_ --> [quando], spaces(_). 1194where_ --> [donde], spaces(_). 1195
1196scenario_ --> spaces_or_newlines(_), ['Scenario'], !, spaces(_).
1197scenario_ --> spaces_or_newlines(_), [scenario], spaces(_). 1198scenario_ --> spaces_or_newlines(_), [le], spaces(_), [scénario], spaces(_). 1199scenario_ --> spaces_or_newlines(_), [escenario], spaces(_). 1200
1201is_colon_ --> [is], spaces(_), [':'], spaces(_).
1202is_colon_ --> [es], spaces(_), [':'], spaces(_). 1203is_colon_ --> [est], spaces(_), [':'], spaces(_). 1204is_colon_ --> [è], spaces(_), [':'], spaces(_). 1205
1206query_ --> spaces_or_newlines(_), ['Query'], !, spaces(_).
1207query_ --> spaces_or_newlines(_), [query], spaces(_).
1208query_ --> spaces_or_newlines(_), [la], spaces(_), [question], spaces(_). 1209query_ --> spaces_or_newlines(_), [la], spaces(_), [pregunta], spaces(_). 1210query_ --> spaces_or_newlines(_), [domanda], spaces(_). 1211
1212for_which_ --> [for], spaces(_), [which], spaces(_).
1213for_which_ --> [para], spaces(_), [el], spaces(_), [cual], spaces(_). 1214for_which_ --> [pour], spaces(_), [qui], spaces(_). 1215for_which_ --> [per], spaces(_), [cui], spaces(_). 1216
1217
1218as_title_ --> [as], spaces(_), [title], spaces(_).
1219
1220as_x_axis_label_ --> [as], spaces(_), [x], spaces(_), [axis], spaces(_), [label], spaces(_).
1221
1222as_y_axis_label_ --> [as], spaces(_), [y], spaces(_), [axis], spaces(_), [label], spaces(_).
1223
1224x_axis_limits_(X, Y) --> [x], spaces(_), [axis], spaces(_), [limits], spaces(_), [from], spaces(_), item(X, []), spaces(_), [to], spaces(_), item(Y, []), spaces(_), {number(X), number(Y)}.
1225
1226y_axis_limits_(X, Y) --> [y], spaces(_), [axis], spaces(_), [limits], spaces(_), [from], spaces(_), item(X, []), spaces(_), [to], spaces(_), item(Y, []), spaces(_), {number(X), number(Y)}.
1227
(Ind, Map) --> spaces(Ind), for_which_, list_of_vars([], Map), colon_, spaces_or_newlines(_).
1229query_header(0, []) --> [].
1230
1231list_of_vars(Map1, MapN) -->
1232 extract_variable([',', and, el, et, y, ':'], [], NameWords, [], _),
1233 { name_predicate(NameWords, Name), update_map(_Var, Name, Map1, Map2) },
1234 rest_of_list_of_vars(Map2, MapN).
1235
1236rest_of_list_of_vars(Map1, MapN) --> and_or_comma_, list_of_vars(Map1, MapN).
1237rest_of_list_of_vars(Map, Map) --> [].
1238
1239and_or_comma_ --> [','], spaces(_).
1240and_or_comma_ --> and_, spaces(_).
1241
1242it_becomes_the_case_that_ -->
1243 it_, [becomes], spaces(_), [the], spaces(_), [case], spaces(_), [that], spaces(_).
1244
1245it_becomes_not_the_case_that_ -->
1246 it_, [becomes], spaces(_), [not], spaces(_), [the], spaces(_), [case], spaces(_), [that], spaces(_).
1247it_becomes_not_the_case_that_ -->
1248 it_, [becomes], spaces(_), [no], spaces(_), [longer], spaces(_), [the], spaces(_), [case], spaces(_), [that], spaces(_).
1249
1250when_ --> [when], spaces(_).
1251
1252it_ --> [it], spaces(_), !.
1253it_ --> ['It'], spaces(_).
1254
1255observe_ --> [observe], spaces(_).
1256
1257it_is_illegal_that_ -->
1258 it_, [is], spaces(_), [illegal], spaces(_), [that], spaces(_).
1259
1260it_is_unknown_whether_ -->
1261 it_, [is], spaces(_), [unknown], spaces(_), [whether], spaces(_).
1262
1263it_is_unknown_whether_ -->
1264 it_, [is], spaces(_), [unknown], spaces(_), [that], spaces(_).
1265
1266it_is_unknown_whether_ -->
1267 [non], spaces(_), [è], spaces(_), [noto], spaces(_), [se], spaces(_). 1268
1269it_must_not_be_true_that_ -->
1270 it_, [must], spaces(_), [not], spaces(_), [be], spaces(_), [true], spaces(_), [that], spaces(_).
1271
1272ontology_ --> spaces_or_newlines(_), ['Ontology'], !, spaces(_).
1273ontology_ --> spaces_or_newlines(_), [ontology], spaces(_). 1274ontology_ --> spaces_or_newlines(_), [the], spaces(_), [ontology], spaces(_). 1275ontology_ --> spaces_or_newlines(_), ['l\''], spaces(_), [ontologie], spaces(_). 1276ontology_ --> spaces_or_newlines(_), [la], spaces(_), ['ontologĂa'], spaces(_). 1277
1281
1282ri(P, L) :- rinden(Q, L), c2p(Q, P).
1283
1285rinden(Q, List) :- rind(_, _, Q, List).
1286
1287rind(L, I, Q, List) :- rind_and(L, I, Q, List); rind_or(L, I, Q, List).
1288
1289rind_and(100, [], true, []).
1290rind_and(100, [], Cond, [Cond]) :- simple(Cond).
1291rind_and(T, [T|RestT], and(First,Rest), Final) :-
1292 combine(NewF, [ind(T), and|RestC], Final),
1293 rind(T1, Tr1, First, NewF),
1294 T1>T,
1295 rind(Tn, Tr, Rest, RestC),
1296 append(Tr1, Tr, RestT),
1297 right_order_and(Rest, Tn, T).
1298
1299rind_or(100, [], false, []).
1300rind_or(100, [], Cond, [Cond]) :- simple(Cond).
1301rind_or(T, [T|RestT], or(First,Rest), Final) :-
1302 combine(NewF, [ind(T), or|RestC], Final),
1303 rind(T1, Tr1, First, NewF),
1304 T1>T,
1305 rind(Tn, Tr, Rest, RestC),
1306 append(Tr1, Tr, RestT),
1307 right_order_or(Rest, Tn, T).
1308
1309right_order_and(Rest, Tn, T) :- Rest=or(_,_), Tn>T.
1310right_order_and(Rest, Tn, T) :- Rest=and(_,_), Tn=T.
1311right_order_and(Rest, _, _) :- simple(Rest).
1312
1313right_order_or(Rest, Tn, T) :- Rest=and(_,_), Tn>T.
1314right_order_or(Rest, Tn, T) :- Rest=or(_,_), Tn=T.
1315right_order_or(Rest, _, _) :- simple(Rest).
1316
1317combine(F, S, O) :- ( F\=[], S=[ind(_), Op, V], ((Op==and_); (Op==or_)), simple(V), O=F) ; (F=[], O=S).
1318combine([H|T], S, [H|NT]) :- combine(T, S, NT).
1319
1320simple(Cond) :- Cond\=and(_,_), Cond\=or(_,_), Cond\=true, Cond\=false.
1321
1322c2p(true, true).
1323c2p(false, false).
1324c2p(C, C) :- simple(C).
1325c2p(and(A, RestA), (AA, RestAA)) :-
1326 c2p(A, AA),
1327 c2p(RestA, RestAA).
1328c2p(or(A, RestA), (AA; RestAA)) :-
1329 c2p(A, AA),
1330 c2p(RestA, RestAA).
1331
1334ss_(All, [' '|RestIn], Output) :-
1335 ss_(All, RestIn, Output).
1336ss_([Word|Rest], [Word|RestIn], Output) :-
1337 ss_(Rest, RestIn, Output).
1338ss_([], Rin, Rout) :- spaces(_, Rin, Rout).
1339
([], []) :- !.
1341clean_comments(['%'|Rest], New) :- 1342 jump_comment(Rest, Next),
1343 clean_comments(Next, New).
1344clean_comments([Code|Rest], [Code|New]) :-
1345 clean_comments(Rest, New).
1346
([], []).
1348jump_comment([newline(N)|Rest], [newline(N)|Rest]). 1349jump_comment([_|R1], R2) :-
1350 jump_comment(R1, R2).
1351
1354template_decl([], [newline(_)|RestIn], [newline(_)|RestIn]) :-
1355 asserterror('LE error: misplaced new line found in a template declaration ', RestIn), !,
1356 fail. 1357template_decl(RestW, [' '|RestIn], Out) :- !, 1358 template_decl(RestW, RestIn, Out).
1359template_decl(RestW, ['\t'|RestIn], Out) :- !, 1360 template_decl(RestW, RestIn, Out).
1364template_decl([Word|RestW], [Word|RestIn], Out) :-
1365 not(lists:member(Word,['.', ','])), 1366 template_decl(RestW, RestIn, Out), !.
1367template_decl([], [Word|Rest], [Word|Rest]) :-
1368 lists:member(Word,['.', ',']), !.
1369template_decl(_, Rest, _) :-
1370 asserterror('LE error found in a template declaration ', Rest), fail.
1371
1373build_template(RawTemplate, Predicate, Arguments, TypesAndNames, Template) :-
1374 build_template_elements(RawTemplate, [], Arguments, TypesAndNames, OtherWords, Template),
1375 name_predicate(OtherWords, Predicate).
1376
1378build_template_elements([], _, [], [], [], []) :- !.
1380build_template_elements(['*', Word|RestOfWords], _Previous, [Var|RestVars], [Name-Type|RestTypes], Others, [Var|RestTemplate]) :-
1381 has_pairing_asteriks([Word|RestOfWords]),
1382 1383 phrase(determiner, [Word|RestOfWords], RRestOfWords), 1384 extract_variable_template(['*'], [], NameWords, [], TypeWords, RRestOfWords, ['*'|NextWords]), !, 1385 name_predicate(NameWords, Name),
1386 name_predicate(TypeWords, Type),
1387 build_template_elements(NextWords, [], RestVars, RestTypes, Others, RestTemplate).
1388build_template_elements(['*', Word|RestOfWords], _Previous,_, _, _, _) :-
1389 not(has_pairing_asteriks([Word|RestOfWords])), !, fail. 1397build_template_elements([Word|RestOfWords], Previous, RestVars, RestTypes, [Word|Others], [Word|RestTemplate]) :-
1398 build_template_elements(RestOfWords, [Word|Previous], RestVars, RestTypes, Others, RestTemplate).
1399
1400has_pairing_asteriks(RestOfTemplate) :-
1401 findall('*',member('*', RestOfTemplate), Asteriks), length(Asteriks, N), 1 is mod(N, 2).
1402
1403name_predicate(Words, Predicate) :-
1404 concat_atom(Words, '_', Predicate).
1405
1406name_predicate_with_spaces(Words, Predicate) :-
1407 concat_atom(Words, ' ', Predicate).
1408
1410name_as_atom([Number], Number) :-
1411 number(Number), !.
1412name_as_atom([Atom], Number) :-
1413 atom_number(Atom, Number), !.
1414name_as_atom(Words, Name) :-
1415 numbervars(Words, 1, _, [functor_name('unknown')]),
1416 replace_vars(Words, Atoms),
1417 list_words_to_codes(Atoms, Codes),
1418 replace_ast_a(Codes, CCodes),
1419 atom_codes(Name, CCodes).
1420
1421words_to_atom(Words, Name) :- 1422 numbervars(Words, 0, _, [singletons(true)]),
1423 list_words_to_codes(Words, Codes),
1424 atom_codes(Name, Codes).
1425
1426replace_ast_a([], []) :- !.
1427replace_ast_a([42,32,97|Rest], [42,97|Out]) :- !,
1428 replace_final_ast(Rest, Out).
1429replace_ast_a([C|Rest], [C|Out]) :-
1430 replace_ast_a(Rest, Out).
1431
1432replace_final_ast([], []) :- !.
1433replace_final_ast([32,42|Rest], [42|Out]) :- !,
1434 replace_ast_a(Rest, Out).
1435replace_final_ast([C|Rest], [C|Out]) :-
1436 replace_final_ast(Rest, Out).
1437
1441list_words_to_codes([], []).
1442list_words_to_codes([Word|RestW], Out) :-
1443 atom_codes(Word, Codes),
1444 remove_quotes(Codes, CleanCodes),
1445 list_words_to_codes(RestW, Next),
1446 (Next=[]-> Out=CleanCodes;
1447 1448 (Next=[95|_]; Next=[43|_]; Next=[45|_]; Next=[47|_]; Next=[92|_];
1449 CleanCodes=[43]; CleanCodes=[45])->
1450 append(CleanCodes, Next, Out);
1451 append(CleanCodes, [32|Next], Out)
1452 ), !.
1453
1454remove_quotes([], []) :-!.
1455remove_quotes([39|RestI], RestC) :- remove_quotes(RestI, RestC), !.
1457remove_quotes([40, _, 41|RestI], RestC) :- remove_quotes(RestI, RestC), !.
1459remove_quotes([C|RestI], [C|RestC]) :- remove_quotes(RestI, RestC).
1460
1461replace_vars([],[]) :- !.
1462replace_vars([A|RI], [A|RO]) :- atom(A), replace_vars(RI,RO), !.
1463replace_vars([W|RI], [A|RO]) :- term_to_atom(W, A), replace_vars(RI,RO).
1464
1465add_cond(and, Ind1, Ind2, Previous, C4, (C; (C3, C4))) :-
1466 last_cond(or, Previous, C, C3), 1467 Ind1 < Ind2, !.
1468add_cond(and, Ind1, Ind2, Previous, C4, ((C; C3), C4)) :-
1469 last_cond(or, Previous, C, C3), 1470 Ind1 > Ind2, !.
1471add_cond(and,I, I, (C, C3), C4, (C, (C3, C4))) :- !.
1472add_cond(and,_, _, Cond, RestC, (Cond, RestC)) :- !.
1473add_cond(or, Ind1, Ind2, Previous, C4, (C, (C3; C4))) :-
1474 last_cond(and, Previous, C, C3), 1475 Ind1 < Ind2, !.
1476add_cond(or, Ind1, Ind2, Previous, C4, ((C, C3); C4)) :-
1477 last_cond(and, Previous, C, C3), 1478 Ind1 > Ind2, !.
1479add_cond(or, I, I, (C; C3), C4, (C; (C3; C4))) :- !.
1480add_cond(or, _, _, Cond, RestC, (Cond; RestC)).
1481
1482last_cond(or, (A;B), A, B) :- B\=(_;_), !.
1483last_cond(or, (C;D), (C;R), Last) :- last_cond(or, D, R, Last).
1484
1485last_cond(and, (A,B), A, B) :- B\=(_,_), !.
1486last_cond(and, (C,D), (C,R), Last) :- last_cond(and, D, R, Last).
1487
1490adjust_op(Ind1, Ind2, C1, and, C2, and, C3, ((C1, C2), C3) ) :-
1491 Ind1 =< Ind2, !.
1492adjust_op(Ind1, Ind2, C1, and, C2, and, C3, ((C1, C2), C3) ) :-
1493 Ind1 > Ind2, !.
1495adjust_op(Ind1, Ind2, C1, or, C2, or, C3, ((C1; C2); C3) ) :-
1496 Ind1 =< Ind2, !.
1497adjust_op(Ind1, Ind2, C1, or, C2, or, C3, ((C1; C2); C3) ) :-
1498 Ind1 > Ind2, !.
1500adjust_op(Ind1, Ind2, C1, and, C2, or, C3, (C1, (C2; C3)) ) :-
1501 Ind1 < Ind2, !.
1503adjust_op(Ind1, Ind2, C1, or, C2, and, C3, ((C1; C2), C3) ) :-
1504 Ind1 > Ind2, !.
1506adjust_op(Ind1, Ind2, C1, or, C2, and, C3, (C1; (C2, C3)) ) :-
1507 Ind1 < Ind2, !.
1509adjust_op(Ind1, Ind2, C1, and, C2, or, C3, ((C1, C2); C3) ) :-
1510 Ind1 > Ind2.
1511
1512operator(and, In, Out) :- and_(In, Out).
1513operator(or, In, Out) :- or_(In, Out).
1514
1518possible_instance([], [], []) :- !.
1519possible_instance(Final, ['['|RestIn], Out) :- !,
1520 possible_instance_for_lists(List, RestIn, [']'|Next]),
1521 possible_instance(RestW, Next, Out),
1522 append(['['|List], [']'|RestW], Final).
1523possible_instance(RestW, [' '|RestIn], Out) :- !, 1524 possible_instance(RestW, RestIn, Out).
1525possible_instance(RestW, ['\t'|RestIn], Out) :- !, 1526 possible_instance(RestW, RestIn, Out).
1527possible_instance([that|Instance], In, Out) :- 1528 phrase(spaces_or_newlines(_), In, [that|Rest]),
1529 phrase(spaces_or_newlines(_), Rest, Next), !,
1530 possible_instance(Instance, Next, Out).
1531possible_instance([Word|RestW], [Word|RestIn], Out) :-
1532 1533 not(lists:member(Word,[newline(_), if, '.', ','])),
1534 1535 possible_instance(RestW, RestIn, Out).
1536possible_instance([], [Word|Rest], [Word|Rest]) :-
1537 lists:member(Word,[newline(_), if, '.', ',']). 1538
1541possible_instance_for_lists([], [']'|Out], [']'|Out]) :- !.
1542possible_instance_for_lists(RestW, [' '|RestIn], Out) :- !, 1543 possible_instance_for_lists(RestW, RestIn, Out).
1544possible_instance_for_lists(RestW, ['\t'|RestIn], Out) :- !, 1545 possible_instance_for_lists(RestW, RestIn, Out).
1546possible_instance_for_lists([Word|RestW], [Word|RestIn], Out) :-
1547 1548 possible_instance_for_lists(RestW, RestIn, Out).
1551
1553match_template(PossibleLiteral, Map1, MapN, Literal) :-
1554 1555 meta_dictionary(Predicate, _, MetaCandidate),
1556 meta_match(MetaCandidate, PossibleLiteral, Map1, MapN, MetaTemplate), !,
1557 meta_dictionary(Predicate, _, MetaTemplate),
1558 Literal =.. Predicate.
1559
1560match_template(PossibleLiteral, Map1, MapN, Literal) :-
1561 1562 dictionary(Predicate, _, Candidate),
1563 match(Candidate, PossibleLiteral, Map1, MapN, Template), !,
1564 dictionary(Predicate, _, Template),
1565 Literal =.. Predicate.
1566 1567
1570meta_match([], [], Map, Map, []) :- !.
1571meta_match([Word|_LastElement], [Word|PossibleLiteral], Map1, MapN, [Word,Literal]) :- 1572 Word = that, 1573 (meta_dictionary(Predicate, _, Candidate); dictionary(Predicate, _, Candidate)), 1574 match(Candidate, PossibleLiteral, Map1, MapN, InnerTemplate),
1575 (meta_dictionary(Predicate, _, InnerTemplate); dictionary(Predicate, _, InnerTemplate)),
1576 Literal =.. Predicate, !.
1577meta_match([MetaElement|RestMetaElements], [MetaWord|RestPossibleLiteral], Map1, MapN, [MetaElement|RestSelected]) :-
1578 nonvar(MetaElement), MetaWord = MetaElement, !,
1579 meta_match(RestMetaElements, RestPossibleLiteral, Map1, MapN, RestSelected).
1588meta_match([MetaElement|RestMetaElements], PossibleLiteral, Map1, MapN, [Literal|RestSelected]) :-
1589 var(MetaElement), stop_words(RestMetaElements, StopWords),
1590 extract_literal(StopWords, LiteralWords, PossibleLiteral, NextWords),
1591 dictionary(Predicate, _, Candidate), 1592 match(Candidate, LiteralWords, Map1, Map2, Template),
1593 dictionary(Predicate, _, Template),
1594 Literal =.. Predicate, !,
1595 meta_match(RestMetaElements, NextWords, Map2, MapN, RestSelected).
1597meta_match([Element|RestElements], [Det|PossibleLiteral], Map1, MapN, [Var|RestSelected]) :-
1598 var(Element),
1599 phrase(indef_determiner, [Det|PossibleLiteral], RPossibleLiteral), stop_words(RestElements, StopWords),
1600 extract_variable(StopWords, [], NameWords, [], _, RPossibleLiteral, NextWords), NameWords \= [], 1601 name_predicate(NameWords, Name),
1602 update_map(Var, Name, Map1, Map2), !, 1603 meta_match(RestElements, NextWords, Map2, MapN, RestSelected).
1604meta_match([Element|RestElements], [Det|PossibleLiteral], Map1, MapN, [Var|RestSelected]) :-
1605 var(Element),
1606 phrase(def_determiner, [Det|PossibleLiteral], RPossibleLiteral), stop_words(RestElements, StopWords),
1607 extract_variable(StopWords, [], NameWords, [], _, RPossibleLiteral, NextWords), NameWords \= [], 1608 name_predicate(NameWords, Name),
1609 consult_map(Var, Name, Map1, Map2), !, 1610 meta_match(RestElements, NextWords, Map2, MapN, RestSelected).
1612meta_match([Element|RestElements], PossibleLiteral, Map1, MapN, [Var|RestSelected]) :-
1613 var(Element), stop_words(RestElements, StopWords),
1614 extract_variable(StopWords, [], NameWords, [], _, PossibleLiteral, NextWords), NameWords \= [], 1615 name_predicate(NameWords, Name),
1616 consult_map(Var, Name, Map1, Map2), !, 1617 meta_match(RestElements, NextWords, Map2, MapN, RestSelected).
1618meta_match([Element|RestElements], ['['|PossibleLiteral], Map1, MapN, [List|RestSelected]) :-
1619 var(Element), stop_words(RestElements, StopWords),
1620 extract_list([']'|StopWords], List, Map1, Map2, PossibleLiteral, [']'|NextWords]), !, 1621 meta_match(RestElements, NextWords, Map2, MapN, RestSelected).
1623meta_match([Element|RestElements], [Word|PossibleLiteral], Map1, MapN, [Expression|RestSelected]) :-
1624 var(Element), stop_words(RestElements, StopWords),
1625 extract_expression([','|StopWords], NameWords, [Word|PossibleLiteral], NextWords), NameWords \= [],
1626 1627 ( phrase(expression(Expression, Map1), NameWords) -> true ; ( name_predicate_with_spaces(NameWords, Expression) ) ),
1628 1629 meta_match(RestElements, NextWords, Map1, MapN, RestSelected).
1630
1633match([], [], Map, Map, []) :- !. 1635match([Word|_LastElement], [Word|PossibleLiteral], Map1, MapN, [Word,Literal]) :- 1636 Word = that, 1637 (meta_dictionary(Predicate, _, Candidate); dictionary(Predicate, _, Candidate)), 1638 match(Candidate, PossibleLiteral, Map1, MapN, InnerTemplate),
1639 (meta_dictionary(Predicate, _, InnerTemplate); dictionary(Predicate, _, InnerTemplate)),
1640 Literal =.. Predicate, !.
1647match([Element|RestElements], [Word|PossibleLiteral], Map1, MapN, [Element|RestSelected]) :-
1648 nonvar(Element), Word = Element,
1649 match(RestElements, PossibleLiteral, Map1, MapN, RestSelected).
1650match([Element|RestElements], [Det|PossibleLiteral], Map1, MapN, [Var|RestSelected]) :-
1651 var(Element),
1652 phrase(indef_determiner,[Det|PossibleLiteral], RPossibleLiteral), stop_words(RestElements, StopWords),
1653 extract_variable(StopWords, [], NameWords, [], _, RPossibleLiteral, NextWords), NameWords \= [], 1654 name_predicate(NameWords, Name),
1655 update_map(Var, Name, Map1, Map2), !, 1656 match(RestElements, NextWords, Map2, MapN, RestSelected).
1657match([Element|RestElements], [Det|PossibleLiteral], Map1, MapN, [Var|RestSelected]) :-
1658 var(Element),
1659 phrase(def_determiner, [Det|PossibleLiteral], RPossibleLiteral), stop_words(RestElements, StopWords),
1660 extract_variable(StopWords, [], NameWords, [], _, RPossibleLiteral, NextWords), NameWords \= [], 1661 name_predicate(NameWords, Name),
1662 consult_map(Var, Name, Map1, Map2), !, 1663 match(RestElements, NextWords, Map2, MapN, RestSelected).
1665match([Element|RestElements], PossibleLiteral, Map1, MapN, [Var|RestSelected]) :-
1666 var(Element), stop_words(RestElements, StopWords),
1667 extract_variable(StopWords, [], NameWords, [], _, PossibleLiteral, NextWords), NameWords \= [], 1668 name_predicate(NameWords, Name),
1669 consult_map(Var, Name, Map1, Map2), !, 1670 match(RestElements, NextWords, Map2, MapN, RestSelected).
1671match([Element|RestElements], ['['|PossibleLiteral], Map1, MapN, [List|RestSelected]) :-
1672 var(Element), stop_words(RestElements, StopWords),
1673 extract_list([']'|StopWords], List, Map1, Map2, PossibleLiteral, [']'|NextWords]), 1674 1675 1676 match(RestElements, NextWords, Map2, MapN, RestSelected).
1678match([Element|RestElements], [Word|PossibleLiteral], Map1, MapN, [Expression|RestSelected]) :-
1679 var(Element), stop_words(RestElements, StopWords),
1680 1681 extract_expression([','|StopWords], NameWords, [Word|PossibleLiteral], NextWords), NameWords \= [],
1682 1683 1684 ( phrase(expression(Expression, Map1), NameWords) -> true ; (
1685 name_predicate_with_spaces(NameWords, Expression)
1686 1687 )
1688 ),
1689 1690 match(RestElements, NextWords, Map1, MapN, RestSelected).
1691 1692
1693correct_list([], []) :- !.
1694correct_list([A,B], [A,B]) :- atom(B), !. 1695correct_list([A,B], [A|B] ) :- !.
1696correct_list([A|B], [A|NB]) :- correct_list(B, NB).
1697
1699expression(X, InMap) --> dates(X, InMap).
1700
1703expression(X, InMap, In, Out) :- not(dates(X, InMap, In, Out)), expr(X, InMap, In, Out), !.
1704
1705expr(X, InMap) --> addExp(X, InMap).
1706
1708dates(DateInSeconds, _Map) --> [Year,'-', Month, '-', Day, THours,':', Minutes, ':', Seconds], spaces(_),
1709 { number(Year),number(Month),number(Day),number(Minutes),number(Seconds),
1710 pad_number(Year, 4, YearStr), pad_number(Month, 2, MonthStr), pad_number(Day, 2, DayStr), pad_number(Minutes, 2, MinutesStr), pad_number(Seconds, 2, SecondsStr),
1711 concat_atom([YearStr,'-', MonthStr, '-', DayStr, THours,':', MinutesStr, ':', SecondsStr], '', Date),
1712 parse_time(Date,DateInSeconds) 1713 }, !.
1715dates(DateInSeconds, _Map) --> [Year,'-', Month, '-', Day], spaces(_),
1716 { number(Year),number(Month),number(Day),
1717 pad_number(Year, 4, YearStr), pad_number(Month, 2, MonthStr), pad_number(Day, 2, DayStr),
1718 concat_atom([YearStr, '-', MonthStr, '-', DayStr], '', Date), parse_time(Date, DateInSeconds) }, !.
1719
1721addExp(X+Y, InMap) --> addExp(X, InMap), ['+'], mulExp(Y, InMap).
1722addExp(X-Y, InMap) --> addExp(X, InMap), ['-'], mulExp(Y, InMap).
1723addExp(Out, InMap) --> mulExp(Out, InMap).
1724
1725mulExp(X*Y, InMap) --> mulExp(X, InMap), ['*'], item(Y, InMap).
1726mulExp(X/Y, InMap) --> mulExp(X, InMap), ['/'], item(Y, InMap).
1727mulExp(Out, InMap) --> item(Out, InMap).
1728
1729item(Y, InMap) --> ['+'], item(X, InMap), {Y is +X}.
1730item(Y, InMap) --> ['-'], item(X, InMap), {Y is -X}.
1731item(Out, InMap) --> element(Out, InMap).
1732
1733element(X, _InMap) --> [X], {number(X)}, !.
1734element(X, _InMap) --> [le_string(X)], !.
1735element(X, InMap) --> ['('], addExp(X, InMap), [')'].
1736element(Var, InMap) --> variable_invocation(['+', '-', '*', '/', ')', '('], _Name, Var, InMap, InMap).
1740
1741element_string_list([H|T]) --> [H], element_string_list(T).
1742element_string_list([]) --> [].
1743
1745pad_number(Number, Width, Out) :-
1746 format(atom(Out), '~|~`0t~d~*+', [Number, Width]).
1747
1750binary_op(Op, In, Out) :-
1751 op2tokens(Op, OpTokens, _),
1752 append(OpTokens, Out, In),
1753 print_message(informational, "binary_op ~w ~w ~w"-[Op, In, Out]).
1754
1756op_tokens(Op, OpTokens) :-
1757 current_op(_Prec, Fix, Op), Op \= '.', 1758 (Fix = 'xfx'; Fix='yfx'; Fix='xfy'; Fix='yfy'),
1759 term_string(Op, OpString), tokenize(OpString, Tokens, [cased(true), spaces(true), numbers(false)]),
1760 unpack_tokens(Tokens, OpTokens).
1761
1781op2tokens(::,[:,:],[:,:]).
1782op2tokens(->,[-,>],[-,>]).
1783op2tokens(:,[:],[:]).
1785op2tokens(:=,[:,=],[:,=]).
1786op2tokens(==,[=,=],[=,=]).
1787op2tokens(:-,[:,-],[:,-]).
1788op2tokens(/\,[/,\],[/,\]).
1789op2tokens(=,[=],[=]).
1792op2tokens(=:=,[=,:,=],[=,:,=]).
1793op2tokens(=\=,[=,\,=],[=,\,=]).
1794op2tokens(xor,[xor],[xor]).
1796op2tokens(rdiv,[rdiv],[rdiv]).
1797op2tokens(>=,[>,=],[>,=]).
1798op2tokens(@<,[@,<],[@,<]).
1799op2tokens(@=<,[@,=,<],[@,=,<]).
1800op2tokens(=@=,[=,@,=],[=,@,=]).
1801op2tokens(\=@=,[\,=,@,=],[\,=,@,=]).
1802op2tokens(@>,[@,>],[@,>]).
1803op2tokens(@>=,[@,>,=],[@,>,=]).
1804op2tokens(\==,[\,=,=],[\,=,=]).
1805op2tokens(\=,[\,=],[\,=]).
1806op2tokens(>,[>],[>]).
1808op2tokens('|',['|'],['|']).
1809op2tokens(\/,[\,/],[\,/]).
1810op2tokens(+,[+],[+]).
1811op2tokens(>>,[>,>],[>,>]).
1812op2tokens(;,[;],[;]).
1813op2tokens(<<,[<,<],[<,<]).
1814op2tokens(:<,[:,<],[:,<]).
1815op2tokens(>:<,[>,:,<],[>,:,<]).
1816op2tokens(/,[/],[/]).
1817op2tokens(=>,[=,>],[=,>]).
1818op2tokens(=..,[=,.,.],[=,.,.]).
1819op2tokens(div,[div],[div]).
1820op2tokens(//,[/,/],[/,/]).
1821op2tokens(**,[*,*],[*,*]).
1822op2tokens(*,[*],[*]).
1823op2tokens(^,[^],[^]).
1824op2tokens(mod,[mod],[mod]).
1825op2tokens(-,[-],[-]).
1826op2tokens(*->,[*,-,>],[*,-,>]).
1827op2tokens(<,[<],[<]).
1828op2tokens(=<,[=,<],[=,<]).
1829op2tokens(-->,[-,-,>],[-,-,>]).
1830
1832op_stop_words(Words) :-
1833 op_stop(Words) -> true; (
1834 findall(Word,
1835 (current_op(_Prec, _, Op), Op \= '.', 1836 term_string(Op, OpString),
1837 tokenize(OpString, Tokens, [cased(true), spaces(true), numbers(false)]),
1838 unpack_tokens(Tokens, [Word|_])), Words), 1839 assertz(op_stop(Words))
1840 ), !.
1841
1843op_stop([
1844 1845 1846 1847 1848 1849 1850 1851 1852 (html_meta),
1853 1854 1855 1856 (+),
1857 1858 1859 1860 ($),
1861 (\),
1862 (=),
1863 (thread_initialization),
1864 (:),
1865 (\),
1866 '\'',
1867 (xor),
1868 (:),
1869 (rem),
1870 (\),
1871 1872 1873 (rdiv),
1874 (/),
1875 (>),
1876 (>),
1877 (=),
1878 (=),
1879 (;),
1880 1881 1882 (=),
1883 @,
1884 (\),
1885 (thread_local),
1886 (>),
1887 (=),
1888 (<),
1889 (*),
1890 '\'',
1891 (=),
1892 (\),
1893 (+),
1894 (:),
1895 (>),
1896 (div),
1897 1898 (<),
1899 (/),
1900 1901 (=),
1902 (-),
1903 1904 1905 (:),
1906 (*),
1907 ?,
1908 (/),
1909 (*),
1910 (-),
1911 1912 1913 (mod),
1914 (^)
1915 1916 ]).
1917
1918stop_words([], []).
1919stop_words([Word|_], [Word]) :- nonvar(Word). 1920stop_words([Word|_], []) :- var(Word).
1921
1923list_symbol('[').
1924list_symbol(']').
1925
1926parenthesis('(').
1927parenthesis(')').
1928
(_, [], [], []) :- !.
1930extract_literal(StopWords, [], [Word|RestOfWords], [Word|RestOfWords]) :-
1931 (member(Word, StopWords); that_(Word); phrase(newline, [Word])), !.
1932extract_literal(SW, RestName, [' '|RestOfWords], NextWords) :- !, 1933 extract_literal(SW, RestName, RestOfWords, NextWords).
1934extract_literal(SW, RestName, ['\t'|RestOfWords], NextWords) :- !,
1935 extract_literal(SW, RestName, RestOfWords, NextWords).
1936extract_literal(SW, [Word|RestName], [Word|RestOfWords], NextWords) :-
1937 extract_literal(SW, RestName, RestOfWords, NextWords).
1938
(_, Names, Names, Types, Types, [], []) :- !. 1943extract_variable_template(StopWords, Names, Names, Types, Types, [Word|RestOfWords], [Word|RestOfWords]) :- 1944 1945 (member(Word, StopWords); that_(Word); list_symbol(Word); punctuation(Word); phrase(newline, [Word])), !.
1946extract_variable_template(SW, InName, OutName, InType, OutType, [' '|RestOfWords], NextWords) :- !, 1947 extract_variable_template(SW, InName, OutName, InType, OutType, RestOfWords, NextWords).
1948extract_variable_template(SW, InName, OutName, InType, OutType, ['\t'|RestOfWords], NextWords) :- !, 1949 extract_variable_template(SW, InName, OutName, InType, OutType, RestOfWords, NextWords).
1950extract_variable_template(SW, InName, OutName, InType, OutType, [Word|RestOfWords], NextWords) :- 1951 ordinal(Word), !,
1952 extract_variable_template(SW, [Word|InName], OutName, InType, OutType, RestOfWords, NextWords).
1957extract_variable_template(SW, InName, [Word|OutName], InType, [Word|OutType], [Word|RestOfWords], NextWords) :- 1958 extract_variable_template(SW, InName, OutName, InType, OutType, RestOfWords, NextWords).
1959
(_, Names, Names, Types, Types, [], []) :- !. 1964extract_variable(_, _, _, _, _, [le_string(Word)|RestOfWords], [le_string(Word)|RestOfWords]) :- !. 1965extract_variable(StopWords, Names, Names, Types, Types, [Word|RestOfWords], [Word|RestOfWords]) :- 1966 1967 (member(Word, StopWords); that_(Word); list_symbol(Word); punctuation(Word); phrase(newline, [Word])), !.
1968extract_variable(SW, InName, OutName, InType, OutType, [' '|RestOfWords], NextWords) :- !, 1969 extract_variable(SW, InName, OutName, InType, OutType, RestOfWords, NextWords).
1970extract_variable(SW, InName, OutName, InType, OutType, ['\t'|RestOfWords], NextWords) :- !, 1971 extract_variable(SW, InName, OutName, InType, OutType, RestOfWords, NextWords).
1972extract_variable(SW, InName, OutName, InType, OutType, [Word|RestOfWords], NextWords) :- 1973 ordinal(Word), !,
1974 extract_variable(SW, [Word|InName], OutName, InType, OutType, RestOfWords, NextWords).
1975extract_variable(SW, InName, OutName, InType, OutType, [Word|RestOfWords], NextWords) :- 1976 is_a_type(Word),
1977 extract_variable(SW, InName, NextName, InType, OutType, RestOfWords, NextWords),
1978 (NextName = [] -> OutName = [Word]; OutName = NextName), !.
1979extract_variable(SW, InName, [Word|OutName], InType, [Word|OutType], [Word|RestOfWords], NextWords) :- 1980 not(number(Word)),
1981 extract_variable(SW, InName, OutName, InType, OutType, RestOfWords, NextWords).
1982
(_, [], [], []) :- !. 1987extract_expression(StopWords, [], [Word|RestOfWords], [Word|RestOfWords]) :- 1988 (member(Word, StopWords); that_(Word); list_symbol(Word); parenthesis(Word), phrase(newline, [Word])), !.
1989 1993extract_expression(SW, RestName, [' '|RestOfWords], NextWords) :- !, 1994 extract_expression(SW, RestName, RestOfWords, NextWords).
1995extract_expression(SW, RestName, ['\t'|RestOfWords], NextWords) :- !,
1996 extract_expression(SW, RestName, RestOfWords, NextWords).
1997extract_expression(SW, [Word|RestName], [Word|RestOfWords], NextWords) :-
1998 1999 2000 extract_expression(SW, RestName, RestOfWords, NextWords).
2001 2002
(_, [], [], []) :- !. 2006extract_constant(_, [], RestOfWords, RestOfWords). 2007extract_constant(StopWords, [], [Word|RestOfWords], [Word|RestOfWords]) :- 2008 2009 (member(Word, StopWords); that_(Word); list_symbol(Word); parenthesis(Word); punctuation(Word); phrase(newline, [Word])), !.
2013extract_constant(SW, RestName, [' '|RestOfWords], NextWords) :- !, 2014 extract_constant(SW, RestName, RestOfWords, NextWords).
2015extract_constant(SW, RestName, ['\t'|RestOfWords], NextWords) :- !,
2016 extract_constant(SW, RestName, RestOfWords, NextWords).
2017extract_constant(SW, [Word|RestName], [Word|RestOfWords], NextWords) :-
2018 2019 2020 extract_constant(SW, RestName, RestOfWords, NextWords).
2021
([], [], []) :- !.
2024extract_string([], [newline(A)|RestOfWords], [newline(A)|RestOfWords]):- !.
2025extract_string([String], InWords, NextWords) :-
2026 extract_all_string([newline(_), ',', '.'], Words, InWords, NextWords),
2027 concat_atom(Words, '', String).
2028 2029
(StopWords, [], [Word|RestOfWords], RestOfWords) :-
2031 member(Word, StopWords), !.
2032extract_all_string(StopWords, [Word|RestString], [Word|RestOfWords], NextWords) :-
2033 extract_all_string(StopWords, RestString, RestOfWords, NextWords ).
2034
(SW, [], Map, Map, [Word|Rest], [Word|Rest]) :-
2038 lists:member(Word, SW), !. 2040extract_list(SW, RestList, Map1, MapN, [' '|RestOfWords], NextWords) :- !, 2041 extract_list(SW, RestList, Map1, MapN, RestOfWords, NextWords).
2042extract_list(SW, RestList, Map1, MapN, [' '|RestOfWords], NextWords) :- !, 2043 extract_list(SW, RestList, Map1, MapN, RestOfWords, NextWords).
2044extract_list(SW, RestList, Map1, MapN, ['\t'|RestOfWords], NextWords) :- !,
2045 extract_list(SW, RestList, Map1, MapN, RestOfWords, NextWords).
2046extract_list(SW, RestList, Map1, MapN, [','|RestOfWords], NextWords) :- !, 2047 extract_list(SW, RestList, Map1, MapN, RestOfWords, NextWords).
2048extract_list(SW, RestList, Map1, MapN, ['|'|RestOfWords], NextWords) :- !, 2049 extract_list(SW, RestList, Map1, MapN, RestOfWords, NextWords).
2050extract_list(StopWords, List, Map1, MapN, [Det|InWords], LeftWords) :-
2051 phrase(indef_determiner, [Det|InWords], RInWords),
2052 extract_variable(['|'|StopWords], [], NameWords, [], _, RInWords, NextWords), NameWords \= [], 2053 name_predicate(NameWords, Name),
2054 update_map(Var, Name, Map1, Map2),
2055 (NextWords = [']'|_] -> (RestList = [], LeftWords=NextWords, MapN=Map2 ) ;
2056 extract_list(StopWords, RestList, Map2, MapN, NextWords, LeftWords) ),
2057 (RestList\=[] -> List=[Var|RestList]; List=[Var]),
2058 !.
2059extract_list(StopWords, List, Map1, MapN, [Det|InWords], LeftWords) :-
2060 phrase(def_determiner, [Det|InWords], RInWords),
2061 extract_variable(['|'|StopWords], [], NameWords, [], _, RInWords, NextWords), NameWords \= [], 2062 name_predicate(NameWords, Name),
2063 consult_map(Var, Name, Map1, Map2),
2064 (NextWords = [']'|_] -> (RestList = [], LeftWords=NextWords, MapN=Map2 ) ;
2065 extract_list(StopWords, RestList, Map2, MapN, NextWords, LeftWords) ),
2066 (RestList\=[] -> List=[Var|RestList]; List=[Var]), !.
2067extract_list(StopWords, List, Map1, MapN, InWords, LeftWords) :- 2068 extract_variable(['|'|StopWords], [], NameWords, [], _, InWords, NextWords), NameWords \= [], 2069 name_predicate(NameWords, Name),
2070 consult_map(Var, Name, Map1, Map2),
2071 (NextWords = [']'|_] -> (RestList = [], LeftWords=NextWords, MapN=Map2 ) ;
2072 extract_list(StopWords, RestList, Map2, MapN, NextWords, LeftWords) ),
2073 (RestList\=[] -> List=[Var|RestList]; List=[Var]), !.
2074extract_list(StopWords, List, Map1, Map1, InWords, LeftWords) :-
2075 extract_expression(['|',','|StopWords], NameWords, InWords, NextWords), NameWords \= [],
2076 ( phrase(expression(Expression, Map1), NameWords) -> true ; ( name_predicate_with_spaces(NameWords, Expression) ) ),
2077 ( NextWords = [']'|_] -> ( RestList = [], LeftWords=NextWords )
2078 ; extract_list(StopWords, RestList, Map1, Map1, NextWords, LeftWords) ),
2079 extend_list(RestList, Expression, List), !. 2080 2081 2082 2083
2084extend_list([A,B|R], X, List) :- append([X], [A,B|R], List).
2085extend_list([A], X, [X|[A]]).
2086extend_list([], X, [X]).
2087
2088determiner --> ind_det, !.
2089determiner --> ind_det_C, !.
2090determiner --> def_det, !.
2091determinar --> def_det_C.
2092
2093indef_determiner --> ind_det, !.
2094indef_determiner --> ind_det_C.
2095
2096def_determiner --> def_det, !.
2097def_determiner --> def_det_C.
2098
2099rebuild_template(RawTemplate, Map1, MapN, Template) :-
2100 template_elements(RawTemplate, Map1, MapN, [], Template).
2101
2103template_elements([], Map1, Map1, _, []).
2104template_elements([Word|RestOfWords], Map1, MapN, Previous, [Var|RestTemplate]) :-
2105 (phrase(ind_det, [Word|RestOfWords], RRestOfWords); phrase(ind_det_C,[Word|RestOfWords], RRestOfWords)), Previous \= [is|_],
2106 extract_variable([], [], NameWords, [], _, RRestOfWords, NextWords), !, 2107 name_predicate(NameWords, Name),
2108 update_map(Var, Name, Map1, Map2),
2109 template_elements(NextWords, Map2, MapN, [], RestTemplate).
2110template_elements([Word|RestOfWords], Map1, MapN, Previous, [Var|RestTemplate]) :-
2111 (phrase(def_det, [Word|RestOfWords], RRestOfWords); phrase(def_det_C,[Word|RestOfWords], RRestOfWords)), Previous \= [is|_],
2112 extract_variable([], [], NameWords, [], _, RRestOfWords, NextWords), !, 2113 name_predicate(NameWords, Name),
2114 member(map(Var,Name), Map1), 2115 template_elements(NextWords, Map1, MapN, [], RestTemplate).
2116template_elements([Word|RestOfWords], Map1, MapN, Previous, [Word|RestTemplate]) :-
2117 template_elements(RestOfWords, Map1, MapN, [Word|Previous], RestTemplate).
2118
2121update_map(V, Name, InMap, InMap) :-
2122 var(V), nonvar(Name), nonvar(InMap),
2123 member(map(O,Name), InMap), O\==V, fail, !.
2124update_map(V, Name, InMap, OutMap) :- 2125 var(V), nonvar(Name), nonvar(InMap),
2126 not(member(map(_,Name), InMap)),
2127 OutMap = [map(V,Name)|InMap].
2130
2133consult_map(V, Name, InMap, InMap) :-
2134 member(map(Var, SomeName), InMap), (Name == SomeName -> Var = V; ( Var == V -> Name = SomeName ; fail ) ), !.
2136
2137builtin_(BuiltIn, [BuiltIn1, BuiltIn2|RestWords], RestWords) :-
2138 atom_concat(BuiltIn1, BuiltIn2, BuiltIn),
2139 Predicate =.. [BuiltIn, _, _], 2140 predicate_property(system:Predicate, built_in), !.
2141builtin_(BuiltIn, [BuiltIn|RestWords], RestWords) :-
2142 Predicate =.. [BuiltIn, _, _], 2143 predicate_property(system:Predicate, built_in).
2144
2146time_of(P, T) :- P=..[_|Arguments], lists:append(_, [T], Arguments). 2147
2149unpack_tokens([], []).
2150unpack_tokens([cntrl(Char)|Rest], [newline(Next)|NewRest]) :- (Char=='\n' ; Char=='\r'), !,
2151 2152 update_nl_count(Next), unpack_tokens(Rest, NewRest).
2153unpack_tokens([First|Rest], [New|NewRest]) :-
2154 (First = word(New); First=cntrl(New); First=punct(New); First=space(New); First=number(New);
2155 (First=string(Content), New=le_string(Content)) 2156 ),
2157 2158 !,
2159 unpack_tokens(Rest, NewRest).
2160
2162update_nl_count(NN) :- retract(last_nl_parsed(N)), !, NN is N + 1, assert(last_nl_parsed(NN)).
2163
2164ordinal(Ord) :-
2165 ordinal(_, Ord).
2166
2167ordinal(1, 'first').
2168ordinal(2, 'second').
2169ordinal(3, 'third').
2170ordinal(4, 'fourth').
2171ordinal(5, 'fifth').
2172ordinal(6, 'sixth').
2173ordinal(7, 'seventh').
2174ordinal(8, 'eighth').
2175ordinal(9, 'ninth').
2176ordinal(10, 'tenth').
2178ordinal(1, 'premier').
2179ordinal(2, 'seconde').
2180ordinal(3, 'troisième').
2181ordinal(4, 'quatrième').
2182ordinal(5, 'cinquième').
2183ordinal(6, 'sixième').
2184ordinal(7, 'septième').
2185ordinal(8, 'huitième').
2186ordinal(9, 'neuvième').
2187ordinal(10, 'dixième').
2189ordinal(1, 'primero').
2190ordinal(2, 'segundo').
2191ordinal(3, 'tercero').
2192ordinal(4, 'cuarto').
2193ordinal(5, 'quinto').
2194ordinal(6, 'sexto').
2195ordinal(7, 'séptimo').
2196ordinal(8, 'octavo').
2197ordinal(9, 'noveno').
2198ordinal(10, 'decimo').
2200ordinal(1, 'primera').
2201ordinal(2, 'segunda').
2202ordinal(3, 'tercera').
2203ordinal(4, 'cuarta').
2204ordinal(5, 'quinta').
2205ordinal(6, 'sexta').
2206ordinal(7, 'séptima').
2207ordinal(8, 'octava').
2208ordinal(9, 'novena').
2209ordinal(10, 'decima').
2210
2212is_a_type(T) :- 2213 2214 (is_type(T); pre_is_type(T)), !.
2215 2216 2217 2218 2219 2220
2222
2223ind_det_C --> ['A'].
2224ind_det_C --> ['An'].
2225ind_det_C --> ['Un']. 2226ind_det_C --> ['Una']. 2227ind_det_C --> ['Une']. 2228ind_det_C --> ['Qui']. 2229ind_det_C --> ['Quoi']. 2230ind_det_C --> ['Uno']. 2231ind_det_C --> ['Che']. 2232ind_det_C --> ['Quale']. 2234ind_det_C --> ['Each']. 2235ind_det_C --> ['Which']. 2236ind_det_C --> ['CuĂ¡l']. 2237
2238def_det_C --> ['The'].
2239def_det_C --> ['El']. 2240def_det_C --> ['La']. 2241def_det_C --> ['Le']. 2242def_det_C --> ['L'], [A], {atom_string(A, "'")}. 2243def_det_C --> ['Il']. 2244def_det_C --> ['Lo']. 2245
2246ind_det --> [a].
2247ind_det --> [an].
2248ind_det --> [another]. 2249ind_det --> [which]. 2250ind_det --> [each]. 2251ind_det --> [un]. 2252ind_det --> [una]. 2253ind_det --> [une]. 2254ind_det --> [qui]. 2255ind_det --> [quel]. 2256ind_det --> [quelle]. 2257ind_det --> [che]. 2258ind_det --> [quale]. 2259ind_det --> [uno]. 2260ind_det --> ['cuĂ¡l']. 2262
2263def_det --> [the].
2264def_det --> [el]. 2265def_det --> [la]. 2266def_det --> [le]. 2267def_det --> [l], [A], {atom_string(A, "'")}. 2268def_det --> [il]. 2269def_det --> [lo]. 2270
2272reserved_word(W) :- 2273 W = 'is'; W ='not'; W='if'; W='If'; W='then'; W = 'where'; W = '&'; 2274 W = 'at'; W= 'from'; W='to'; W='half'; 2275 W = 'else'; W = 'otherwise';
2276 W = such ;
2277 W = '<'; W = '='; W = '>'; W = '+'; W = '-'; W = '/'; W = '*'; 2278 W = '{' ; W = '}' ; W = '(' ; W = ')' ; W = '[' ; W = ']',
2279 W = ':', W = ','; W = ';'. 2280reserved_word(P) :- punctuation(P).
2281
2282that_(that).
2283that_('That').
2284
2287
2288punctuation('.').
2289punctuation(',').
2290punctuation(';').
2292punctuation('\'').
2293
2295verb(Verb) :- present_tense_verb(Verb); continuous_tense_verb(Verb); past_tense_verb(Verb).
2296
2297present_tense_verb(is).
2298present_tense_verb(complies).
2299present_tense_verb(does).
2300present_tense_verb(occurs).
2301present_tense_verb(meets).
2302present_tense_verb(relates).
2303present_tense_verb(can).
2304present_tense_verb(qualifies).
2305present_tense_verb(has).
2306present_tense_verb(satisfies).
2307present_tense_verb(owns).
2308present_tense_verb(belongs).
2309present_tense_verb(applies).
2310present_tense_verb(must).
2311present_tense_verb(acts).
2312present_tense_verb(falls).
2313present_tense_verb(corresponds).
2314present_tense_verb(likes).
2315
2316continuous_tense_verb(according).
2317continuous_tense_verb(beginning).
2318continuous_tense_verb(ending).
2319
2320past_tense_verb(spent).
2321past_tense_verb(looked).
2322past_tense_verb(could).
2323past_tense_verb(had).
2324past_tense_verb(tried).
2325past_tense_verb(explained).
2326past_tense_verb(ocurred).
2327
2329preposition(of).
2331preposition(from).
2332preposition(to).
2333preposition(at).
2334preposition(in).
2335preposition(with).
2336preposition(plus).
2337preposition(as).
2338preposition(by).
2339
2341assertall([]).
2342assertall([F|R]) :-
2343 not(asserted(F)),
2344 2345 assertz(F), !,
2346 assertall(R).
2347assertall([_F|R]) :-
2348 assertall(R).
2349
2350asserted(F :- B) :- clause(F, B). 2351asserted(F) :- clause(F,true). 2352
2354currentLine(LineNumber, Rest, Rest) :-
2355 once( nth1(_,Rest,newline(NextLine)) ), LineNumber is NextLine-2.
2356
2359assert_error_os([]) :- !.
2360assert_error_os([error(Message, LineNumber, Tokens)|Re]) :-
2361 asserta(error_notice(error, Message, LineNumber, Tokens)),
2362 assert_error_os(Re).
2363
2364asserterror(Me, Rest) :-
2365 2366 2367 2368 once( nth1(N,Rest,newline(NextLine)) ), LineNumber is NextLine-2,
2369 RelevantN is N-1,
2370 length(Relevant,RelevantN), append(Relevant,_,Rest),
2371 findall(Token, (member(T,Relevant), (T=newline(_) -> Token='\n' ; Token=T)), Tokens),
2372 asserta(error_notice(error, Me, LineNumber, Tokens)). 2373
2375select_first_section([], _, []) :- !.
2376select_first_section(_, 0, []) :- !.
2377select_first_section([E|R], N, [E|NR]) :-
2378 N > 0, NN is N - 1,
2379 select_first_section(R, NN, NR).
2380
2381showErrors(File,Baseline) :- 2382 findall(error_notice(error, Me,Pos, ContextTokens),
2383 error_notice(error, Me,Pos, ContextTokens), ErrorsList),
2384 deepest(ErrorsList,
2385 error_notice(error, 'None',0, ['There was no syntax error']),
2386 error_notice(error, MeMax,PosMax, ContextTokensMax)),
2387 atomic_list_concat([MeMax,': '|ContextTokensMax],ContextTokens_),
2388 Line is PosMax+Baseline,
2389 print_message(error,error(syntax_error(ContextTokens_),file(File,Line,_One,_Char))).
2390 2391 2392 2393 2394 2395 2396
2397deepest([], Deepest, Deepest) :- !.
2398deepest([error_notice(error, Me,Pos, ContextTokens)|Rest],
2399 error_notice(error,_Me0, Pos0,_ContextTokens0), Out) :-
2400 Pos0 < Pos, !,
2401 deepest(Rest, error_notice(error, Me,Pos, ContextTokens), Out).
2402deepest([_|Rest], In, Out) :-
2403 deepest(Rest, In, Out).
2404
2405showProgress :-
2406 findall(error_notice(error, Me,Pos, ContextTokens),
2407 error_notice(error, Me,Pos, ContextTokens), ErrorsList),
2408 deepest(ErrorsList,
2409 error_notice(error, 'None',0, ['There was no syntax error']),
2410 error_notice(error, MeMax,PosMax, ContextTokensMax)),
2411 atomic_list_concat([MeMax,': '|ContextTokensMax],ContextTokens_),
2412 Line is PosMax+1,
2413 print_message(informational,error(syntax_error(ContextTokens_),file(someFile,Line,_One,_Char))).
2414
2415
2416spypoint(A,A). 2417
2421meta_dictionary(Predicate, VariablesNames, Template) :-
2422 meta_dict(Predicate, VariablesNames, Template) ; predef_meta_dict(Predicate, VariablesNames, Template).
2423
2424:- discontiguous predef_meta_dict/3. 2425predef_meta_dict([\=, T1, T2], [first_thing-time, second_thing-time], [T1, is, different, from, T2]).
2426predef_meta_dict([=, T1, T2], [first_thing-time, second_thing-time], [T1, is, equal, to, T2]).
2427predef_meta_dict([nonvar, T1], [thing_1-thing], [T1, is, known]). 2428
2435dictionary(Predicate, VariablesNames, Template) :- 2436 dict(Predicate, VariablesNames, Template) ; predef_dict(Predicate, VariablesNames, Template).
2438
2439:- discontiguous predef_dict/3. 2478predef_dict([has_affiliated_with_at, _A, B, C], [entity-entity, affiliate-affiliate, date-date], [who, affiliated, with, B, at, C]).
2479predef_dict([has_affiliated_with_at, _A, B, C], [entity-entity, affiliate-affiliate, date-date], [what, entity, affiliated, with, B, at, C]).
2480predef_dict([has_affiliated_with_at, A, B, _C], [entity-entity, affiliate-affiliate, date-date], [when, did, A, affiliate, with, B]).
2482predef_dict([has_affiliated_with_at, A, B, _C], [entity-entity, affiliate-affiliate, date-date], [on, what, date, did, A, affiliate, with, B]).
2483predef_dict([has_affiliated_with_at, A, B, _C], [entity-entity, affiliate-affiliate, date-date], [is, there, an, affiliation, between, A, and, B]).
2484predef_dict([has_affiliated_with_at, A, B, _C], [entity-entity, affiliate-affiliate, date-date], [when, did, the, affiliation, between, A, and, B, begin]).
2486predef_dict([is_of_type, Object, Type], [object-object, type-type], [Object, is, of, type, Type]). 2487predef_dict([is_a, Object, Type], [object-object, type-type], [Object, is, an, Type]). 2488predef_dict([is_a, Object, Type], [object-object, type-type], [Object, is, a, Type]). 2489predef_dict([is_a, Object, Type], [object-object, type-type], [Object, is, of, Type]).
2490
2492predef_dict(A,B,C) :- prolog_predef_dict(A,B,C).
2493
2494prolog_predef_dict([length, List, Length], [member-object, list-list], [the, length, of, List, is, Length]).
2495prolog_predef_dict([bagof, Thing, Condition, Bag], [bag-thing, thing-thing, condition-condition], [Bag, is, a, bag, of, Thing, such, that, Condition]).
2496prolog_predef_dict([has_as_head_before, A, B, C], [list-list, symbol-term, rest_of_list-list], [A, has, B, as, head, before, C]).
2497prolog_predef_dict([append, A, B, C],[first_list-list, second_list-list, third_list-list], [appending, A, then, B, gives, C]).
2498prolog_predef_dict([reverse, A, B], [list-list, other_list-list], [A, is, the, reverse, of, B]).
2499prolog_predef_dict([same_date, T1, T2], [time_1-time, time_2-time], [T1, is, the, same, date, as, T2]). 2500prolog_predef_dict([between,Minimum,Maximum,Middle], [min-date, max-date, middle-date],
2501 [Middle, is, between, Minimum, &, Maximum]).
2502prolog_predef_dict([is_1_day_after, A, B], [date-date, second_date-date],
2503 [A, is, '1', day, after, B]).
2504prolog_predef_dict([is_days_after, A, B, C], [date-date, number-number, second_date-date],
2505 [A, is, B, days, after, C]).
2506prolog_predef_dict([immediately_before, T1, T2], [time_1-time, time_2-time], [T1, is, immediately, before, T2]). 2507prolog_predef_dict([\=, T1, T2], [thing_1-thing, thing_2-thing], [T1, is, different, from, T2]).
2508prolog_predef_dict([==, T1, T2], [thing_1-thing, thing_2-thing], [T1, is, equivalent, to, T2]).
2509prolog_predef_dict([is_not_before, T1, T2], [time1-time, time2-time], [T1, is, not, before, T2]). 2510prolog_predef_dict([=, T1, T2], [thing_1-thing, thing_2-thing], [T1, is, equal, to, T2]).
2511prolog_predef_dict([isbefore, T1, T2], [time1-time, time2-time], [T1, is, before, T2]). 2512prolog_predef_dict([isafter, T1, T2], [time1-time, time2-time], [T1, is, after, T2]). 2513prolog_predef_dict([member, Member, List], [member-object, list-list], [Member, is, in, List]).
2515prolog_predef_dict([nonvar, T1], [thing_1-thing], [T1, is, known]). 2516prolog_predef_dict([=, T1, T2], [thing_1-thing, thing_2-thing], [T1, is, T2]). 2519prolog_predef_dict([\=@=, T1, T2], [thing_1-thing, thing_2-thing], [T1, \,=,@,=, T2]).
2520prolog_predef_dict([\==, T1, T2], [thing_1-thing, thing_2-thing], [T1, \,=,=, T2]).
2521prolog_predef_dict([=\=, T1, T2], [thing_1-thing, thing_2-thing], [T1, =,\,=, T2]).
2522prolog_predef_dict([=@=, T1, T2], [thing_1-thing, thing_2-thing], [T1, =,@,=, T2]).
2523prolog_predef_dict([==, T1, T2], [thing_1-thing, thing_2-thing], [T1, =,=, T2]).
2524prolog_predef_dict([=<, T1, T2], [thing_1-thing, thing_2-thing], [T1, =,<, T2]).
2525prolog_predef_dict([=<, T1, T2], [thing_1-thing, thing_2-thing], [T1, =,<, T2]).
2526prolog_predef_dict([>=, T1, T2], [thing_1-thing, thing_2-thing], [T1, >,=, T2]).
2527prolog_predef_dict([is, T1, T2], [thing_1-thing, thing_2-thing], [T1, =, T2]).
2528prolog_predef_dict([<, T1, T2], [thing_1-thing, thing_2-thing], [T1, <, T2]).
2529prolog_predef_dict([>, T1, T2], [thing_1-thing, thing_2-thing], [T1, >, T2]).
2530prolog_predef_dict([unparse_time, Secs, Date], [secs-time, date-date], [Secs, corresponds, to, date, Date]).
2533
2535pre_is_type(thing).
2536pre_is_type(time).
2537pre_is_type(type).
2538pre_is_type(object).
2539pre_is_type(date).
2540pre_is_type(day).
2541pre_is_type(person).
2542pre_is_type(list).
2543pre_is_type(number).
2544
2546must_be(A, var) :- var(A).
2547must_be(A, nonvar) :- nonvar(A).
2548must_be_nonvar(A) :- nonvar(A).
2549must_not_be(A,B) :- not(must_be(A,B)).
2550
2551has_as_head_before([B|C], B, C).
2552
2555
2556matches_name(Word, [Element|_], [Name-_|_], Name) :- Word == Element, !.
2557matches_name(Word, [_|RestElem], [_|RestTypes], Name) :-
2558 matches_name(Word, RestElem, RestTypes, Name).
2559
2560matches_type(Word, [Element|_], [_-Type|_], Type) :- Word == Element, !.
2561matches_type(Word, [_|RestElem], [_|RestTypes], Type) :-
2562 matches_type(Word, RestElem, RestTypes, Type).
2563
2564delete_underscore([], []) :- !.
2565delete_underscore(['_'|Rest], Final) :- delete_underscore(Rest, Final), !.
2566delete_underscore([W|Rest], [W|Final]) :- delete_underscore(Rest, Final).
2567
2568add_determiner([Word|RestWords], [Det, Word|RestWords]) :-
2569 name(Word,[First|_]), proper_det(First, Det).
2570
2571proper_det(97, an) :- !.
2572proper_det(101, an) :- !.
2573proper_det(105, an) :- !.
2574proper_det(111, an) :- !.
2575proper_det(117, an) :- !.
2576proper_det(_, a).
2577
2578filtered_dictionary(Pred) :-
2579 dictionary(PredicateElements, _, _),
2580 PredicateElements\=[],
2581 not(le_input:prolog_predef_dict(PredicateElements, _, _)), 2582 Pred=..PredicateElements.
2583
2585
2586sandbox:safe_primitive(le_input:source_lang(_)).
2587sandbox:safe_primitive(le_input:is_type(_)).
2588sandbox:safe_primitive(le_input:dict(_,_,_)).
2589sandbox:safe_primitive(le_input:meta_dict(_,_,_)).
2590sandbox:safe_primitive(le_input:assertall(_)).
2591sandbox:safe_primitive(le_input:asserted(_))