35
36:- module(prolog_trace,
37 [ trace/1, 38 trace/2, 39 tracing/2, 40 list_tracing/0,
41 notraceall/0
42 ]). 43:- autoload(library(apply),[maplist/2]). 44:- autoload(library(error),[instantiation_error/1]). 45:- autoload(library(prolog_wrap),[wrap_predicate/4]). 46:- autoload(library(prolog_code), [pi_head/2]). 47
48
57
58:- meta_predicate
59 trace(:),
60 trace(:, +),
61 tracing(:, -). 62
63:- dynamic tracing_mask/2. 64:- volatile tracing_mask/2. 65
107
108trace(Pred) :-
109 trace(Pred, +all).
110
111trace(Pred, Spec) :-
112 '$find_predicate'(Pred, Preds),
113 Preds \== [],
114 maplist(set_trace(Spec), Preds).
115
116set_trace(Spec, Pred) :-
117 ( tracing_mask(Pred, Spec0)
118 -> true
119 ; Spec0 = 0
120 ),
121 modify(Spec, Spec0, Spec1),
122 retractall(tracing_mask(Pred, _)),
123 ( Spec1 == [] ; Spec1 == 0
124 -> true
125 ; asserta(tracing_mask(Pred, Spec1))
126 ),
127 mask_ports(Spec1, Ports),
128 pi_head(Pred, Head0),
129 ( predicate_property(Head0, imported_from(M))
130 -> requalify(Head0, M, Head)
131 ; Head = Head0
132 ),
133 ( Spec1 == 0
134 -> unwrap_predicate(Head, trace),
135 print_message(informational, trace(Head, Ports))
136 ; wrapper(Spec1, Head, Wrapped, Wrapper),
137 wrap_predicate(Head, trace, Wrapped, Wrapper),
138 print_message(informational, trace(Head, Ports))
139 ).
140
141requalify(Term, M, M:Plain) :-
142 strip_module(Term, _, Plain).
143
144modify(Var, _, _) :-
145 var(Var),
146 !,
147 instantiation_error(Var).
148modify([], Spec, Spec) :-
149 !.
150modify([H|T], Spec0, Spec) :-
151 !,
152 modify(H, Spec0, Spec1),
153 modify(T, Spec1, Spec).
154modify(+Port, Spec0, Spec) :-
155 !,
156 port_mask(Port, Mask),
157 Spec is Spec0 \/ Mask.
158modify(-Port, Spec0, Spec) :-
159 !,
160 port_mask(Port, Mask),
161 Spec is Spec0 /\ \Mask.
162modify(Port, Spec0, Spec) :-
163 port_mask(Port, Mask),
164 Spec is Spec0 \/ Mask.
165
166port_mask(all, 0x0f).
167port_mask(call, 0x01).
168port_mask(exit, 0x02).
169port_mask(redo, 0x04).
170port_mask(fail, 0x08).
171
172mask_ports(0, []) :-
173 !.
174mask_ports(Pattern, [H|T]) :-
175 is_masked(Pattern, H, Pattern1),
176 mask_ports(Pattern1, T).
177
178wrapper(Ports, Head, Wrapped, Wrapper) :-
179 wrapper(Ports, Head,
180 #{frame:Frame, level:Level, start:Start},
181 Wrapped, Wrapped1),
182 Wrapper = ( prolog_current_frame(Frame),
183 prolog_frame_attribute(Frame, level, Level),
184 get_time(Start),
185 Wrapped1
186 ).
187
188wrapper(0, _, _, Wrapped, Wrapped) :-
189 !.
190wrapper(Pattern, Head, Id, Wrapped, Call) :-
191 is_masked(Pattern, call, Pattern1),
192 !,
193 wrapper(Pattern1, Head, Id, Wrapped, Call0),
194 Call = ( print_message(debug, frame(Head, trace(call, Id))),
195 Call0
196 ).
197wrapper(Pattern, Head, Id, Wrapped, Call) :-
198 is_masked(Pattern, exit, Pattern1),
199 !,
200 wrapper(Pattern1, Head, Id, Wrapped, Call0),
201 Call = ( Call0,
202 print_message(debug, frame(Head, trace(exit, Id)))
203 ).
204wrapper(Pattern, Head, Id, Wrapped, Call) :-
205 is_masked(Pattern, redo, Pattern1),
206 !,
207 wrapper(Pattern1, Head, Id, Wrapped, Call0),
208 Call = ( call_cleanup(Call0, Det = true),
209 ( Det == true
210 -> true
211 ; true
212 ; print_message(debug, frame(Head, trace(redo, Id))),
213 fail
214 )
215 ).
216wrapper(Pattern, Head, Id, Wrapped, Call) :-
217 is_masked(Pattern, fail, Pattern1),
218 !,
219 wrapper(Pattern1, Head, Id, Wrapped, Call0),
220 Call = call(( call_cleanup(Call0, Det = true),
221 ( Det == true
222 -> !
223 ; true
224 )
225 ; print_message(debug, frame(Head, trace(fail, Id))),
226 fail
227 )).
228
229is_masked(Pattern0, Port, Pattern) :-
230 port_mask(Port, Mask),
231 Pattern0 /\ Mask =:= Mask,
232 !,
233 Pattern is Pattern0 /\ \Mask.
234
238
239tracing(Spec, Ports) :-
240 tracing_mask(Spec, Mask),
241 mask_ports(Mask, Ports).
242
246
247list_tracing :-
248 PI = _:_,
249 findall(trace(Head, Ports), (tracing(PI, Ports), pi_head(PI, Head)), Tracing),
250 print_message(informational, tracing(Tracing)).
251
252:- multifile
253 prolog_debug_tools:debugging_hook/0. 254
255prolog_debug_tools:debugging_hook :-
256 ( tracing(_:_, _)
257 -> list_tracing
258 ).
259
260
264
265notraceall :-
266 forall(tracing(M:Spec, _Ports),
267 trace(M:Spec, -all))