35
36:- module(gui_tracer,
37 [ guitracer/0,
38 noguitracer/0, 39 gtrace/0, 40 gtrace/1, 41 gspy/1, 42 gdebug/0, 43 gtrap/1 44 ]). 45:- use_module(library(pce)). 46:- use_module(library(edinburgh)). 47:- use_module(library(prolog_debug)). 48
49:- set_prolog_flag(generate_debug_info, false). 50:- meta_predicate
51 gtrace(0),
52 gspy(:).
70guitracer :-
71 current_prolog_flag(gui_tracer, true),
72 !.
73guitracer :-
74 current_prolog_flag(gui_tracer, _),
75 !,
76 set_prolog_flag(gui_tracer, true),
77 visible(+cut_call),
78 print_message(informational, gui_tracer(true)).
79guitracer :-
80 in_pce_thread_sync(
81 load_files([library('trace/trace')],
82 [ silent(true),
83 if(not_loaded)
84 ])),
85 set_prolog_flag(gui_tracer, true),
86 visible(+cut_call),
87 print_message(informational, gui_tracer(true)).
95noguitracer :-
96 current_prolog_flag(gui_tracer, true),
97 !,
98 set_prolog_flag(gui_tracer, false),
99 visible(-cut_call),
100 print_message(informational, gui_tracer(false)).
101noguitracer.
107:- '$hide'(gtrace/0). 108
109gtrace :-
110 guitracer,
111 trace.
118gtrace(Goal) :-
119 guitracer,
120 thread_create(trace_goal(Goal), Id, [detached(true)]),
121 print_message(informational, gui_tracer(in_thread(Id, Goal))).
122
123:- meta_predicate trace_goal(0). 124
125trace_goal(Goal) :-
126 catch(trace_goal_2(Goal), _, true),
127 !.
128trace_goal(_).
129
130trace_goal_2(Goal) :-
131 setup_call_catcher_cleanup(
132 trace,
133 Goal,
134 Catcher,
135 finished(Catcher, Det)),
136 notrace,
137 ( Det == true
138 -> true
139 ; in_pce_thread_sync(send(@(display), confirm, 'Retry goal?'))
140 -> trace, fail
141 ; !
142 ).
143
144:- '$hide'(finished/2). 145
146finished(Reason, Det) :-
147 notrace,
148 print_message(informational, gui_tracer(completed(Reason))),
149 ( Reason == exit
150 -> Det = true
151 ; Det = false
152 ).
158gspy(Predicate) :-
159 guitracer,
160 spy(Predicate).
166gdebug :-
167 guitracer,
168 debug.
177gtrap(Error) :-
178 guitracer,
179 trap(Error).
180
181 184
185:- multifile
186 prolog:message/3. 187
188prolog:message(gui_tracer(true)) -->
189 [ 'The graphical front-end will be used for subsequent tracing' ].
190prolog:message(gui_tracer(false)) -->
191 [ 'Subsequent tracing uses the commandline tracer' ].
192prolog:message(gui_tracer(in_thread(Id, _Goal))) -->
193 [ 'Debugging goal in new thread ~q'-[Id] ].
194prolog:message(gui_tracer(completed(Reason))) -->
195 [ 'Goal completed: ~q~n'-[Reason] ]
Graphical debugger utilities
This module provides utilities that use the graphical debugger rather than the conventional 4-port commandline debugger. This library is part of XPCE.