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@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2002-2013, 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(swi_ide,
   37          [ prolog_ide/0,               %
   38            prolog_ide/1                % +Action
   39          ]).   40:- use_module(library(pce)).

SWI-Prolog IDE controller

This module defines the application @prolog_ide and the predicate prolog_ide(+Action). The major motivation is be able to delay loading the IDE components to the autoloading of one single predicate. */

   49                 /*******************************
   50                 *    AUTOLOAD OF COMPONENTS    *
   51                 *******************************/
   52
   53:- pce_image_directory(library('trace/icons')).   54
   55:- pce_autoload(swi_console,            library('swi/swi_console')).   56:- pce_autoload(prolog_debug_status,    library('trace/status')).   57:- pce_autoload(prolog_navigator,       library('trace/browse')).   58:- pce_autoload(prolog_query_frame,     library('trace/query')).   59:- pce_autoload(prolog_trace_exception, library('trace/exceptions')).   60:- pce_autoload(prolog_thread_monitor,  library('swi/thread_monitor')).   61:- pce_autoload(prolog_debug_monitor,   library('swi/pce_debug_monitor')).   62:- pce_autoload(xref_frame,             library('pce_xref')).   63
   64                 /*******************************
   65                 *            TOPLEVEL          *
   66                 *******************************/
 prolog_ide(+Action)
Invoke an action on the (SWI-)Prolog IDE application. This is a predicate to ensure optimal delaying of loading and object creation for accessing the various components of the Prolog Integrated Development Environment.
   75prolog_ide :-
   76    prolog_ide(open_console).
   77
   78prolog_ide(Action) :-
   79    in_pce_thread(send(@prolog_ide, Action)).
   80
   81
   82                 /*******************************
   83                 *         THE IDE CLASS        *
   84                 *******************************/
   85
   86:- pce_global(@prolog_ide, new(prolog_ide)).
   87:- pce_global(@prolog_exception_window, new(prolog_trace_exception)).
   88
   89:- pce_begin_class(prolog_ide, application, "Prolog IDE application").
   90
   91initialise(IDE) :->
   92    "Create as service application"::
   93    send_super(IDE, initialise, prolog_ide),
   94    send(IDE, kind, service).
   95
   96open_console(IDE) :->
   97    "Open SWI-Prolog Cross-Referencer frontend"::
   98    (   get(IDE, member, swi_console, Console)
   99    ->  send(Console, open)
  100    ;   new(Console, swi_console),
  101        send(Console, application, IDE),
  102        send(Console, wait)
  103    ).
  104
  105open_debug_status(IDE) :->
  106    "Open/show the status of the debugger"::
  107    (   get(IDE, member, prolog_debug_status, W)
  108    ->  send(W, expose)
  109    ;   send(prolog_debug_status(IDE), open)
  110    ).
  111
  112open_exceptions(IDE, Gui:[bool]) :->
  113    "Open/show exceptions"::
  114    W = @prolog_exception_window,
  115    (   object(W)
  116    ->  send(W, expose)
  117    ;   (   Gui == @on
  118        ->  catch(tdebug, _, guitracer)
  119        ;   true
  120        ),
  121        send(W, application, IDE),
  122        send(W, open)
  123    ).
  124
  125open_navigator(IDE, Where:[directory|source_location]) :->
  126    "Open Source Navigator"::
  127    (   send(Where, instance_of, directory)
  128    ->  get(IDE, navigator, Where, Navigator),
  129        send(Navigator, directory, Where)
  130    ;   send(Where, instance_of, source_location)
  131    ->  get(Where, file_name, File),
  132        file_directory_name(File, Dir),
  133        get(Where, line_no, Line),
  134        (   integer(Line)
  135        ->  LineNo = Line
  136        ;   LineNo = 1
  137        ),
  138        get(IDE, navigator, Dir, Navigator),
  139        send(Navigator, goto, File, LineNo)
  140    ;   get(IDE, navigator, directory('.'), Navigator)
  141    ),
  142    send(Navigator, expose).
  143
  144
  145navigator(IDE, Dir:[directory], Navigator:prolog_navigator) :<-
  146    "Create or return existing navigator"::
  147    (   get(IDE, member, prolog_navigator, Navigator)
  148    ->  true
  149    ;   new(Navigator, prolog_navigator(Dir)),
  150        send(Navigator, application, IDE)
  151    ).
  152
  153open_query_window(IDE) :->
  154    "Open window to enter a query"::
  155    (   get(IDE, member, prolog_query_frame, QF)
  156    ->  true
  157    ;   new(QF, prolog_query_frame),
  158        send(QF, application, IDE)
  159    ),
  160    send(QF, expose).
  161
  162open_interactor(_) :->
  163    "Create a new interactor window"::
  164    interactor.
  165
  166thread_monitor(IDE) :->
  167    "Open a monitor for running threads"::
  168    (   current_prolog_flag(threads, true)
  169    ->  (   get(IDE, member, prolog_thread_monitor, Monitor)
  170        ->  true
  171        ;   new(Monitor, prolog_thread_monitor),
  172            send(Monitor, application, IDE)
  173        ),
  174        send(Monitor, open)
  175    ;   send(@display, report, error,
  176             'This version of SWI-Prolog is not built \n\c
  177                  with thread-support')
  178    ).
  179
  180debug_monitor(IDE) :->
  181    "Open monitor for debug messages"::
  182    (   get(IDE, member, prolog_debug_monitor, Monitor)
  183    ->  true
  184    ;   new(Monitor, prolog_debug_monitor),
  185        send(Monitor, application, IDE)
  186    ),
  187    send(Monitor, open).
  188
  189xref(IDE) :->
  190    "Open Cross-Referencer frontend"::
  191    (   get(IDE, member, xref_frame, XREF)
  192    ->  send(XREF, open)
  193    ;   new(XREF, xref_frame),
  194        send(XREF, application, IDE),
  195        send(XREF, wait),
  196        send(XREF, update)
  197    ).
  198
  199:- pce_end_class(prolog_ide)