1:- module('plammar/pt_ast', [
2 pt_ast/5
3 ]). 4
5:- use_module(library(lists), [append/3]). 6:- use_module(library(option), [option/3]). 7
8:- use_module(util). 9:- use_module(state). 10:- use_module(format_space). 11:- use_module(format_check). 12
13:- discontiguous
14 pt_ast/5,
15 pt_kind/6,
16 pt/5. 17
19pt_ast(Opts, S0, SN, prolog([shebang(['#','!',comment_text(Atom,_),_])|PT_List]), prolog([shebang(Atom)|AST_List])) :-
20 !,
21 check(Opts, S0, S1, shebang),
22 state_space(S1, S2, rows(1)),
23 pt_kind(Opts, S2, SN, prolog, PT_List, AST_List).
24pt_ast(Opts, S0, SN, prolog(PT_List), prolog(AST_List)) :-
25 pt_kind(Opts, S0, SN, prolog, PT_List, AST_List).
26
27pt_kind(_Opts, S0, S0, prolog, [], []).
28pt_kind(_Opts, S0, S0, prolog, [layout_text_sequence(_)], []).
29pt_kind(Opts, S0, SN, prolog, [PT|PTs], [AST|ASTs]) :-
30 set_context(S0, S1, indent, level(0)),
31 pt_ast(Opts, S1, S2, PT, AST),
32 pt_kind(Opts, S2, SN, prolog, PTs, ASTs).
33
35pt_ast(Opts, S0, SN,
36 clause_term([Term, end(PT_End)]),
37 fact(AST_Term)
38) :-
39 pt_ast(Opts, S0, S1, Term, AST_Term),
40 pt(Opts, S1, S2, end, PT_End),
41 set_context(S2, S3, after_clause),
42 inc_state(S3, SN, statistics, facts).
43
45pt_ast(Opts, S0, SN,
46 directive_term([
47 term(xfx, [
48 PT_Head,
49 op(atom(name(PT_Op))),
50 PT_Body
51 ]),
52 end(PT_End)
53 ]),
54 rule(AST_Head, AST_Body)
55) :-
56 pt_ast(Opts, S0, S1, PT_Head, AST_Head),
57 pt(Opts, S1, S2, ':-', PT_Op),
58 set_context(S2, S3, after_rule_op),
59 inc_context(S3, S4, indent, level),
60 pt_kind(Opts, S4, S5, rule_body, PT_Body, AST_Body),
61 pt(Opts, S5, S6, end, PT_End),
62 set_context(S6, S7, after_clause),
63 check_entity(Opts, S7, S8, max_subgoals, AST_Body),
64 check_entity(Opts, S8, S9, max_rule_lines, [S0, S6]),
65 inc_state(S9, SN, statistics, rules).
66
68pt_ast(Opts, S0, SN,
69 directive_term([
70 term(fx, [
71 op(atom(name(PT_Op))),
72 PT_Body
73 ]),
74 end(PT_End)
75 ]),
76 directive(AST_Body)
77) :-
78 pt(Opts, S0, S1, ':-', PT_Op),
79 set_context(S1, S2, after_directive_op),
80 pt_kind(Opts, S2, S3, directive_body, PT_Body, AST_Body),
81 pt(Opts, S3, S4, end, PT_End),
82 set_context(S4, S5, after_clause),
83 inc_state(S5, SN, statistics, directives).
84
86pt_ast(Opts, S0, SN,
87 term(atom(name(PT_Name))),
88 atom(Atom)
89) :-
90 Atom \== '{}',
91 layout(Opts, S0, S1, PT_Name, PT),
92 pt_kind(Opts, S1, SN, name_token, PT, Atom).
93
94pt_kind(Opts, S0, SN, name_token, PT, Atom) :-
95 PT = name_token(_, quoted_token(PT_Quoted_Token)),
96 !,
97 state_space(S0, S1, cols(1)), 98 99 100 append([Quote_Char|Quoteds], [Quote_Char], PT_Quoted_Token),
101 quoted_items(Opts, S1, S2, Quoteds, Atom),
102 state_space(S2, SN, cols(1)). 103
104pt_kind(_Opts, S0, SN, name_token, PT, Atom) :-
105 PT = name_token(Atom, _),
106 atom_length(Atom, Length),
107 state_space(S0, SN, cols(Length)).
108
110pt_ast(Opts, S0, SN,
111 term([
112 name(PT_Name),
113 open_curly([open_curly_token(open_curly_char('{'))]),
114 close_curly(PT_Close_Curly)
115 ]),
116 dict(atom(Atom), [])
117) :-
118 pt_ast(Opts, S0, S1, term(atom(name(PT_Name))), atom(Atom)),
119 check(Opts, S1, S2, dicts),
120 state_space(S2, S3, cols(1)), 121 layout(Opts, S3, S4, PT_Close_Curly, close_curly_token(close_curly_char('}'))),
122 state_space(S4, SN, cols(1)). 123
125pt_ast(Opts, S0, SN,
126 term([
127 name(PT_Name),
128 open_curly([open_curly_token(open_curly_char('{'))]),
129 key_value_list(_PT_Key_Value_List),
130 close_curly(PT_Close_Curly)
131 ]
131),
132 dict(atom(Atom), [])
133)
133 :-
134 pt_ast(Opts, S0, S1, term(atom(name(PT_Name))), atom(Atom)),
135 check(Opts, S1, S2, dicts),
136 state_space(S2, S3, cols(1)), 137 layout(Opts, S3, S4, PT_Close_Curly, close_curly_token(close_curly_char('}'))),
138 state_space(S4, SN, cols(1))
138. 139
141pt_ast(Opts, S0, SN,
142 term([
143 variable(PT_Variable),
144 open_curly([open_curly_token(open_curly_char('{'))]),
145 close_curly(PT_Close_Curly)
146 ]),
147 dict(AST_Variable, [])
148) :-
149 pt_ast(Opts, S0, S1, term(variable(PT_Variable)), AST_Variable),
150 check(Opts, S1, S2, dicts),
151 state_space(S2, S3, cols(1)), 152 layout(Opts, S3, S4, PT_Close_Curly, close_curly_token(close_curly_char('}'))),
153 state_space(S4, SN, cols(1)). 154
156pt_ast(Opts, S0, SN,
157 term([
158 variable(PT_Variable),
159 open_curly([open_curly_token(open_curly_char('{'))]),
160 key_value_list(_PT_Key_Value_List),
161 close_curly(PT_Close_Curly)
162 ]
162),
163 dict(AST_Variable, [])
164)
164 :-
165 pt_ast(Opts, S0, S1, term(variable(PT_Variable)), AST_Variable),
166 check(Opts, S1, S2, dicts),
167 state_space(S2, S3, cols(1)), 168 layout(Opts, S3, S4, PT_Close_Curly, close_curly_token(close_curly_char('}'))),
169 state_space(S4, SN, cols(1))
169. 170
172pt_ast(Opts, S0, SN,
173 term(double_quoted_list(PT_Double_Quoted_List)),
174 double_quoted(Atom)
175) :-
176 layout(Opts, S0, S1, PT_Double_Quoted_List, PT),
177 state_space(S1, S2, cols(1)), 178 179 180 PT = double_quoted_list_token(_, PT_Double_Quoted_List_Token),
181 append([Quote_Char|Quoteds], [Quote_Char], PT_Double_Quoted_List_Token),
182 quoted_items(Opts, S2, S3, Quoteds, Atom),
183 state_space(S3, SN, cols(1)). 184
186pt_ast(Opts, S0, SN,
187 term(back_quoted_string(PT_Back_Quoted_String)),
188 back_quoted(Atom)
189) :-
190 layout(Opts, S0, S1, PT_Back_Quoted_String, PT),
191 state_space(S1, S2, cols(1)), 192 193 194 PT = back_quoted_string_token(_, PT_Back_Quoted_String_Token),
195 append([Quote_Char|Quoteds], [Quote_Char], PT_Back_Quoted_String_Token),
196 quoted_items(Opts, S2, S3, Quoteds, Atom),
197 state_space(S3, SN, cols(1)). 198
200pt_ast(Opts, S0, SN,
201 term(atom([
202 open_curly(PT_Open_Curly),
203 close_curly(PT_Close_Curly)
204 ])),
205 atom('{}')
206) :-
207 layout(Opts, S0, S1, PT_Open_Curly, open_curly_token(open_curly_char('{'))),
208 state_space(S1, S2, cols(1)), 209 layout(Opts, S2, S3, PT_Close_Curly, close_curly_token(close_curly_char('}'))),
210 state_space(S3, SN, cols(1)). 211
213pt_ast(Opts, S0, SN,
214 term([
215 open_curly(PT_Open_Curly),
216 PT_Term,
217 close_curly(PT_Close_Curly)
218 ]),
219 prefix('{}', fx, AST_Term)
220) :-
221 layout(Opts, S0, S1, PT_Open_Curly, open_curly_token(open_curly_char('{'))),
222 state_space(S1, S2, cols(1)), 223 pt_ast(Opts, S2, S3, PT_Term, AST_Term),
224 layout(Opts, S3, S4, PT_Close_Curly, close_curly_token(close_curly_char('}'))),
225 state_space(S4, SN, cols(1)). 226
228pt_ast(Opts, S0, SN,
229 term(integer(PT_Integer)),
230 integer(Integer)
231) :-
232 layout(Opts, S0, S1, PT_Integer, PT),
233 PT = integer_token(Atom, Inner_PT),
234 check_entity(Opts, S1, S2, digit_groups, Inner_PT),
235 check_entity(Opts, S2, S3, single_quote_char_in_character_code_constant, Inner_PT),
236 ( Inner_PT = character_code_constant(['0', single_quote_char('\''), single_quoted_character(PT_Single_Quoted_Character)]) ->
237 check_entity(Opts, S3, S4, symbolic_chars, PT_Single_Quoted_Character)
238 ; otherwise ->
239 S4 = S3
240 ),
241 integer_number(Atom, Inner_PT, Integer),
242 atom_length(Atom, Length),
243 state_space(S4, SN, cols(Length)).
244
246pt_ast(Opts, S0, SN,
247 term(float_number(PT_Float)),
248 float(Float)
249) :-
250 layout(Opts, S0, S1, PT_Float, PT),
251 PT = float_number_token(Atom, PT_Float_Number_Token),
252 check_entity(Opts, S1, S2, integer_exponential_notation, PT_Float_Number_Token),
253 atom_number(Atom, Float),
254 atom_length(Atom, Length),
255 state_space(S2, SN, cols(Length)).
256
258pt_ast(Opts, S0, SN,
259 term(variable(PT_Variable)),
260 anonymous
261) :-
262 ( PT_Variable = [PT] ; PT_Variable = [_LTS, PT] ),
263 PT = variable_token('_', anonymous_variable(_)),
264 !,
265 layout(Opts, S0, S1, PT_Variable, PT),
266 state_space(S1, SN, cols(1)).
267
269pt_ast(Opts, S0, SN,
270 term(variable(PT_Variable)),
271 variable(Variable)
272) :-
273 ( PT_Variable = [PT] ; PT_Variable = [_LTS, PT] ),
274 PT = variable_token(Variable, named_variable(_)),
275 !,
276 layout(Opts, S0, S1, PT_Variable, PT),
277 atom_length(Variable, Length),
278 state_space(S1, SN, cols(Length)).
279
281pt_ast(Opts, S0, SN,
282 term([
283 atom(PT_Atom),
284 open_ct(open_token(open_char('('))),
285 arg_list(PT_Arg_List),
286 close(PT_Close)
287 ]),
288 compound(Atom, AST_Arg_list)
289) :-
290 AST_Arg_list \== [],
291 pt_ast(Opts, S0, S1, term(atom(PT_Atom)), Atom),
292 state_space(S1, S2, cols(1)), 293 inc_context(S2, S3, indent, level),
294 pt_kind(Opts, S3, S4, arg_list, PT_Arg_List, AST_Arg_list),
295 dec_context(S4, S5, indent, level),
296 pt(Opts, S5, SN, close, PT_Close).
297
299pt_ast(Opts, S0, SN,
300 term([
301 atom(PT_Atom),
302 open_ct(open_token(open_char('('))),
303 close(PT_Close)
304 ]),
305 compound(Atom, [])
306) :-
307 pt_ast(Opts, S0, S1, term(atom(PT_Atom)), Atom),
308 state_space(S1, S2, cols(1)), 309 check(Opts, S2, S3, compounds_with_zero_arguments),
310 pt(Opts, S3, SN, close, PT_Close).
311
313pt_kind(Opts, S0, SN, arg_list,
314 arg(PT_Arg),
315 [AST_Arg]
316) :-
317 pt_kind(Opts, S0, SN, arg, PT_Arg, AST_Arg).
318
319pt_kind(Opts, S0, SN, arg_list,
320 [arg(PT_Arg), comma(PT_Comma), arg_list(PT_Arg_List)],
321 [AST_Arg|AST_Arg_List]
322) :-
323 pt_kind(Opts, S0, S1, arg, PT_Arg, AST_Arg),
324 pt(Opts, S1, S2, comma, PT_Comma),
325 set_context(S2, S3, after_arglist_comma),
326 pt_kind(Opts, S3, SN, arg_list, PT_Arg_List, AST_Arg_List).
327
329pt_kind(Opts, S0, SN, arg,
330 atom(PT_Atom),
331 AST_Atom
332) :-
333 pt_ast(Opts, S0, SN, term(atom(PT_Atom)), AST_Atom).
334
336pt_kind(Opts, S0, SN, arg,
337 PT_Term,
338 AST_Term
339) :-
340 ( PT_Term = term(_) ; PT_Term = term(_,_) ),
341 !,
342 pt_ast(Opts, S0, SN, PT_Term, AST_Term).
343
345pt_ast(Opts, S0, SN,
346 term(Spec, [
347 PT_Term1,
348 op(PT_Op),
349 PT_Term2
350 ]),
351 infix(Atom, Spec, AST_Term1, AST_Term2)
352) :-
353 spec_class(Spec, infix),
354 pt_ast(Opts, S0, S1, PT_Term1, AST_Term1),
355 pt_kind(Opts, S1, S2, op, PT_Op, Atom),
356 pt_ast(Opts, S2, SN, PT_Term2, AST_Term2).
357
359pt_ast(Opts, S0, SN,
360 term(Spec, [
361 op(PT_Op),
362 PT_Term
363 ]),
364 prefix(Atom, Spec, AST_Term)
365) :-
366 spec_class(Spec, prefix),
367 pt_kind(Opts, S0, S1, op, PT_Op, Atom),
368 pt_ast(Opts, S1, SN, PT_Term, AST_Term).
369
371pt_ast(Opts, S0, SN,
372 term(Spec, [
373 PT_Term,
374 op(PT_Op)
375 ]),
376 postfix(Atom, Spec, AST_Term)
377) :-
378 spec_class(Spec, postfix),
379 pt_ast(Opts, S0, S1, PT_Term, AST_Term),
380 pt_kind(Opts, S1, SN, op, PT_Op, Atom).
381
383pt_kind(Opts, S0, SN, op,
384 atom(name(PT_Name)),
385 Atom
386) :-
387 Atom \== ',',
388 layout(Opts, S0, S1, PT_Name, PT),
389 PT = name_token(Atom, _),
390 atom_length(Atom, Length),
391 state_space(S1, SN, cols(Length)).
392
393pt_kind(Opts, S0, SN, op,
394 comma(PT_Comma),
395 ','
396) :-
397 layout(Opts, S0, S1, PT_Comma, PT),
398 PT = comma_token(_),
399 state_space(S1, SN, cols(1)).
400
401pt_kind(Opts, S0, SN, op,
402 ht_sep(PT_Ht_Sep),
403 '|'
404) :-
405 layout(Opts, S0, S1, PT_Ht_Sep, PT),
406 PT = head_tail_separator_token(head_tail_separator_char('|')),
407 state_space(S1, SN, cols(1)).
408
410pt_ast(Opts, S0, SN,
411 term([
412 open(PT_Open),
413 PT_Term,
414 close(PT_Close)
415 ]),
416 AST_Term
417) :-
418 pt(Opts, S0, S1, open, PT_Open),
419 pt_ast(Opts, S1, S2, PT_Term, AST_Term),
420 pt(Opts, S2, SN, close, PT_Close).
421
423pt_ast(Opts, S0, SN,
424 term([
425 open_ct(PT_Open),
426 PT_Term,
427 close(PT_Close)
428 ]),
429 AST_Term
430) :-
431 pt(Opts, S0, S1, open_ct, PT_Open),
432 pt_ast(Opts, S1, S2, PT_Term, AST_Term),
433 pt(Opts, S2, SN, close, PT_Close).
434
436pt_ast(Opts, S0, SN,
437 term(atom([
438 open_list(PT_Open_List),
439 close_list(PT_Close_List)
440 ])),
441 list([], eol)
442) :-
443 pt(Opts, S0, S1, open_list, PT_Open_List),
444 pt(Opts, S1, SN, close_list, PT_Close_List).
445
447pt_ast(Opts, S0, SN,
448 term([
449 open_list(PT_Open_List),
450 items(PT_Items),
451 close_list(PT_Close_List)
452 ]),
453 list(AST_Items, EOL)
454) :-
455 AST_Items = [_|_], 456 pt(Opts, S0, S1, open_list, PT_Open_List),
457 pt_kind(Opts, S1, S2, items, PT_Items, list(AST_Items, EOL)),
458 pt(Opts, S2, SN, close_list, PT_Close_List).
459
461pt_kind(Opts, S0, SN, items, arg(PT_Arg), list([AST_Arg],eol)) :-
462 pt_ast(Opts, S0, SN, PT_Arg, AST_Arg).
463
464pt_kind(Opts, S0, SN, items,
465 [arg(PT_Arg), comma(PT_Comma), items(PT_Item_List)],
466 list([AST_Arg|AST_Item_List],EOL)
467) :-
468 AST_Item_List = [_|_], 469 pt_ast(Opts, S0, S1, PT_Arg, AST_Arg),
470 pt(Opts, S1, S2, comma, PT_Comma),
471 pt_kind(Opts, S2, SN, items, PT_Item_List, list(AST_Item_List, EOL)).
472
473pt_kind(Opts, S0, SN, items,
474 [arg(PT_Arg1), ht_sep(PT_Ht_Sep), arg(PT_Arg2)],
475 list([AST_Arg1],AST_Arg2)
476) :-
477 AST_Arg2 \== eol,
478 pt_ast(Opts, S0, S1, PT_Arg1, AST_Arg1),
479 pt(Opts, S1, S2, ht_sep, PT_Ht_Sep),
480 pt_ast(Opts, S2, SN, PT_Arg2, AST_Arg2).
481
483pt_kind(Opts, S0, SN, rule_body,
484 term(xfy, [
485 PT_Term1,
486 op(PT_Op),
487 PT_Term2
488 ]),
489 AST
490) :-
491 pt_ast(Opts, S0, S1, PT_Term1, AST_Term1),
492 pt_kind(Opts, S1, S2, op, PT_Op, Atom),
493 ( Atom = ',' ->
494 set_context(S2, S3, after_subgoal),
495 AST = [AST_Term1|Rest],
496 pt_kind(Opts, S3, SN, rule_body, PT_Term2, Rest)
497 ; otherwise ->
498 pt_ast(Opts, S2, SN, PT_Term2, AST_Term2),
499 AST = [infix(Atom, xfy, AST_Term1, AST_Term2)]
500 ).
501pt_kind(Opts, S0, SN, rule_body, PT, [AST]) :-
502 PT \= term(xfy, _),
503 pt_ast(Opts, S0, SN, PT, AST).
504
506pt_kind(Opts, S0, SN, directive_body,
507 term(xfy, [
508 PT_Term1,
509 op(PT_Op),
510 PT_Term2
511 ]),
512 AST
513) :-
514 pt_ast(Opts, S0, S1, PT_Term1, AST_Term1),
515 pt_kind(Opts, S1, S2, op, PT_Op, Atom),
516 ( Atom = ',' ->
517 set_context(S2, S3, after_subgoal),
518 AST = [AST_Term1|Rest],
519 pt_kind(Opts, S3, SN, directive_body, PT_Term2, Rest)
520 ; otherwise ->
521 pt_ast(Opts, S2, SN, PT_Term2, AST_Term2),
522 AST = [infix(Atom, xfy, AST_Term1, AST_Term2)]
523 ).
524pt_kind(Opts, S0, SN, directive_body, PT, [AST]) :-
525 PT \= term(xfy, _),
526 pt_ast(Opts, S0, SN, PT, AST).
527
529pt(Opts, S0, SN, end, PT) :-
530 PT_End_Token = end_token(end_char('.')),
531 layout(Opts, S0, S1, PT, PT_End_Token),
532 state_space(S1, SN, cols(1)).
533
535pt(Opts, S0, SN, open, PT) :-
536 PT_Open_Token = open_token(open_char('(')),
537 layout(Opts, S0, S1, PT, PT_Open_Token),
538 state_space(S1, SN, cols(1)).
539
541pt(_Opts, S0, SN, open_ct, PT) :-
542 PT = open_token(open_char('(')),
543 state_space(S0, SN, cols(1)).
544
546pt(Opts, S0, SN, close, PT) :-
547 PT_Close_Token = close_token(close_char(')')),
548 layout(Opts, S0, S1, PT, PT_Close_Token),
549 state_space(S1, SN, cols(1)).
550
552pt(Opts, S0, SN, comma, PT) :-
553 PT_Comma_Token = comma_token(comma_char(',')),
554 layout(Opts, S0, S1, PT, PT_Comma_Token),
555 state_space(S1, SN, cols(1)).
556
558pt(Opts, S0, SN, open_list, PT) :-
559 PT_Open_List_Token = open_list_token(open_list_char('[')),
560 layout(Opts, S0, S1, PT, PT_Open_List_Token),
561 state_space(S1, SN, cols(1)).
562
564pt(Opts, S0, SN, close_list, PT) :-
565 PT_Close_List_Token = close_list_token(close_list_char(']')),
566 layout(Opts, S0, S1, PT, PT_Close_List_Token),
567 state_space(S1, SN, cols(1)).
568
570pt(Opts, S0, SN, ht_sep, PT) :-
571 PT_Head_Tail_Separator_Token = head_tail_separator_token(head_tail_separator_char('|')),
572 layout(Opts, S0, S1, PT, PT_Head_Tail_Separator_Token),
573 state_space(S1, SN, cols(1)).
574
576pt(Opts, S0, SN, ':-', PT) :-
577 PT_Directive_Sep = name_token(':-', graphic_token([
578 graphic_token_char(graphic_char(':')),
579 graphic_token_char(graphic_char('-'))
580 ])),
581 layout(Opts, S0, S1, PT, PT_Directive_Sep),
582 state_space(S1, SN, cols(2)).
583
584
586pt_ast(_, S0, S0, Q, R) :-
587 var(R),
588 option(pos(L0:C0), S0, na:na),
589 functor(Q, Kind, _),
590 setof(
591 Type,
592 [Opts,S0,S1,A,B,Argument,Body]^(
593 clause(pt_ast(Opts,S0,S1,A,B), Body),
594 nonvar(A),
595 A =.. [Type, Argument]
596 ),
597 Types
598 ),
599 Msg = 'No pt_ast/5 rule defined for ~w. Use one of ~w. Complete call was at line ~d, column ~d:~n~w.',
600 warning(Msg, [Kind, Types, L0, C0, Q]),
601 R = Q.
602
603pt_kind(_, S0, S0, Target, Q, R) :-
604 var(R),
605 option(pos(L0:C0), S0, na:na),
606 Msg = 'No pt_kind/6 rule defined for ~w. Complete call was at line ~d, column ~d:~n~w.',
607 warning(Msg, [Target, L0, C0, Q]),
608 R = Q.
609
610pt(_, S0, S0, Target, Q) :-
611 option(pos(L0:C0), S0, na:na),
612 Msg = 'No pt/5 rule defined for ~w. Complete call was at line ~d, column ~d:~n~w.',
613 warning(Msg, [Target, L0, C0, Q])