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:- set_prolog_flag(generate_debug_info, false). 48
56
62
63:- multifile
64 prolog:debug_control_hook/1. 65
66:- meta_predicate
67 spy(:),
68 nospy(:). 69
84
85spy(Spec) :-
86 '$notrace'(spy_(Spec)).
87
88spy_(_:X) :-
89 var(X),
90 throw(error(instantiation_error, _)).
91spy_(_:[]) :- !.
92spy_(M:[H|T]) :-
93 !,
94 spy(M:H),
95 spy(M:T).
96spy_(Spec) :-
97 prolog:debug_control_hook(spy(Spec)),
98 !.
99spy_(Spec) :-
100 '$find_predicate'(Spec, Preds),
101 '$member'(PI, Preds),
102 pi_to_head(PI, Head),
103 '$define_predicate'(Head),
104 '$spy'(Head),
105 fail.
106spy_(_).
107
108nospy(Spec) :-
109 '$notrace'(nospy_(Spec)).
110
111nospy_(_:X) :-
112 var(X),
113 throw(error(instantiation_error, _)).
114nospy_(_:[]) :- !.
115nospy_(M:[H|T]) :-
116 !,
117 nospy(M:H),
118 nospy(M:T).
119nospy_(Spec) :-
120 prolog:debug_control_hook(nospy(Spec)),
121 !.
122nospy_(Spec) :-
123 '$find_predicate'(Spec, Preds),
124 '$member'(PI, Preds),
125 pi_to_head(PI, Head),
126 '$nospy'(Head),
127 fail.
128nospy_(_).
129
130nospyall :-
131 '$notrace'(nospyall_).
132
133nospyall_ :-
134 prolog:debug_control_hook(nospyall),
135 fail.
136nospyall_ :-
137 spy_point(Head),
138 '$nospy'(Head),
139 fail.
140nospyall_.
141
142pi_to_head(M:PI, M:Head) :-
143 !,
144 pi_to_head(PI, Head).
145pi_to_head(Name/Arity, Head) :-
146 functor(Head, Name, Arity).
147
151
152debugging :-
153 '$notrace'(debugging_).
154
155debugging_ :-
156 prolog:debug_control_hook(debugging),
157 !.
158debugging_ :-
159 ( current_prolog_flag(debug, true)
160 -> print_message(informational, debugging(on)),
161 findall(H, spy_point(H), SpyPoints),
162 print_message(informational, spying(SpyPoints))
163 ; print_message(informational, debugging(off))
164 ),
165 trapping.
166
167spy_point(Module:Head) :-
168 current_predicate(_, Module:Head),
169 '$get_predicate_attribute'(Module:Head, spy, 1),
170 \+ predicate_property(Module:Head, imported_from(_)).
171
172
173 176
203
204:- dynamic
205 exception/4, 206 installed/1. 207
208trap(Error) :-
209 '$notrace'(trap_(Error)).
210
211trap_(Error) :-
212 gensym(ex, Rule),
213 asserta(exception(Rule, error(Error, _), true, true)),
214 print_message(informational, trap(Rule, error(Error, _), true, true)),
215 install_exception_hook,
216 debug.
217
218notrap(Error) :-
219 '$notrace'(notrap_(Error)).
220
221notrap_(Error) :-
222 Exception = error(Error, _),
223 findall(exception(Name, Exception, NotCaught, Caught),
224 retract(exception(Name, error(Error, _), Caught, NotCaught)),
225 Trapping),
226 print_message(informational, notrap(Trapping)).
227
228
229trapping :-
230 findall(exception(Name, Term, NotCaught, Caught),
231 exception(Name, Term, NotCaught, Caught),
232 Trapping),
233 print_message(information, trapping(Trapping)).
234
235:- dynamic
236 user:prolog_exception_hook/4. 237
241
242:- public exception_hook/4. 243
244exception_hook(Ex, Ex, _Frame, Catcher) :-
245 thread_self(Me),
246 thread_property(Me, debug(true)),
247 broadcast(debug(exception(Ex))),
248 exception(_, Ex, NotCaught, Caught),
249 !,
250 ( Caught == true
251 -> true
252 ; Catcher == none,
253 NotCaught == true
254 ),
255 trace, fail.
256
257
261
262install_exception_hook :-
263 installed(Ref),
264 ( nth_clause(_, I, Ref)
265 -> I == 1, ! 266 ; retractall(installed(Ref)),
267 erase(Ref), 268 fail
269 ).
270install_exception_hook :-
271 asserta((user:prolog_exception_hook(Ex, Out, Frame, Catcher) :-
272 exception_hook(Ex, Out, Frame, Catcher)), Ref),
273 assert(installed(Ref)).
274
275
276 279
280:- multifile
281 prolog:message//1. 282
283prolog:message(trapping([])) -->
284 [ 'No exception traps'-[] ].
285prolog:message(trapping(Trapping)) -->
286 [ 'Exception traps on'-[], nl ],
287 trapping(Trapping).
288prolog:message(trap(_Rule, Error, _Caught, _NotCaught)) -->
289 [ 'Installed trap for exception '-[] ],
290 exception(Error),
291 [ nl ].
292prolog:message(notrap([])) -->
293 [ 'No matching traps'-[] ].
294prolog:message(notrap(Trapping)) -->
295 [ 'Removed traps from exceptions'-[], nl ],
296 trapping(Trapping).
297
298trapping([]) --> [].
299trapping([exception(_Rule, Error, _Caught, _NotCaught)|T]) -->
300 [ ' '-[] ],
301 exception(Error),
302 [ nl ],
303 trapping(T).
304
305exception(Term) -->
306 { copy_term(Term, T2),
307 numbervars(T2, 0, _, [singletons(true)])
308 },
309 [ '~p'-[T2] ]