View source with raw comments or as raw
    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/projects/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          ]).   44:- use_module(library(pce)).   45:- set_prolog_flag(generate_debug_info, false).   46:- meta_predicate
   47    gtrace(0),
   48    gspy(:).

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.

See also
-
library(threadutil) provides another set t* predicates that deal with threads. */
 guitracer is det
Enable the graphical debugger. A subsequent call to trace/0 opens the de debugger window. The tranditional debugger can be re-enabled using noguitracer/0.
   66guitracer :-
   67    current_prolog_flag(gui_tracer, true),
   68    !.
   69guitracer :-
   70    current_prolog_flag(gui_tracer, _),
   71    !,
   72    set_prolog_flag(gui_tracer, true),
   73    visible(+cut_call),
   74    print_message(informational, gui_tracer(true)).
   75guitracer :-
   76    in_pce_thread_sync(
   77        load_files([library('trace/trace')],
   78                   [ silent(true),
   79                     if(not_loaded)
   80                   ])),
   81    set_prolog_flag(gui_tracer, true),
   82    visible(+cut_call),
   83    print_message(informational, gui_tracer(true)).
 noguitracer is det
Disable the graphical debugger.
See also
- guitracer/0
   91noguitracer :-
   92    current_prolog_flag(gui_tracer, true),
   93    !,
   94    set_prolog_flag(gui_tracer, false),
   95    visible(-cut_call),
   96    print_message(informational, gui_tracer(false)).
   97noguitracer.
 gtrace is det
Like trace/0, but uses the graphical tracer.
  103:- '$hide'(gtrace/0).                   % don't trace it
  104
  105gtrace :-
  106    guitracer,
  107    trace.
 gtrace(:Goal) is det
Trace Goal in a separate thread, such that the toplevel remains free for user interaction.
  114gtrace(Goal) :-
  115    guitracer,
  116    thread_create(trace_goal(Goal), Id, [detached(true)]),
  117    print_message(informational, gui_tracer(in_thread(Id, Goal))).
  118
  119:- meta_predicate trace_goal(0).  120
  121trace_goal(Goal) :-
  122    catch(trace_goal_2(Goal), _, true),
  123    !.
  124trace_goal(_).
  125
  126trace_goal_2(Goal) :-
  127    setup_call_catcher_cleanup(
  128        trace,
  129        Goal,
  130        Catcher,
  131        finished(Catcher, Det)),
  132    notrace,
  133    (   Det == true
  134    ->  true
  135    ;   in_pce_thread_sync(send(@(display), confirm, 'Retry goal?'))
  136    ->  trace, fail
  137    ;   !
  138    ).
  139
  140:- '$hide'(finished/2).  141
  142finished(Reason, Det) :-
  143    notrace,
  144    print_message(informational, gui_tracer(completed(Reason))),
  145    (   Reason == exit
  146    ->  Det = true
  147    ;   Det = false
  148    ).
 gspy(:Spec) is det
Same as spy/1, but uses the graphical debugger.
  154gspy(Predicate) :-
  155    guitracer,
  156    spy(Predicate).
 gdebug is det
Same as debug/0, but uses the graphical tracer.
  162gdebug :-
  163    guitracer,
  164    debug.
  165
  166
  167                 /*******************************
  168                 *            MESSAGES          *
  169                 *******************************/
  170
  171:- multifile
  172    prolog:message/3.  173
  174prolog:message(gui_tracer(true)) -->
  175    [ 'The graphical front-end will be used for subsequent tracing' ].
  176prolog:message(gui_tracer(false)) -->
  177    [ 'Subsequent tracing uses the commandline tracer' ].
  178prolog:message(gui_tracer(in_thread(Id, _Goal))) -->
  179    [ 'Debugging goal in new thread ~q'-[Id] ].
  180prolog:message(gui_tracer(completed(Reason))) -->
  181    [ 'Goal completed: ~q~n'-[Reason] ]