35
36:- module(prolog_code,
37 [ comma_list/2, 38 semicolon_list/2, 39
40 mkconj/3, 41 mkdisj/3, 42
43 pi_head/2, 44 head_name_arity/3, 45
46 most_general_goal/2, 47 extend_goal/3, 48
49 predicate_label/2, 50 predicate_sort_key/2, 51
52 is_control_goal/1, 53 is_predicate_indicator/1, 54
55 body_term_calls/2 56 ]). 57:- autoload(library(error),[must_be/2, instantiation_error/1]). 58:- autoload(library(lists),[append/3]). 59
60:- meta_predicate
61 body_term_calls(:, -). 62
63:- multifile
64 user:prolog_predicate_name/2. 65
79
94
95comma_list(CommaList, List) :-
96 phrase(binlist(CommaList, ','), List).
97semicolon_list(CommaList, List) :-
98 phrase(binlist(CommaList, ';'), List).
99
100binlist(Term, Functor) -->
101 { nonvar(Term) },
102 !,
103 ( { Term =.. [Functor,A,B] }
104 -> binlist(A, Functor),
105 binlist(B, Functor)
106 ; [Term]
107 ).
108binlist(Term, Functor) -->
109 [A],
110 ( var_tail
111 -> ( { Term = A }
112 ; { Term =.. [Functor,A,B] },
113 binlist(B,Functor)
114 )
115 ; \+ [_]
116 -> {Term = A}
117 ; binlist(B,Functor),
118 {Term =.. [Functor,A,B]}
119 ).
120
121var_tail(H, H) :-
122 var(H).
123
129
130mkconj(A,B,Conj) :-
131 ( is_true(A)
132 -> Conj = B
133 ; is_true(B)
134 -> Conj = A
135 ; Conj = (A,B)
136 ).
137
138mkdisj(A,B,Conj) :-
139 ( is_false(A)
140 -> Conj = B
141 ; is_false(B)
142 -> Conj = A
143 ; Conj = (A;B)
144 ).
145
146is_true(Goal) :- Goal == true.
147is_false(Goal) :- (Goal == false -> true ; Goal == fail).
148
152
153is_predicate_indicator(Var) :-
154 var(Var),
155 !,
156 instantiation_error(Var).
157is_predicate_indicator(PI) :-
158 strip_module(PI, M, PI1),
159 atom(M),
160 ( PI1 = (Name/Arity)
161 -> true
162 ; PI1 = (Name//Arity)
163 ),
164 atom(Name),
165 integer(Arity),
166 Arity >= 0.
167
174
175pi_head(PI, Head) :-
176 '$pi_head'(PI, Head).
177
183
184head_name_arity(Goal, Name, Arity) :-
185 '$head_name_arity'(Goal, Name, Arity).
186
192
193most_general_goal(Goal, General) :-
194 var(Goal),
195 !,
196 General = Goal.
197most_general_goal(Goal, General) :-
198 atom(Goal),
199 !,
200 General = Goal.
201most_general_goal(M:Goal, M:General) :-
202 !,
203 most_general_goal(Goal, General).
204most_general_goal(Compound, General) :-
205 compound_name_arity(Compound, Name, Arity),
206 compound_name_arity(General, Name, Arity).
207
208
213
214extend_goal(Goal0, _, _) :-
215 var(Goal0),
216 !,
217 instantiation_error(Goal0).
218extend_goal(M:Goal0, Extra, M:Goal) :-
219 extend_goal(Goal0, Extra, Goal).
220extend_goal(Atom, Extra, Goal) :-
221 atom(Atom),
222 !,
223 Goal =.. [Atom|Extra].
224extend_goal(Goal0, Extra, Goal) :-
225 compound_name_arguments(Goal0, Name, Args0),
226 append(Args0, Extra, Args),
227 compound_name_arguments(Goal, Name, Args).
228
229
230 233
243
244predicate_label(PI, Label) :-
245 must_be(ground, PI),
246 pi_head(PI, Head),
247 user:prolog_predicate_name(Head, Label),
248 !.
249predicate_label(M:Name/Arity, Label) :-
250 !,
251 ( hidden_module(M, Name/Arity)
252 -> atomic_list_concat([Name, /, Arity], Label)
253 ; atomic_list_concat([M, :, Name, /, Arity], Label)
254 ).
255predicate_label(M:Name//Arity, Label) :-
256 !,
257 ( hidden_module(M, Name//Arity)
258 -> atomic_list_concat([Name, //, Arity], Label)
259 ; atomic_list_concat([M, :, Name, //, Arity], Label)
260 ).
261predicate_label(Name/Arity, Label) :-
262 !,
263 atomic_list_concat([Name, /, Arity], Label).
264predicate_label(Name//Arity, Label) :-
265 !,
266 atomic_list_concat([Name, //, Arity], Label).
267
268hidden_module(system, _).
269hidden_module(user, _).
270hidden_module(M, Name/Arity) :-
271 functor(H, Name, Arity),
272 predicate_property(system:H, imported_from(M)).
273hidden_module(M, Name//DCGArity) :-
274 Arity is DCGArity+1,
275 functor(H, Name, Arity),
276 predicate_property(system:H, imported_from(M)).
277
281
282predicate_sort_key(_:PI, Name) :-
283 !,
284 predicate_sort_key(PI, Name).
285predicate_sort_key(Name/_Arity, Name).
286predicate_sort_key(Name//_Arity, Name).
287
295
296is_control_goal(Goal) :-
297 var(Goal),
298 !, fail.
299is_control_goal((_,_)).
300is_control_goal((_;_)).
301is_control_goal((_->_)).
302is_control_goal((_|_)).
303is_control_goal((_*->_)).
304is_control_goal(\+(_)).
305
310
311body_term_calls(M:Body, Calls) :-
312 body_term_calls(Body, M, M, Calls).
313
314body_term_calls(Var, M, C, Calls) :-
315 var(Var),
316 !,
317 qualify(M, C, Var, Calls).
318body_term_calls(M:Goal, _, C, Calls) :-
319 !,
320 body_term_calls(Goal, M, C, Calls).
321body_term_calls(Goal, M, C, Calls) :-
322 qualify(M, C, Goal, Calls).
323body_term_calls((A,B), M, C, Calls) :-
324 !,
325 ( body_term_calls(A, M, C, Calls)
326 ; body_term_calls(B, M, C, Calls)
327 ).
328body_term_calls((A;B), M, C, Calls) :-
329 !,
330 ( body_term_calls(A, M, C, Calls)
331 ; body_term_calls(B, M, C, Calls)
332 ).
333body_term_calls((A->B), M, C, Calls) :-
334 !,
335 ( body_term_calls(A, M, C, Calls)
336 ; body_term_calls(B, M, C, Calls)
337 ).
338body_term_calls((A*->B), M, C, Calls) :-
339 !,
340 ( body_term_calls(A, M, C, Calls)
341 ; body_term_calls(B, M, C, Calls)
342 ).
343body_term_calls(\+ A, M, C, Calls) :-
344 !,
345 body_term_calls(A, M, C, Calls).
346body_term_calls(Goal, M, C, Calls) :-
347
348 predicate_property(M:Goal, meta_predicate(Spec)),
349 !,
350 arg(I, Spec, SArg),
351 arg(I, Goal, GArg),
352 meta_calls(SArg, GArg, Call0),
353 body_term_calls(Call0, M, C, Calls).
354
355meta_calls(0, Goal, Goal) :-
356 !.
357meta_calls(I, Goal0, Goal) :-
358 integer(I),
359 !,
360 length(Extra, I),
361 extend_goal(Goal0, Extra, Goal).
362meta_calls(//, Goal0, Goal) :-
363 extend_goal(Goal0, [_,_], Goal).
364meta_calls(^, Goal0, Goal) :-
365 !,
366 strip_existential(Goal0, Goal).
367
368strip_existential(Var, Var) :-
369 var(Var),
370 !.
371strip_existential(_^In, Out) :-
372 strip_existential(In, Out).
373
374qualify(M, C, Goal, Calls) :-
375 M == C,
376 !,
377 Calls = Goal.
378qualify(M, _, Goal, M:Goal)