1/* Part of XPCE --- The SWI-Prolog GUI toolkit 2 3 Author: Jan Wielemaker and Anjo Anjewierden 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org/packages/xpce/ 6 Copyright (c) 2001-2015, University of Amsterdam 7 VU University Amsterdam 8 All rights reserved. 9 10 Redistribution and use in source and binary forms, with or without 11 modification, are permitted provided that the following conditions 12 are met: 13 14 1. Redistributions of source code must retain the above copyright 15 notice, this list of conditions and the following disclaimer. 16 17 2. Redistributions in binary form must reproduce the above copyright 18 notice, this list of conditions and the following disclaimer in 19 the documentation and/or other materials provided with the 20 distribution. 21 22 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 23 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 24 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 25 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 26 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 27 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 28 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 29 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 30 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 31 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 32 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 33 POSSIBILITY OF SUCH DAMAGE. 34*/ 35 36:- module(gui_tracer, 37 [ guitracer/0, 38 noguitracer/0, % Switch it off 39 gtrace/0, % Start tracer and trace 40 gtrace/1, % :Goal 41 gspy/1, % Start tracer and set spypoint 42 gdebug/0, % Start tracer and debug 43 gtrap/1 % +Error 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( ), 52 gspy( ). 53 54/** <module> Graphical debugger utilities 55 56This module provides utilities that use the graphical debugger rather 57than the conventional 4-port commandline debugger. This library is part 58of XPCE. 59 60@see library(threadutil) provides another set t* predicates that 61 deal with threads. 62*/ 63 64%! guitracer is det. 65% 66% Enable the graphical debugger. A subsequent call to trace/0 67% opens the de debugger window. The tranditional debugger can be 68% re-enabled using noguitracer/0. 69 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)). 88 89%! noguitracer is det. 90% 91% Disable the graphical debugger. 92% 93% @see guitracer/0 94 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. 102 103%! gtrace is det. 104% 105% Like trace/0, but uses the graphical tracer. 106 107:- '$hide'(gtrace/0). % don't trace it 108 109gtrace :- 110 guitracer, 111 trace. 112 113%! gtrace(:Goal) is det. 114% 115% Trace Goal in a separate thread, such that the toplevel remains 116% free for user interaction. 117 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( ). 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 ). 153 154%! gspy(:Spec) is det. 155% 156% Same as spy/1, but uses the graphical debugger. 157 158gspy(Predicate) :- 159 guitracer, 160 spy(Predicate). 161 162%! gdebug is det. 163% 164% Same as debug/0, but uses the graphical tracer. 165 166gdebug :- 167 guitracer, 168 debug. 169 170%! gtrap(+Exception) is det. 171% 172% Trap exceptions matching Exception using trap/1 and start the 173% graphical tracer. 174% 175% @see trap/1 for details. 176 177gtrap(Error) :- 178 guitracer, 179 trap(Error). 180 181 /******************************* 182 * MESSAGES * 183 *******************************/ 184 185:- multifile 186 prolog:message/3. 187 188prologmessage(gui_tracer(true)) --> 189 [ 'The graphical front-end will be used for subsequent tracing' ]. 190prologmessage(gui_tracer(false)) --> 191 [ 'Subsequent tracing uses the commandline tracer' ]. 192prologmessage(gui_tracer(in_thread(Id, _Goal))) --> 193 [ 'Debugging goal in new thread ~q'-[Id] ]. 194prologmessage(gui_tracer(completed(Reason))) --> 195 [ 'Goal completed: ~q~n'-[Reason] ]