35
36:- module('$dcg',
37 [ dcg_translate_rule/2, 38 dcg_translate_rule/4, 39 phrase/2, 40 phrase/3, 41 call_dcg/3 42 ]). 43
44 47
61
62dcg_translate_rule(Rule, Clause) :-
63 dcg_translate_rule(Rule, _, Clause, _).
64
65dcg_translate_rule(((LP,MNT)-->RP), Pos0, (H:-B), Pos) :-
66 !,
67 f2_pos(Pos0, PosH0, PosRP0, Pos, PosH, PosRP),
68 f2_pos(PosH0, PosLP0, PosMNT0, PosH, PosLP, PosMNT),
69 '$current_source_module'(M),
70 Qualify = q(M,M,_),
71 dcg_extend(LP, PosLP0, S0, SR, H, PosLP),
72 dcg_body(RP, PosRP0, Qualify, S0, S1, B0, PosRP),
73 dcg_body(MNT, PosMNT0, Qualify, SR, S1, B1, PosMNT),
74 dcg_optimise((B0,B1),B2,S0),
75 dcg_optimise(B2,B,SR).
76dcg_translate_rule((LP-->RP), Pos0, (H:-B), Pos) :-
77 f2_pos(Pos0, PosLP0, PosRP0, Pos, PosLP, PosRP),
78 dcg_extend(LP, PosLP0, S0, S, H, PosLP),
79 '$current_source_module'(M),
80 Qualify = q(M,M,_),
81 dcg_body(RP, PosRP0, Qualify, S0, S, B0, PosRP),
82 dcg_optimise(B0,B,S0).
95dcg_optimise((S00=X,B), B, S0) :-
96 S00 == S0,
97 !,
98 S0 = X.
99dcg_optimise(S00=X, B, S0) :-
100 S00 == S0,
101 !,
102 S0 = X,
103 B = true.
104dcg_optimise(B, B, _).
111dcg_body(Var, P0, Q, S, SR, phrase(QVar, S, SR), P) :-
112 var(Var),
113 !,
114 qualify(Q, Var, P0, QVar, P).
115dcg_body(M:X, Pos0, q(_,C,_), S, SR, Ct, Pos) :-
116 !,
117 f2_pos(Pos0, _, XP0, _, _, _),
118 dcg_body(X, XP0, q(M,C,Pos0), S, SR, Ct, Pos).
119dcg_body([], P0, _, S, SR, S=SR, P) :- 120 !,
121 dcg_terminal_pos(P0, P).
122dcg_body(List, P0, _, S, SR, C, P) :-
123 ( List = [_|_]
124 -> !,
125 ( is_list(List)
126 -> '$append'(List, SR, OL), 127 C = (S = OL)
128 ; '$skip_list'(_, List, Tail),
129 var(Tail)
130 -> C = '$append'(List, SR, S) 131 ; '$type_error'(list_or_partial_list, List)
132 )
133 ; string(List) 134 -> !,
135 string_codes(List, Codes),
136 '$append'(Codes, SR, OL),
137 C = (S = OL)
138 ),
139 dcg_terminal_pos(P0, P).
140dcg_body(!, P0, _, S, SR, (!, SR = S), P) :-
141 !,
142 dcg_cut_pos(P0, P).
143dcg_body({}, P, _, S, S, true, P) :- !.
144dcg_body({T}, P0, Q, S, SR, (QT, SR = S), P) :-
145 !,
146 dcg_bt_pos(P0, P1),
147 qualify(Q, T, P1, QT, P).
148dcg_body((T,R), P0, Q, S, SR, (Tt, Rt), P) :-
149 !,
150 f2_pos(P0, PA0, PB0, P, PA, PB),
151 dcg_body(T, PA0, Q, S, SR1, Tt, PA),
152 dcg_body(R, PB0, Q, SR1, SR, Rt, PB).
153dcg_body((T;R), P0, Q, S, SR, (Tt;Rt), P) :-
154 !,
155 f2_pos(P0, PA0, PB0, P, PA, PB),
156 dcg_body(T, PA0, Q, S, S1, T1, PA), or_delay_bind(S, SR, S1, T1, Tt),
157 dcg_body(R, PB0, Q, S, S2, R1, PB), or_delay_bind(S, SR, S2, R1, Rt).
158dcg_body((T|R), P0, Q, S, SR, (Tt;Rt), P) :-
159 !,
160 f2_pos(P0, PA0, PB0, P, PA, PB),
161 dcg_body(T, PA0, Q, S, S1, T1, PA), or_delay_bind(S, SR, S1, T1, Tt),
162 dcg_body(R, PB0, Q, S, S2, R1, PB), or_delay_bind(S, SR, S2, R1, Rt).
163dcg_body((C->T), P0, Q, S, SR, (Ct->Tt), P) :-
164 !,
165 f2_pos(P0, PA0, PB0, P, PA, PB),
166 dcg_body(C, PA0, Q, S, SR1, Ct, PA),
167 dcg_body(T, PB0, Q, SR1, SR, Tt, PB).
168dcg_body((C*->T), P0, Q, S, SR, (Ct*->Tt), P) :-
169 !,
170 f2_pos(P0, PA0, PB0, P, PA, PB),
171 dcg_body(C, PA0, Q, S, SR1, Ct, PA),
172 dcg_body(T, PB0, Q, SR1, SR, Tt, PB).
173dcg_body((\+ C), P0, Q, S, SR, (\+ Ct, SR = S), P) :-
174 !,
175 f1_pos(P0, PA0, P, PA),
176 dcg_body(C, PA0, Q, S, _, Ct, PA).
177dcg_body(T, P0, Q, S, SR, QTt, P) :-
178 dcg_extend(T, P0, S, SR, Tt, P1),
179 qualify(Q, Tt, P1, QTt, P).
180
181or_delay_bind(S, SR, S1, T, (T, SR=S)) :-
182 S1 == S,
183 !.
184or_delay_bind(_S, SR, SR, T, T).
192qualify(q(M,C,_), X0, Pos0, X, Pos) :-
193 M == C,
194 !,
195 X = X0,
196 Pos = Pos0.
197qualify(q(M,_,MP), X, Pos0, M:X, Pos) :-
198 dcg_qualify_pos(Pos0, MP, Pos).
208:- dynamic dcg_extend_cache/4. 209:- volatile dcg_extend_cache/4. 210
211dcg_no_extend([]).
212dcg_no_extend([_|_]).
213dcg_no_extend({_}).
214dcg_no_extend({}).
215dcg_no_extend(!).
216dcg_no_extend((\+_)).
217dcg_no_extend((_,_)).
218dcg_no_extend((_;_)).
219dcg_no_extend((_|_)).
220dcg_no_extend((_->_)).
221dcg_no_extend((_*->_)).
222dcg_no_extend((_-->_)).
231dcg_extend(V, _, _, _, _, _) :-
232 var(V),
233 !,
234 throw(error(instantiation_error,_)).
235dcg_extend(M:OldT, Pos0, A1, A2, M:NewT, Pos) :-
236 !,
237 f2_pos(Pos0, MPos, P0, Pos, MPos, P),
238 dcg_extend(OldT, P0, A1, A2, NewT, P).
239dcg_extend(OldT, P0, A1, A2, NewT, P) :-
240 dcg_extend_cache(OldT, A1, A2, NewT),
241 !,
242 extended_pos(P0, P).
243dcg_extend(OldT, P0, A1, A2, NewT, P) :-
244 ( callable(OldT)
245 -> true
246 ; throw(error(type_error(callable,OldT),_))
247 ),
248 ( dcg_no_extend(OldT)
249 -> throw(error(permission_error(define,dcg_nonterminal,OldT),_))
250 ; true
251 ),
252 ( compound(OldT)
253 -> compound_name_arity(OldT, Name, Arity),
254 compound_name_arity(CopT, Name, Arity)
255 ; CopT = OldT,
256 Name = OldT,
257 Arity = 0
258 ),
259 NewArity is Arity+2,
260 functor(NewT, Name, NewArity),
261 copy_args(1, Arity, CopT, NewT),
262 A1Pos is Arity+1,
263 A2Pos is Arity+2,
264 arg(A1Pos, NewT, A1C),
265 arg(A2Pos, NewT, A2C),
266 assert(dcg_extend_cache(CopT, A1C, A2C, NewT)),
267 OldT = CopT,
268 A1C = A1,
269 A2C = A2,
270 extended_pos(P0, P).
271
272copy_args(I, Arity, Old, New) :-
273 I =< Arity,
274 !,
275 arg(I, Old, A),
276 arg(I, New, A),
277 I2 is I + 1,
278 copy_args(I2, Arity, Old, New).
279copy_args(_, _, _, _).
280
281
282 285
286extended_pos(Pos0, Pos) :-
287 '$expand':extended_pos(Pos0, 2, Pos).
288f2_pos(Pos0, A0, B0, Pos, A, B) :- '$expand':f2_pos(Pos0, A0, B0, Pos, A, B).
289f1_pos(Pos0, A0, Pos, A) :- '$expand':f1_pos(Pos0, A0, Pos, A).
295dcg_bt_pos(Var, Var) :-
296 var(Var),
297 !.
298dcg_bt_pos(brace_term_position(F,T,P0),
299 term_position(F,T,F,F,
300 [ P0,
301 term_position(T,T,T,T,_)
302 ])) :- !.
303dcg_bt_pos(Pos, _) :-
304 expected_layout(brace_term, Pos).
305
306dcg_cut_pos(Var, Var) :-
307 var(Var),
308 !.
309dcg_cut_pos(F-T, term_position(F,T,F,T,
310 [ F-T,
311 term_position(T,T,T,T,_)
312 ])).
313dcg_cut_pos(Pos, _) :-
314 expected_layout(atomic, Pos).
318dcg_terminal_pos(Pos, _) :-
319 var(Pos),
320 !.
321dcg_terminal_pos(list_position(F,T,_Elms,_Tail),
322 term_position(F,T,_,_,_)).
323dcg_terminal_pos(F-T,
324 term_position(F,T,_,_,_)).
325dcg_terminal_pos(Pos, _) :-
326 expected_layout(terminal, Pos).
330dcg_qualify_pos(Var, _, _) :-
331 var(Var),
332 !.
333dcg_qualify_pos(Pos,
334 term_position(F,T,FF,FT,[MP,_]),
335 term_position(F,T,FF,FT,[MP,Pos])) :- !.
336dcg_qualify_pos(_, Pos, _) :-
337 expected_layout(f2, Pos).
338
339expected_layout(Expected, Found) :-
340 '$expand':expected_layout(Expected, Found).
341
342
343
352:- meta_predicate
353 phrase(//, ?),
354 phrase(//, ?, ?),
355 call_dcg(//, ?, ?). 356:- noprofile((phrase/2,
357 phrase/3,
358 call_dcg/3)). 359:- '$iso'((phrase/2, phrase/3)). 360
361phrase(RuleSet, Input) :-
362 phrase(RuleSet, Input, []).
363phrase(RuleSet, Input, Rest) :-
364 phrase_input(Input),
365 phrase_input(Rest),
366 call_dcg(RuleSet, Input, Rest).
367
368call_dcg(RuleSet, Input, Rest) :-
369 ( strip_module(RuleSet, M, Plain),
370 nonvar(Plain),
371 dcg_special(Plain)
372 -> dcg_body(Plain, _, q(M,M,_), S0, S, Body, _),
373 Input = S0, Rest = S,
374 call(M:Body)
375 ; call(RuleSet, Input, Rest)
376 ).
377
378phrase_input(Var) :- var(Var), !.
379phrase_input([_|_]) :- !.
380phrase_input([]) :- !.
381phrase_input(Data) :-
382 throw(error(type_error(list, Data), _)).
383
384dcg_special(S) :-
385 string(S).
386dcg_special((_,_)).
387dcg_special((_;_)).
388dcg_special((_|_)).
389dcg_special((_->_)).
390dcg_special(!).
391dcg_special({_}).
392dcg_special([]).
393dcg_special([_|_]).
394dcg_special(\+_)