3:-module(nal_reader,[
4 test_nal/0,
5 test_nal/1,
6 7 8 call_nal/3
9 ]). 10
11:- set_module(class(library)). 12:- set_module(base(system)). 13
14:- use_module(library(logicmoo_common)). 15
16:- use_module(library(logicmoo/dcg_meta)). 17:- use_module(library(narsese)). 18
97
98task(S)--> cwhite,!,task(S),!.
99task(task(X,S,T,O,B)) --> task(X,S,T,O,B),!.
100
101
102
103task(X,S,T,O,B) --> optional(B, budget),!, sentence(X,S,T,O). 104
105
106sentence(X,S,T,O)--> statement(S), post_statement(X,T,O).
107
108post_statement(X,T,O)-->
109 o(`.` ,X, judgement)-> optional(T,tense)-> optional(O,truth),! 110 ; o(`?` ,X, question_truth)-> optional(T,tense)-> optional(O,truth),! 111 ; o(`!` ,X, goal), optional(O,desire) 112 ; o(`@` ,X, question_desire), optional(O,desire) 113 .
114
115statement(S)--> mw(statement0(S)),!.
116statement0(S)-->
117 mw(`<`) ,!, term(A), copula(R), term(B), mw(`>`) , {S=..[R,A,B]} 118 ; l_paren, `^` , nars_term_list(L), paren_r, {S= exec(L)} 119 ; l_paren, term(A), copula(R), term(B), paren_r, {S=..[R,A,B]} 120 ; nars_word(A), l_paren, nars_term_list(L), paren_r, {S= exec([A|L])} 121 ; nal_term1(X), {S= named_statement(X)} 122 .
123
124
125copula(X) -->
126 o(`-->` ,X, inheritance )
127 ; o(`<->` ,X, similarity )
128 ; o(`{--` ,X, instance )
129 ; o(`--]` ,X, property )
130 ; o(`{-]` ,X, inst_prop )
131 ; o(`==>` ,X, implication )
132 ; o(`=/>` ,X, predictive_impl )
133 ; o(`=|>` ,X, concurrent_impl )
134 ; o(`=\\>` ,X, retrospective_impl )
135 ; o(`<=>` ,X, equiv )
136 ; o(`</>` ,X, predictive_equiv )
137 ; o(`<|>` ,X, concurrent_equiv )
138 ; o(`=>` ,X, unknown_impl )
139 .
140
141term(S)--> nars_word(S) 142 ; nars_variable(S) 143 ; compound_term(S) 144 ; statement(S) 145 .
146
147term0(S)--> word0(S) 148 ; variable0(S) 149 ; compound_term0(S) 150 ; statement0(S) 151 .
152
153nal_term1(S)--> nars_word(S) 154 ; nars_variable(S) 155 ; compound_term(S) 156 .
157
158compound_term(X)--> mw(compound_term0(X)).
159
160compound_term0('exec'([S]))--> `^`,!,nal_term1(S).
161compound_term0(S)--> \+ dcg_peek(`<`),!,
162 ( o(op_ext_set,X,ext_set), nars_term_list(L), `}` 163 ; o(op_int_set,X,int_set), nars_term_list(L), `]` 164
165 ; word0(A), `[`, nars_term_list(L), `]`, {S= v(A,L)} 166 ; o(op_negation,X,negation), term(AB),{L=[AB]} 167 ; l_paren, paren_compound_term(X,L), paren_r
168 ), {S=..[X,L]}.
169
170paren_compound_term(X,L) -->
171 op_multi(X), comma, nars_term_list(L) 172 ; op_single(X), comma, term(A), comma, term(B), {L=[A,B]} 173 ; o(op_ext_image,X,ext_image), comma, nars_term_list(L) 174 ; o(op_int_image,X,int_image), comma, nars_term_list(L) 175 ; o(op_negation,X,negation), comma, term(AB),{L=[AB]} 176 ; term(A), op_multi(X), term(B),{L=[A,B]} 177 ; term(A), op_single(X), term(B),{L=[A,B]} 178 ; preserve_whitespace((term0(A), cspace, {X=rel}, term_list_sep(SL, ` `))),{L=[A|SL]}
179 ; {X=product}, nars_term_list(L) 180 .
181
182op_int_set-->`[`. 183op_ext_set-->`{`. 184op_negation-->`--`. 185op_int_image-->`\\`. 186op_ext_image-->`/`. 187
188
189preserve_whitespace(DCG,S,E) :- locally(b_setval(whitespace,preserve),phrase(DCG,S,E)).
190no_preserve_whitespace(DCG,S,E) :- phrase(DCG,S,E).
191
192
193op_multi(X)-->
194 o(`&&` ,X, and) 195 ; o(`*` ,X, product) 196 ; o(`||` ,X, or) 197 ; o(`#` ,X, sequence_spatial) 198 ; o(`&|` ,X, parallel_evnts) 199 ; o(`&/` ,X, sequence_evnts) 200 ; o(`|` ,X, int_intersection) 201 ; o(`&` ,X, ext_intersection) 202 .
203op_single(X) -->
204 o(`-`, X, ext_difference) 205 ; o(`~`, X, int_difference) 206 .
207
208nars_variable(V)--> mw(variable0(V)).
209
210variable0(var(X,W))
211 -->o(`$`, X, ind), word0(W) 212 ;o(`#`, X, dep), word0(W) 213 ;o(`?`, X, query), word0(W) 214 ;o(`/`, X, arg), word0(W) 215 .
216
217variable0(('_')) --> `_`.
218variable0(('#')) --> `#`.
219variable0(('$')) --> `$`.
220
221
222tense(X) -->
223 o(`:/:`, X, future) 224 ; o(`:|:`, X, present) 225 ; o(`:\\:`, X, past) 226 .
227tense('t!'(X)) --> `:!`, number(X), `:`.
228tense('t'(X)) --> `:`, nal_term1(X), `:`.
229
231desire(D)-->truth(D).
233truth([F,C])--> `%`, !, frequency(F), optional((`;`, confidence(C))), `%`.
234truth([F,C])--> `{`, !, frequency(F), confidence(C), `}`.
236budget(budget_pdq(P,D,Q))--> `$`,!, priority(P), optional(( `;`, durability(D))), optional((`;`, quality(Q))), `$`.
237
238
239nars_word(E) --> mw(word0(E)).
240
241word0(E) --> dcg_basics:number(E),!.
242word0(E) --> quoted_string(E),!.
243word0(E) --> dcg_peek([C]),{char_type(C,alpha)},!, nars_rsymbol([],E),!.
244
245
246 priority(F) --> float_inclusive(0,1,F). 247durability(F) --> float_exclusive(0,1,F). 248 quality(F) --> float_inclusive(0,1,F). 249 frequency(F) --> float_inclusive(0,1,F). 250confidence(F) --> float_exclusive(0,1,F). 251
252o(S,X,X) --> owhite,S,owhite.
253o(X,X) --> o(X,X,X).
254
255float_inclusive(L,H,F)--> mw((dcg_basics:number(F) -> {warn_if_strict((L=< F,F=< H))})).
256float_exclusive(L,H,F)--> mw((dcg_basics:number(F) -> {warn_if_strict((L < F,F < H))})).
257
258
259
260warn_if_strict(G):- call(G),!.
261warn_if_strict(G):- dmsg(warn_if_strict(G)),!.
262
263:- set_dcg_meta_reader_options(file_comment_reader, nars_comment_expr). 264
265
(X) --> cspace,!,nars_comment_expr(X).
267nars_comment_expr('$COMMENT'(Expr,I,CP)) --> nars_comment_expr_3(Expr,I,CP),!.
268
(T,N,CharPOS) --> `/*`, !, my_lazy_list_location(file(_,_,N,CharPOS)),!, zalwayz(read_string_until_no_esc(S,`*/`)),!,
270 {text_to_string_safe(S,T)},!.
271nars_comment_expr_3(T,N,CharPOS) --> {cmt_until_eoln(Text)},Text,!, my_lazy_list_location(file(_,_,N,CharPOS)),!,zalwayz(read_string_until_no_esc(S,eoln)),!,
272 {text_to_string_safe(S,T)},!.
273
274
275cmt_until_eoln(`//`).
276cmt_until_eoln(`'`).
277cmt_until_eoln(`**`).
278
279
280comma --> mw(`,`).
281l_paren --> mw(`(`).
282paren_r --> mw(`)`).
283
284term_list_sep([H|T], Sep) --> term0(H), ( (Sep,owhite) -> term_list_sep(T, Sep) ; ({T=[]},owhite)).
285nars_term_list([H|T]) --> term(H), ( comma -> nars_term_list(T) ; {T=[]} ).
286
287
288nars_rsymbol(Chars,E) --> [C], {notrace(nars_sym_char(C))},!, nars_sym_continue(S), {append(Chars,[C|S],AChars),string_to_atom(AChars,E)},!.
289nars_sym_continue([]) --> nars_peek_symbol_breaker,!.
290nars_sym_continue([H|T]) --> [H], {nars_sym_char(H)},!, nars_sym_continue(T).
291nars_sym_continue([]) --> [].
292
293nars_peek_symbol_breaker --> dcg_peek(`--`).
294nars_peek_symbol_breaker --> dcg_peek(`-`),!,{fail}.
295nars_peek_symbol_breaker --> dcg_peek(one_blank).
296nars_peek_symbol_breaker --> dcg_peek([C]),{\+ nars_sym_char(C)},!.
297
298nars_sym_char(C):- \+ integer(C),!,char_code(C,D),!,nars_sym_char(D).
299nars_sym_char(C):- bx(C =< 32),!,fail.
302nars_sym_char(C):- never_symbol_char(NeverSymbolList),memberchk(C,NeverSymbolList),!,fail. 304nars_sym_char(_):- !.
305
306never_symbol_char(`";()~'[]<>``{},=\\^`).
307
308
309nars_rsymbol_cont(Prepend,E) --> nars_sym_continue(S), {append(Prepend,S,AChars),string_to_atom(AChars,E)},!.
310
311
312is_nal_test_file(X):-filematch('../../nal-tests/**/*',X), \+ non_nal_file(X).
313is_nal_test_file(X):-filematch('../../examples/**/*',X), \+ non_nal_file(X).
314non_nal_file(X):- downcase_atom(X,DC),X\==DC,!,non_nal_file(DC).
315non_nal_file(X):- atom_concat(readme,_,X).
316non_nal_file(X):- atom_concat(_,'.pl',X).
317
318test_nal_file:-
319 make,
320 catch((
321 forall(is_nal_test_file(X),((dmsg(file_begin(X)),ignore(test_nal_file(X)),dmsg(file_end(X)))))),
322 '$aborted',true).
323
324test_nal_file(File):- (\+ atom(File); \+ is_absolute_file_name(File)),
325 absolute_file_name(File,Absolute), !, test_nal_file(Absolute).
326test_nal_file(File):- open(File,read,In),
327 read_nal_clauses(In, Expr),!,
328 must_or_rtrace(call_nal(test_nal_file,Expr,OutL)),!,
329 flatten([OutL],Out),
330 maplist(wdmsg,Out),!.
331
332
333file_nal(end_of_file) --> file_eof,!.
335file_nal(O) --> cwhite,!,file_nal(O).
336file_nal([]) --> \+ dcg_peek([_]),!.
337file_nal(outputMustContain(O)) --> `''outputMustContain('`, read_string_until(Str,`')`),{phrase(task(O),Str,[])}.
338file_nal('1Answer'(O)) --> `' Answer `, read_string_until(Str,(`{`,read_string_until(_,eoln))),{phrase(task(O),Str,[])}.
342file_nal(do_steps(N)) --> dcg_basics:number(N),!.
343file_nal(N=V) --> mw(`*`), nars_word(N), mw(`=`), term(V).
344file_nal(nal_in(H,V3)) --> `IN:`, task(H), optional(three_vals(V3)).
345file_nal(nal_out(H,V3)) --> `OUT:`, task(H), optional(three_vals(V3)).
346file_nal(H) --> task(H).
347file_nal(term(H)) --> term(H).
348file_nal(english(Text)) --> read_string_until_no_esc(Str,eoln),
349 {atom_string(Str,Text)},!. 350
352three_vals(V3)--> `{`, read_string_until_no_esc(Str,(`}`;eoln)),
353 {read_term_from_codes(Str,V3,[double_quotes(string),syntax_errors(fail)])},!.
354
355
357
358
359:- thread_local(t_l:sreader_options/2). 360
361
362a_nal_test("'the detective claims that tim lives in graz").
363
364a_nal_test("'Revision ------
365
366'Bird is a type of swimmer.
367<bird --> swimmer>.
368
369'Bird is probably not a type of swimmer.
370<bird --> swimmer>. %0.10;0.60%
371
3721
373
374'Bird is very likely to be a type of swimmer.
375''outputMustContain('<bird --> swimmer>. %0.87;0.91%')").
376
377a_nal_test("
378
379'the detective claims that tim lives in graz
380'<{tim} --> (/,livingIn,_,{graz})>.
381'and lawyer claims that this is not the case
382<{tim} --> (/,livingIn,_,{graz})>. %0%
383100
384'the first deponent, a psychologist,
385'claims that people with sunglasses are more aggressive
386<<(*,$1,sunglasses) --> own> ==> <$1 --> [aggressive]>>.
387'the third deponent claims, that he has seen tom with sunglasses on:
388<(*,{tom},sunglasses) --> own>.
389'the teacher claims, that people who are aggressive tend to be murders
390<<$1 --> [aggressive]> ==> <$1 --> murder>>.
391'the second deponent claims, that if the person lives in Graz, he is surely the murder
392<<$1 --> (/,livingIn,_,{graz})> ==> <$1 --> murder>>.
393'who is the murder?
394<{?who} --> murder>?
395''outputMustContain('<{tom} --> murder>. %1.00;0.73%')
396
397").
398
399
400
401test_nal:- forall(a_nal_test(Test),test_nal(Test)).
402
403
404:- use_module(library(dcg/basics)). 405
407test_nal(Test):- call_nal('dmsg',Test,Out),dmsg(Out).
408
409
410nars_zave_varname(N,V):- debug_var(N,V),!.
412
419
420read_nal_clauses( Text, Out):-
421 findall(Cl,read_nal_clause(Text, Cl), OutL),
422 flatten([OutL],Out).
423
424read_nal_clause( NonStream, Out):- \+ is_stream(NonStream), !, 425 must_or_rtrace((open_string(NonStream,Stream), read_nal_clause(Stream, Out))).
426
427read_nal_clause(Stream, Out):-
428 '$current_typein_module'(M),
429 M\== input, !,
430 setup_call_cleanup(
431 '$set_typein_module'(input),
432 read_nal_clause(Stream, Out),
433 '$set_typein_module'(M)).
434
435read_nal_clause(Stream, Out):-
436 op(601, xfx, input:(/)),
437 op(601, xfx, input:(\\)),
438 (at_end_of_stream(Stream)-> Out=[];
439 (read_nal_term(Stream, Term),
440 (Term == end_of_file -> Out=[];
441 (Term = (:- Exec) -> (input:call(Exec), Out=More) ; Out = [Term|More]),
442 read_nal_clause(Stream, More)))).
443
444read_nal_term(In,Expr):-
445 notrace(( is_stream(In),
446 remove_pending_buffer_codes(In,Codes),
447 read_codes_from_pending_input(In,Text), Text\==[])), !,
448 call_cleanup(parse_meta_ascii(file_nal, Text,Expr),
449 append_buffer_codes(In,Codes)).
450read_nal_term(Text,Expr):-
451 notrace(( =( ascii_,In),
452 remove_pending_buffer_codes(In,Codes))),
453 call_cleanup(parse_meta_ascii(file_nal, Text,Expr),
454 append_buffer_codes(In,Codes)).
455
457call_nal(Ctx, Stream, Out):- \+ compound(Stream),
458 must_or_rtrace(read_nal_clauses(Stream, List)), !,
459 call_nal(Ctx, List, Out).
460
461call_nal(Ctx, List, Out):- is_list(List),!, maplist(call_nal(Ctx),List, OutL),flatten(OutL,Out).
462call_nal(Ctx, InnerCtx=json(List), Out):- !, call_nal([InnerCtx|Ctx], List, Out).
463
464call_nal(Ctx, List, Out):-
465 sub_term(Sub, List), nonvar(Sub),
466 rule_rewrite(Ctx, Sub, NewSub),
467 468 nonvar(NewSub), Sub\==NewSub,
469 subst(List, Sub, NewSub, NewList),
470 List\==NewList, !,
471 call_nal(Ctx, NewList, Out).
472
473call_nal(_Ctx, List, Out):- flatten([List], Out),!.
474
475
476
477
478rule_rewrite(_Ctx, json(Replace), Replace):- nonvar(Replace),!.
479
480
481nars_join_atomics(Sep,List,Joined):- atomics_to_string(List,Sep,Joined).
482
502
503:- fixup_exports.