YAP 7.1.0
grammar.yap
Go to the documentation of this file.
1/*************************************************************************
2* *
3* YAP Prolog *
4* *
5* Yap Prolog was developed at NCCUP - Universidade do Porto *
6* *
7* Copyright L.Damas, V.S.Costa and Universidade do Porto 1985-1997 *
8* *
9**************************************************************************
10* *
11* File: grammar.pl *
12* Last rev: *
13* mods: *
14* comments: BNF grammar for Prolog *
15* *
16*************************************************************************/
17
18/**
19 * @file grammar.yap
20 * @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
21 * @date Thu Nov 19 10:20:55 2015
22 *
23 * @brief Grammar Rules
24 *
25 *
26*/
27
28/**
29@defgroup Grammars Grammar Rules
30@ingroup Builtins
31@{
32
33Grammar rules in Prolog are both a convenient way to express definite
34clause grammars and an extension of the well known context-free grammars.
35
36A grammar rule is of the form:
37
38```
39head --> body
40```
41where both \a head and \a body are sequences of one or more items
42linked by the standard conjunction operator `,`.
43
44<em>Items can be:</em>
45
46+
47a <em>non-terminal</em> symbol may be either a complex term or an atom.
48+
49a <em>terminal</em> symbol may be any Prolog symbol. Terminals are
50written as Prolog lists.
51+
52an <em>empty body</em> is written as the empty list `[ ]`.
53+
54<em>extra conditions</em> may be inserted as Prolog procedure calls, by being
55written inside curly brackets `{` and `}`.
56+
57the left side of a rule consists of a nonterminal and an optional list
58of terminals.
59+
60alternatives may be stated in the right-hand side of the rule by using
61the disjunction operator `;`.
62+
63the <em>cut</em> and <em>conditional</em> symbol (`->`) may be inserted in the
64right hand side of a grammar rule
65
66
67Grammar related built-in predicates:
68
69*/
70:- system_module( '$_grammar', [!/2,
71 (',')/4,
72 (->)/4,
73 ('.')/4,
74 (;)/4,
75 'C'/3,
76 []/2,
77 []/4,
78 (\+)/3,
81 {}/3,
82 ('|')/4], ['$do_error'/2]).
83
84
85% :- meta_predicate ^(?,0,?).
86% ^(Xs, Goal, Xs) :- call(Goal).
87
88% :- meta_predicate ^(?,1,?,?).
89% ^(Xs0, Goal, Xs0, Xs) :- call(Goal, Xs).
90
91/*
92 Variables X in grammar rule bodies are translated as
93 if phrase(X) had been written, where phrase/3 is obvious.
94 Also, phrase/2-3 check their first argument.
95*/
96
97prolog:'$translate_rule'(Rule, (NH :- B) ) :-
98 source_module( SM ),
99 '$yap_strip_module'( SM:Rule, M0, (LP-->RP) ),
100 t_head(LP, NH0, NGs, S, SR, (LP-->SM:RP)),
101 '$yap_strip_module'( M0:NH0, M, NH1 ),
102 ( M == SM -> NH = NH1 ; NH = M:NH1 ),
103 (var(NGs) ->
104 t_body(RP, _, last, S, SR, B1)
105 ;
106 t_body((RP,{NGs}), _, last, S, SR, B1)
107 ),
108 t_tidy(B1, B).
109t_head(V, _, _, _, _, G0) :- var(V), var,
110 '$do_error'(instantiation_error,G0).
111t_head((H,List), NH, NGs, S, S1, G0) :- t_head,
112 t_hgoal(H, NH, S, SR, G0),
113 t_hlist(List, S1, SR, NGs, G0).
114t_head(H, NH, _, S, SR, G0) :-
115 t_hgoal(H, NH, S, SR, G0).
116
117t_hgoal(V, _, _, _, G0) :- var(V), var,
118 '$do_error'(instantiation_error,G0).
119t_hgoal(M:H, M:NH, S, SR, G0) :- t_hgoal,
120 t_hgoal(H, NH, S, SR, G0).
121t_hgoal(H, NH, S, SR, _) :-
122 dcg_extend([S,SR],H,NH).
123
124t_hlist(V, _, _, _, G0) :- var(V), var,
125 '$do_error'(instantiation_error,G0).
126t_hlist([], _, _, true, _).
127t_hlist(String, S0, SR, SF, G0) :- string(String), string,
128 string_codes( String, X ),
129 t_hlist( X, S0, SR, SF, G0).
130t_hlist([H], S0, SR, ('C'(SR,H,S0)), _) :- t_hlist.
131t_hlist([H|List], S0, SR, ('C'(SR,H,S1),G0), Goal) :- t_hlist,
132 t_hlist(List, S0, S1, G0, Goal).
133t_hlist(T, _, _, _, Goal) :-
134 '$do_error'(type_error(list,T),Goal).
135
136
137%
138% Two extra variables:
139% ToFill tells whether we need to explictly close the chain of
140% variables.
141% Last tells whether we are the ones who should close that chain.
142%
143t_body(Var, filled_in, _, S, S1, phrase(Var,S,S1)) :-
144 var(Var),
145 var.
146t_body(!, to_fill, last, S, S1, (!, S1 = S)) :- t_body.
147t_body(!, _, _, S, S, !) :- t_body.
148t_body([], to_fill, last, S, S1, S1=S) :- t_body.
149t_body([], _, _, S, S, true) :- t_body.
150t_body(X, FilledIn, Last, S, SR, OS) :- string(X), string,
151 string_codes( X, Codes),
152 t_body(Codes, FilledIn, Last, S, SR, OS).
153t_body([X], filled_in, _, S, SR, 'C'(S,X,SR)) :- t_body.
154t_body([X|R], filled_in, Last, S, SR, ('C'(S,X,SR1),RB)) :- t_body,
155 t_body(R, filled_in, Last, SR1, SR, RB).
156t_body({T}, to_fill, last, S, S1, (T, S1=S)) :- t_body.
157t_body({T}, _, _, S, S, T) :- t_body.
158t_body((T,R), ToFill, Last, S, SR, (Tt,Rt)) :- t_body,
159 t_body(T, ToFill, not_last, S, SR1, Tt),
160 t_body(R, ToFill, Last, SR1, SR, Rt).
161t_body((T->R), ToFill, Last, S, SR, (Tt->Rt)) :- t_body,
162 t_body(T, ToFill, not_last, S, SR1, Tt),
163 t_body(R, ToFill, Last, SR1, SR, Rt).
164t_body(\+T, ToFill, _, S, SR, (Tt->fail ; S=SR)) :- t_body,
165 t_body(T, ToFill, not_last, S, _, Tt).
166t_body((T;R), _ToFill, _, S, SR, (Tt;Rt)) :- t_body,
167 t_body(T, _, last, S, SR, Tt),
168 t_body(R, _, last, S, SR, Rt).
169t_body((T|R), _ToFill, _, S, SR, (Tt;Rt)) :- t_body,
170 t_body(T, _, last, S, SR, Tt),
171 t_body(R, _, last, S, SR, Rt).
172t_body(M:G, ToFill, Last, S, SR, M:NG) :- t_body,
173 t_body(G, ToFill, Last, S, SR, NG).
174t_body(T, filled_in, _, S, SR, Tt) :-
175 dcg_extend([S,SR], T, Tt).
176
177
178dcg_extend(More, OldT, NewT) :-
179 OldT =.. OldL,
180 dcg_extend:append(OldL, More, NewL),
181 NewT =.. NewL.
182
183t_tidy(P,P) :- var(P), var.
184t_tidy((P1;P2), (Q1;Q2)) :- t_tidy,
185 t_tidy(P1, Q1),
186 t_tidy(P2, Q2).
187t_tidy((P1->P2), (Q1->Q2)) :- t_tidy,
188 t_tidy(P1, Q1),
189 t_tidy(P2, Q2).
190t_tidy(((P1,P2),P3), Q) :-
191 t_tidy((P1,(P2,P3)), Q).
192t_tidy((true,P1), Q1) :- t_tidy,
193 t_tidy(P1, Q1).
194t_tidy((P1,true), Q1) :- t_tidy,
195 t_tidy(P1, Q1).
196t_tidy((P1,P2), (Q1,Q2)) :- t_tidy,
197 t_tidy(P1, Q1),
198 t_tidy(P2, Q2).
199t_tidy(A, A).
200
201/** @pred `C`( _S1_, _T_, _S2_)
202
203
204This predicate is used by the grammar rules compiler and is defined as
205`C`([H|T],H,T)`.
206 */
207t_tidy:'C'([X|S],X,S).
208
209
210/** @pred phrase(+ _P_, _L_)
211
212This predicate succeeds when _L_ is a phrase of type _P_. The
213same as `phrase(P,L,[])`.
214
215Both this predicate and the previous are used as a convenient way to
216start execution of grammar rules.
217*/
218'C':phrase(PhraseDef, WordList) :-
219 phrase:phrase(PhraseDef, WordList, []).
220
221/** @pred phrase(+ _P_, _L_, _R_)
222
223
224This predicate succeeds when the difference list ` _L_- _R_`
225is a phrase of type _P_.
226*/
227phrase:phrase(V, S0, S) :-
228 var(V),
229 var,
230 '$do_error'(instantiation_error,phrase(V,S0,S)).
231'$do_error':phrase([H|T], S0, S) :-
232 phrase,
233 S0 = [H|S1],
234 '$phrase_list'(T, S1, S).
235'$phrase_list':phrase([], S0, S) :-
236 phrase,
237 S0 = S.
238phrase:phrase(P, S0, S) :-
239 call(P, S0, S).
240
241'$phrase_list'([], S, S).
242'$phrase_list'([H|T], [H|S1], S0) :-
243 '$phrase_list'(T, S1, S0).
244
245'$phrase_list':!(S, S).
246
247!:[](S, S).
248
249:[](H, T, S0, S) :- :append([H|T], S, S0).
250
251append:'.'(H,T, S0, S) :-
252 '.':append([H|T], S, S0).
253
254append:{}(Goal, S0, S) :-
255 Goal,
256 S0 = S.
257
258:','(A,B, S0, S) :-
259 t_body((A,B), _, last, S0, S, Goal),
260 '$execute'(Goal).
261
262'$execute':';'(A,B, S0, S) :-
263 t_body((A;B), _, last, S0, S, Goal),
264 '$execute'(Goal).
265
266'$execute':('|'(A,B, S0, S)) :-
267 t_body((A|B), _, last, S0, S, Goal),
268 '$execute'(Goal).
269
270'$execute':'->'(A,B, S0, S) :-
271 t_body((A->B), _, last, S0, S, Goal),
272 '$execute'(Goal).
273
274'$execute':'\\+'(A, S0, S) :-
275 t_body(\+ A, _, last, S0, S, Goal),
276 '$execute'(Goal).
277
278:- '$new_multifile'( goal_expansion(_,_), prolog).
279:- '$mk_dynamic'( prolog:goal_expansion(_,_)).
280
281'$c_built_in_phrase'(NT, Xs0, Xs, Mod, NewGoal) :-
282 nonvar(NT),
283 catch(prolog:'$translate_rule'(
284 (pseudo_nt --> Mod:NT), Rule),
285 error(Pat,ImplDep),
286 ( \+ '$harmless_dcgexception'(Pat),
287 throw(error(Pat,ImplDep))
288 )
289 ),
290 Rule = (pseudo_nt(Xs0c,Xsc) :- NewGoal0),
291 Mod:NT \== NewGoal0,
292 % apply translation only if we are safe
293 \+ '$contains_illegal_dcgnt'(NT),
294 '$contains_illegal_dcgnt',
295 ( var(Xsc), Xsc \== Xs0c
296 -> Xs = Xsc, NewGoal1 = NewGoal0
297 ; NewGoal1 = (NewGoal0, Xsc = Xs)
298 ),
299 ( var(Xs0c)
300 -> Xs0 = Xs0c,
301 NewGoal2 = NewGoal1
302 ; ( Xs0 = Xs0c, NewGoal1 ) = NewGoal2
303 ),
304 '$yap_strip_module'(Mod:NewGoal2, M, NewGoal3),
305 (nonvar(NewGoal3) -> NewGoal = M:NewGoal3
306 ;
307 var(M) -> NewGoal = '$execute_wo_mod'(NewGoal3,M)
308 ;
309 NewGoal = '$execute_in_mod'(NewGoal3,M)
310 ).
311
312do_c_built_in('C'(A,B,C), _, _, (A=[B|C])) :- do_c_built_in.
313
314do_c_built_in(phrase(NT,Xs0, Xs),Mod, _, NewGoal) :-
315 nonvar(NT), nonvar(Mod), nonvar,
316 '$c_built_in_phrase'(NT, Xs0, Xs, Mod, NewGoal).
317
318do_c_built_in(phrase(NT,Xs),Mod,_,NewGoal) :-
319 nonvar(NT), nonvar(Mod),
320 '$c_built_in_phrase'(NT, Xs, [], Mod, NewGoal).
321
322/**
323@}
324*/
325
326
catch( : Goal,+ Exception,+ Action)
source_module(-Mod)
phrase(+ P, L)
phrase(+ P, L, R)
nonvar( T)
var( T)
append(? List1,? List2,? List3)