View source with raw comments or as raw
   1:- module(conf_debug, [ tmon/0 ]).
   2:- use_module(library(debug)).
   3
   4/** <module> Set options for development
   5
   6This  module  make  ClioPatria  more    suitable   for  development.  In
   7particular, it implements the following methods:
   8
   9    * Load library(http/http_error), which causes uncaught Prolog
  10    exceptions to produce an HTML page holding a stack-trace.
  11    * Load library(semweb/rdf_portray), which prints RDF resources
  12    in a more compact way.
  13    * Load library(semweb/rdf_db) into the module =user=.  This allows
  14    usage of rdf/3, rdf_load/1, etc. from the toplevel without
  15    specifying the module.
  16    * Use debug/1 on the _topic_ http(request), which causes the
  17    toplevel to print basic information on the HTTP requests processed.
  18    Using copy/paste of the HTTP path, one can assemble a command that
  19    edits the implementation of a page.
  20
  21        ==
  22        ?- edit('/http/path/to/handler').
  23        ==
  24    * Define tmon/0 that brings up a graphical tool showing thread
  25    activity.
  26
  27@see	http://www.swi-prolog.org/howto/http/Developing.html
  28*/
  29
  30:- use_module(library(http/http_error)).	% Print stack on error
  31:- use_module(library(semweb/rdf_portray)).	% Print e.g., rdf:type
  32:- use_module(user:library(semweb/rdf_db)).	% Allow ?- rdf(S,P,O). in toplevel
  33
  34:- debug_message_context(+time).		% Add time to debug message
  35% Enable to see HTTP requests
  36% :- debug(http(request)).			% Print request and reply
  37
  38%%	prepare_editor
  39%
  40%	Start XPCE as edit requests comming from the document server can
  41%	only be handled if XPCE is running.
  42
  43prepare_editor :-
  44	current_prolog_flag(editor, pce_emacs), !,
  45	start_emacs.
  46prepare_editor.
  47
  48:- prepare_editor.
  49
  50%%	tmon
  51%
  52%	Show the graphical thread-monitor. Can be  useful to examine and
  53%	debug active goals.
  54
  55tmon :-
  56	call(prolog_ide(thread_monitor)).