34
35:- module(prolog_debug_tools,
36 [ (spy)/1, 37 (nospy)/1, 38 nospyall/0,
39 debugging/0,
40 trap/1, 41 notrap/1 42 ]). 43:- use_module(library(broadcast), [broadcast/1]). 44:- autoload(library(edinburgh), [debug/0]). 45:- autoload(library(gensym), [gensym/2]). 46
47:- multifile
48 trap_alias/2. 49
50:- set_prolog_flag(generate_debug_info, false). 51
59
65
66:- multifile
67 prolog:debug_control_hook/1. 68
69:- meta_predicate
70 spy(:),
71 nospy(:). 72
87
88spy(Spec) :-
89 '$notrace'(spy_(Spec)).
90
91spy_(_:X) :-
92 var(X),
93 throw(error(instantiation_error, _)).
94spy_(_:[]) :- !.
95spy_(M:[H|T]) :-
96 !,
97 spy(M:H),
98 spy(M:T).
99spy_(Spec) :-
100 prolog:debug_control_hook(spy(Spec)),
101 !.
102spy_(Spec) :-
103 '$find_predicate'(Spec, Preds),
104 '$member'(PI, Preds),
105 pi_to_head(PI, Head),
106 '$define_predicate'(Head),
107 '$spy'(Head),
108 fail.
109spy_(_).
110
111nospy(Spec) :-
112 '$notrace'(nospy_(Spec)).
113
114nospy_(_:X) :-
115 var(X),
116 throw(error(instantiation_error, _)).
117nospy_(_:[]) :- !.
118nospy_(M:[H|T]) :-
119 !,
120 nospy(M:H),
121 nospy(M:T).
122nospy_(Spec) :-
123 prolog:debug_control_hook(nospy(Spec)),
124 !.
125nospy_(Spec) :-
126 '$find_predicate'(Spec, Preds),
127 '$member'(PI, Preds),
128 pi_to_head(PI, Head),
129 '$nospy'(Head),
130 fail.
131nospy_(_).
132
133nospyall :-
134 '$notrace'(nospyall_).
135
136nospyall_ :-
137 prolog:debug_control_hook(nospyall),
138 fail.
139nospyall_ :-
140 spy_point(Head),
141 '$nospy'(Head),
142 fail.
143nospyall_.
144
145pi_to_head(M:PI, M:Head) :-
146 !,
147 pi_to_head(PI, Head).
148pi_to_head(Name/Arity, Head) :-
149 functor(Head, Name, Arity).
150
154
155debugging :-
156 '$notrace'(debugging_).
157
158debugging_ :-
159 prolog:debug_control_hook(debugging),
160 !.
161debugging_ :-
162 ( current_prolog_flag(debug, true)
163 -> print_message(informational, debugging(on)),
164 findall(H, spy_point(H), SpyPoints),
165 print_message(informational, spying(SpyPoints))
166 ; print_message(informational, debugging(off))
167 ),
168 trapping,
169 forall(debugging_hook, true).
170
171spy_point(Module:Head) :-
172 current_predicate(_, Module:Head),
173 '$get_predicate_attribute'(Module:Head, spy, 1),
174 \+ predicate_property(Module:Head, imported_from(_)).
175
181
182:- multifile debugging_hook/0. 183
184
185 188
224
225:- dynamic
226 exception/4, 227 installed/1. 228
229trap(Error) :-
230 '$notrace'(trap_(Error)).
231
232trap_(Spec) :-
233 expand_trap(Spec, Formal),
234 gensym(ex, Rule),
235 asserta(exception(Rule, error(Formal, _), true, true)),
236 print_message(informational, trap(Rule, error(Formal, _), true, true)),
237 install_exception_hook,
238 debug.
239
240notrap(Error) :-
241 '$notrace'(notrap_(Error)).
242
243notrap_(Spec) :-
244 expand_trap(Spec, Formal),
245 Exception = error(Formal, _),
246 findall(exception(Name, Exception, NotCaught, Caught),
247 retract(exception(Name, error(Formal, _), Caught, NotCaught)),
248 Trapping),
249 print_message(informational, notrap(Trapping)).
250
251expand_trap(Var, _Formal), var(Var) =>
252 true.
253expand_trap(Alias, Formal), trap_alias(Alias, For) =>
254 Formal = For.
255expand_trap(Explicit, Formal) =>
256 Formal = Explicit.
257
261
262trap_alias(det, determinism_error(_Pred, _Declared, _Observed, property)).
263trap_alias(=>, existence_error(rule, _)).
264
265
266trapping :-
267 findall(exception(Name, Term, NotCaught, Caught),
268 exception(Name, Term, NotCaught, Caught),
269 Trapping),
270 print_message(information, trapping(Trapping)).
271
272:- dynamic prolog:prolog_exception_hook/5. 273:- multifile prolog:prolog_exception_hook/5. 274
278
279:- public exception_hook/5. 280
281exception_hook(Ex, Ex, _Frame, Catcher, _Debug) :-
282 thread_self(Me),
283 thread_property(Me, debug(true)),
284 broadcast(debug(exception(Ex))),
285 exception(_, Ex, NotCaught, Caught),
286 !,
287 ( Caught == true
288 -> true
289 ; Catcher == none,
290 NotCaught == true
291 ),
292 trace, fail.
293
294
298
299install_exception_hook :-
300 installed(Ref),
301 ( nth_clause(_, I, Ref)
302 -> I == 1, ! 303 ; retractall(installed(Ref)),
304 erase(Ref), 305 fail
306 ).
307install_exception_hook :-
308 asserta((prolog:prolog_exception_hook(Ex, Out, Frame, Catcher, Debug) :-
309 exception_hook(Ex, Out, Frame, Catcher, Debug)), Ref),
310 assert(installed(Ref)).
311
312
313 316
317:- multifile
318 prolog:message//1. 319
320prolog:message(trapping([])) -->
321 [ 'No exception traps'-[] ].
322prolog:message(trapping(Trapping)) -->
323 [ 'Exception traps on'-[], nl ],
324 trapping(Trapping).
325prolog:message(trap(_Rule, Error, _Caught, _NotCaught)) -->
326 [ 'Installed trap for exception '-[] ],
327 exception(Error),
328 [ nl ].
329prolog:message(notrap([])) -->
330 [ 'No matching traps'-[] ].
331prolog:message(notrap(Trapping)) -->
332 [ 'Removed traps from exceptions'-[], nl ],
333 trapping(Trapping).
334
335trapping([]) --> [].
336trapping([exception(_Rule, Error, _Caught, _NotCaught)|T]) -->
337 [ ' '-[] ],
338 exception(Error),
339 [ nl ],
340 trapping(T).
341
342exception(Term) -->
343 { copy_term(Term, T2),
344 numbervars(T2, 0, _, [singletons(true)])
345 },
346 [ '~p'-[T2] ]