2
3:- module('parser', [statements_/5]). 4:- set_prolog_flag(double_quotes,chars). 5:-style_check(-discontiguous). 6:-style_check(-singleton). 7
8statements_(Lang,A,B) --> ws,"\n",{writeln('calling statements_')},top_level_statements(Lang,A,B),ws.
9
10class_statement(Lang,Indent,constructor(Name,Params,Body)) -->
11 optional_indent(Lang,Indent),constructor_(Lang,symbol(Name),parameters(Lang,Params),statements(Lang,indent(Indent),Body),Indent),!.
12
13class_statement(Lang,Indent,instance_method(Type,Name,Params,Body)) -->
14 optional_indent(Lang,Indent),instance_method_(Lang,symbol(Name),type(Lang,Type),parameters(Lang,Params),statements(Lang,indent(Indent),Body),Indent),!.
15
16class_statement(Lang,Indent,static_method(Type,Name,Params,Body)) -->
17 optional_indent(Lang,Indent),static_method_(Lang,symbol(Name),type(Lang,Type),parameters(Lang,Params),statements(Lang,indent(Indent),Body),Indent),!.
18
19statement(Lang,Indent,if_else(A,B,C)) -->
20 optional_indent(Lang,Indent),if_(Lang,Indent,expr(Lang,A),statements(Lang,indent(Indent),B)),else(Lang,Indent,C),!.
21
22statement(Lang,Indent,if(A,B,C,D)) -->
23 optional_indent(Lang,Indent),if_(Lang,Indent,expr(Lang,A),statements(Lang,indent(Indent),B)),elif_statements(Lang,Indent,C),else(Lang,Indent,D),!.
24
25statement(Lang,Indent,if(A,B)) -->
26 optional_indent(Lang,Indent),if_without_else(Lang,Indent,expr(Lang,A),statements(Lang,indent(Indent),B)),{writeln("if without else")},!.
27
28statement(Lang,Indent,while(A,B)) -->
29 optional_indent(Lang,Indent),while_(Lang,Indent,expr(Lang,A),statements(Lang,indent(Indent),B)),!.
30
31statement(Lang,Indent,function(Type,Name,Params,Body)) -->
32 optional_indent(Lang,Indent),function_(Lang,Indent,type(Lang,Type),symbol(Name),parameters(Lang,Params),statements(Lang,indent(Indent),Body)),!.
33
34statement(Lang,Indent,for(Initialize,Condition,Update,Body)) -->
35 optional_indent(Lang,Indent),for_(Lang,Indent,statement_with_semicolon(Lang,Initialize),expr(Lang,Condition),statement_with_semicolon(Lang,Update),statements(Lang,indent(Indent),Body)),!.
36
37statement(Lang,Indent,class(Name,Body)) -->
38 optional_indent(Lang,Indent),class_(Lang,Indent,symbol(Name),class_statements(Lang,indent(Indent),Body)),!.
39
40statement(Lang,Indent,statement_with_semicolon(A)) --> optional_indent(Lang,Indent),statement_with_semicolon_(Lang,Indent,statement_with_semicolon(Lang,A)),!.
41
42statement(Lang,Indent,foreach(Type,Var,Array,Body)) -->
43 optional_indent(Lang,Indent),foreach_(Lang,Indent,type(Lang,Type),var_name(Lang,Type,Var),parentheses_expr(Lang,Array),statements(Lang,indent(Indent),Body)),!.
44
45statement(Lang,Indent,foreach_with_index(Array,Var,Index,Type,Body)) -->
46 optional_indent(Lang,Indent),foreach_with_index(Lang,Indent,parentheses_expr(Lang,Array),var_name(Lang,Type,Var),var_name(Lang,int,Index),type(Lang,Type),statements(Lang,indent(Indent),Body)),!.
47
48indented_block(A) -->
49 python_ws_,A,":";ws,"(",ws,A,ws,"):",!.
50
51elif(Lang,Indent,elif(A,B)) -->
52 optional_indent(Lang,Indent),elif_(Lang,Indent,[expr(Lang,A),statements(Lang,indent(Indent),B)]),!.
53
54
55else(Lang,Indent,B) -->
56 optional_indent(Lang,Indent),else_(Lang,Indent,statements(Lang,indent(Indent),B)),!.
57
58
59elif_statements(Lang,Indent,[A]) --> elif(Lang,Indent,A).
60elif_statements(Lang,Indent,[A|B]) --> elif(Lang,Indent,A),!,ws,elif_statements(Lang,Indent,B).
61
62indent(Indent) --> Indent,"\t".
63
64add_expr(Lang,A) --> mul_expr(Lang,A).
65add_expr(Lang,add(Type,A,B)) --> add_(Lang,Type,mul_expr(Lang,A),add_expr(Lang,B)).
66add_expr(Lang,subtract(A,B)) --> mul_expr(Lang,A),ws,"-",!,ws,add_expr(Lang,B).
67
68mul_expr(Lang,A) --> dot_expr(Lang,A).
69mul_expr(Lang,multiply(A,B)) --> parentheses_expr(Lang,A),ws,"*",!,ws,mul_expr(Lang,B).
70mul_expr(Lang,divide(A,B)) --> parentheses_expr(Lang,A),ws,"/",!,ws,mul_expr(Lang,B).
71
72expr(Lang,A) --> add_expr(Lang,A).
73expr(Lang,not_equals(Type,A,B)) --> not_equals_(Lang,Type,add_expr(Lang,A),add_expr(Lang,B)).
74expr(Lang,equals(Type,A,B)) --> equals_(Lang,Type,add_expr(Lang,A),add_expr(Lang,B)).
75expr(Lang,or(A,B)) --> or_(Lang,add_expr(Lang,A),add_expr(Lang,B)).
76expr(Lang,and(A,B)) --> and_(Lang,add_expr(Lang,A),add_expr(Lang,B)).
77expr(Lang,less_than(Type,A,B)) --> add_expr(Lang,A),ws,"<",ws,add_expr(Lang,B).
78expr(Lang,greater_than(Type,A,B)) --> add_expr(Lang,A),ws,">",ws,add_expr(Lang,B).
79expr(Lang,less_than_or_equal(Type,A,B)) --> add_expr(Lang,A),ws,"<=",!,ws,add_expr(Lang,B).
80expr(Lang,greater_than_or_equal(Type,A,B)) --> add_expr(Lang,A),ws,">=",!,ws,add_expr(Lang,B).
81
82
84
85
87expr(Lang,contains(Type,Container,Contained)) -->
88 contains_(Lang,Type,parentheses_expr(Lang,Container),parentheses_expr(Lang,Contained)).
89
90infix_either_order(A,Op,B) -->
91 A,ws,Op,ws,B;
92 B,ws,Op,ws,A.
93
94parentheses_expr(Lang,initializer_list(Type,S)) -->
95 initializer_list_(Lang,type(Lang,Type),initializer_list_(Lang,S)),!.
96parentheses_expr(Lang,parentheses(A)) -->
97 "(",!,ws,expr(Lang,A),ws,")",!.
98parentheses_expr(Lang,char_literal(S)) -->
99 "\'",string_inner([S]),"\'".
100parentheses_expr(Lang,string_literal(S)) -->
101 string_literal(S),!.
102parentheses_expr(Lang,string_literal(S)) -->
103 string_literal1(S),!.
104parentheses_expr(Lang,abs(Type,A)) -->
105 abs_(Lang,number,expr(Lang,A)),!.
106parentheses_expr(Lang,sqrt(A)) -->
107 sqrt_(Lang,expr(Lang,A)),!.
108parentheses_expr(Lang,sin(A)) -->
109 sin_(Lang,expr(Lang,A)),!.
110parentheses_expr(Lang,cos(A)) -->
111 cos_(Lang,expr(Lang,A)),!.
112parentheses_expr(Lang,acos(A)) -->
113 acos_(Lang,expr(Lang,A)),!.
114parentheses_expr(Lang,tan(A)) -->
115 tan_(Lang,expr(Lang,A)),!.
116parentheses_expr(Lang,atan(A)) -->
117 atan_(Lang,expr(Lang,A)),!.
118parentheses_expr(Lang,asin(A)) -->
119 asin_(Lang,expr(Lang,A)),!.
120parentheses_expr(Lang,floor(A)) -->
121 floor_(Lang,expr(Lang,Arr)),!.
122parentheses_expr(Lang,ceiling(A)) -->
123 ceiling_(Lang,expr(Lang,Arr)),!.
124parentheses_expr(Lang,'false') -->
125 false_(Lang).
126parentheses_expr(Lang,'true') -->
127 true_(Lang).
128parentheses_expr(Lang,number(A)) --> a_double(A).
129parentheses_expr(Lang,A) --> var_name(Lang,Type,A).
130parentheses_expr(Lang,function_call(_,Name,Params)) -->
131 symbol(Name),ws,"(",!,ws,function_call_parameters(Lang,Params),ws,")",!.
132
133
134dot_expr(Lang,A) --> parentheses_expr(Lang,A).
135dot_expr(Lang,not(A)) -->
136 not_(Lang,parentheses_expr(Lang,A)),!.
137dot_expr(Lang,access_array(Type,Arr,In_arr)) -->
138 access_array_(Lang,Type,parentheses_expr(Lang,Arr),expr(Lang,In_arr)),!.
139dot_expr(Lang,range(A,B)) -->
140 range_(Lang,parentheses_expr(Lang,A),parentheses_expr(Lang,B)).
141dot_expr(Lang,length(Type,A)) --> length_(Lang,Type,parentheses_expr(Lang,A)),!.
142dot_expr(Lang,this(Type,A)) -->
143 this_(Lang,var_name(Lang,Type,A)).
144dot_expr(Lang,randint(A,B)) -->
145 randint(Lang,expr(Lang,A),expr(Lang,B)).
146dot_expr(Lang,replace(string,A,B,C)) -->
147 replace_(Lang,string,parentheses_expr(Lang,A),parentheses_expr(Lang,B),parentheses_expr(Lang,C)).
148dot_expr(Lang,split(string,A,B)) -->
149 split_(Lang,string,parentheses_expr(Lang,A),parentheses_expr(Lang,B)).
152dot_expr(Lang,type_conversion(Type1,Type2,A)) -->
153 type_conversion_(Lang,Type1,Type2,expr(Lang,Type1,A)).
154dot_expr(python,Type,pow(A,B)) -->
155 parentheses_expr(python,Type,A),ws,"**",ws,parentheses_expr(python,Type,B).
156dot_expr(Lang,pow(A,B)) -->
157 pow_(Lang,expr(Lang,A),expr(Lang,B)),!.
170
171
172reserved_words(A) :-
173 member(A,["end","float","sin","cos","tan","abs","type","writeln","indexOf","charAt","gets","sample","array","readline","array_rand","input","random","choice","randrange","list","print","print_int","print_string","String","string","int","sort","sorted","reverse","sha1","reversed","len","unique_everseen","True","Number","float","double","return","def","str","char","boolean","function","false","true","enumerate"]) -> false;true.
174
175statement_with_semicolon(Lang,println(Type,A))-->
176 println_(Lang,Type,expr(Lang,A)),!.
177statement_with_semicolon(Lang,return(Type,A))-->
178 return_(Lang,Type,expr(Lang,A)).
179statement_with_semicolon(Lang,initialize_var(Type,A,B)) -->
180 initialize_var_(Lang,type(Lang,Type),var_name(Lang,Type,A),expr(Lang,B)).
181statement_with_semicolon(Lang,initialize_var(Type,A)) -->
182 initialize_var_(Lang,type(Lang,Type),var_name(Lang,Type,A)).
183statement_with_semicolon(Lang,assert(A)) -->
184 assert_(Lang,expr(Lang,A)),!.
187
188statement_with_semicolon(Lang,initialize_constant(Type,A)) -->
189 initialize_constant_(Lang,type(Lang,Type),var_name(Lang,Type,A)).
190statement_with_semicolon(Lang,initialize_constant(Type,A,B)) -->
191 initialize_constant_(Lang,type(Lang,Type),var_name(Lang,Type,A),expr(Lang,B)).
192
193statement_with_semicolon(Lang,set_var(Type,A,B)) -->
194 var_name(Lang,Type,A),ws,"=",!,ws,expr(Lang,B).
195statement_with_semicolon(Lang,reverse_in_place(Type,A)) -->
196 reverse_in_place_(Lang,expr(Lang,A)).
197statement_with_semicolon(Lang,sort_in_place(Type,A)) -->
198 sort_in_place_(Lang,expr(Lang,A)).
199statement_with_semicolon(Lang,set_array_index(A,B,C)) -->
200 set_array_index(Lang,parentheses_expr(Lang,A),expr(Lang,B),expr(Lang,C)).
201statement_with_semicolon(Lang,times_equals(A,B)) -->
202 times_equals_(Lang,parentheses_expr(Lang,A),expr(Lang,B)).
203statement_with_semicolon(Lang,plus_equals(Type,A,B)) -->
204 plus_equals_(Lang,Type,parentheses_expr(Lang,A),expr(Lang,B)).
205statement_with_semicolon(Lang,divide_equals(A,B)) -->
206 divide_equals_(Lang,parentheses_expr(Lang,A),expr(Lang,B)).
207statement_with_semicolon(Lang,minus_equals(A,B)) -->
208 minus_equals_(Lang,parentheses_expr(Lang,A),expr(Lang,B)).
209statement_with_semicolon(Lang,plus_plus(A)) -->
210 plus_plus(Lang,dot_expr(Lang,A)),!.
211statement_with_semicolon(Lang,minus_minus(A)) -->
212 minus_minus(Lang,dot_expr(Lang,A)),!.
213
214top_level_statements(Lang,Indent,[A]) --> top_level_statement(Lang,Indent,A).
215top_level_statements(Lang,Indent,[A|B]) --> top_level_statement(Lang,Indent,A),!,top_level_statement_separator(Lang),top_level_statements(Lang,Indent,B).
216
217
218statements(Lang,Indent,[A]) --> statement(Lang,Indent,A).
219statements(Lang,Indent,[A|B]) --> statement(Lang,Indent,A),!,statement_separator(Lang),statements(Lang,Indent,B).
220
221
223initializer_list_(Lang,[A]) --> parentheses_expr(Lang,A).
224initializer_list_(Lang,[A|B]) --> parentheses_expr(Lang,A),ws,",",!,ws,initializer_list_(Lang,B).
225
226class_statements(Lang,Indent,[A]) --> class_statement(Lang,Indent,A).
227class_statements(Lang,Indent,[A|B]) --> class_statement(Lang,Indent,A),!,ws,class_statements(Lang,Indent,B).
228
229function_call_parameters(Lang,[]) --> "".
230function_call_parameters(Lang,[A]) --> expr(Lang,A).
231function_call_parameters(Lang,[A|B]) --> expr(Lang,A),ws,",",!,ws,function_call_parameters(Lang,B).
232parameters(Lang,[A]) --> parameter(Lang,A);varargs(Lang,A).
233parameters(Lang,[A|B]) --> parameters(Lang,[A]),ws,",",!,ws,parameters(Lang,B).
234parameter(Lang,symbol(Type,A)) --> parameter_(Lang,type(Lang,Type),var_name(Lang,Type,A)).
235varargs(Lang,symbol(Type,A)) --> varargs_(Lang,type(Lang,Type),var_name(Lang,Type,A)).
236
237var_name(Lang,Type,var_name(Type,A)) --> var_name_(Lang,Type,symbol(A)),!.
238
239
240:- include(language_grammars). 241:- include(common_grammar).