1:- module(debug_page, []).

Debugging Page

Displays generally useful debug information.

Note that this can be a security hole. If you load this module, root(debugpage) is loaded as a priority -10 handler. To hide it, you'll need to define a 404 handler at a higher priority.

:- http_handler(root(debugpage) ,
             http_404([index(root(.))]),
             [priority(10)]).

At the moment does little, eventually should include whatever's in

http://www.swi-prolog.org/pldoc/doc/home/vnc/prolog/src/plweb/stats.pl since this code's not integrated

List of registered handlers and paths (done) Current File Search Path Current Session info Info from stats.pl done

*/

   31:- use_module(library(http/html_write)).   32:- use_module(library(http/http_dispatch)).   33:- use_module(library(http/html_head)).   34:- use_module(weblog(formatting/wl_table)).   35:- use_module(weblog(resources/resources)).   36:- use_module(library(http/http_path)).   37:- use_module(weblog(nav/accordion)).   38
   39:- http_handler(root(debugpage) , debug_page_handler, [priority(-10), id(debug_page)]).   40
   41debug_page_handler(_Request) :-
   42	reply_html_page(
   43	    title('Debugging Page'),
   44	    \debug_contents).
   45
   46% dont use abox here, want to keep this separated
   47debug_contents -->
   48	html([
   49	      \html_requires(css('demo.css')),
   50	      h2('Runtime Statistics'),
   51	      \runtime_stats
   52	     ]).
   53
   54runtime_stats -->
   55	{
   56	    with_output_to(atom(Settings), list_settings)
   57	},
   58	html([
   59	    style(
   60		'td   {
   61		     font-size: 80%;
   62		     font-face: sans;
   63		      }'),
   64	    \accordion([], [
   65	       \accordion_section('Handlers',
   66		  \wl_table(handler_info_cells, [
   67		       columns([path, absolute_path, action, is_prefix, options]),
   68		       header(debug_page:handler_headers)])),
   69	       \accordion_section('Settings',
   70	          pre(Settings)),
   71	       \accordion_section('Stats/2',
   72	          \wl_table(rt_stats_cells,
   73		      [columns([key, value, desc]),
   74		      header(debug_page:rt_stats_headers)])),
   75	       \accordion_section('Prolog Flags',
   76	          \wl_table(flags_cells,
   77		      [columns([key, value]),
   78		       header(debug_page:rt_stats_headers)]))
   79		       ])
   80	     ]).
   81
   82handler_headers(path, 'Path').
   83handler_headers(absolute_path, 'Absolute Path').
   84handler_headers(is_prefix, 'prefix?').
   85handler_headers(options, 'Options').
   86
   87handler_info_cells(Path, path, Path) :-
   88	http_dispatch:handler(Path, _, _, _).
   89handler_info_cells(Path, absolute_path, AbsPath) :-
   90	http_dispatch:handler(Path, _, _, _),
   91	http_absolute_location(Path, AbsPath, []).
   92handler_info_cells(Path, action, Action) :-
   93	http_dispatch:handler(Path, A, _, _),
   94	format(atom(Action), '~w', [A]).
   95handler_info_cells(Path, is_prefix, '') :-
   96	http_dispatch:handler(Path, _, false, _).
   97handler_info_cells(Path, is_prefix, b('PREFIX')) :-
   98	http_dispatch:handler(Path, _, true, _).
   99handler_info_cells(Path, options, X) :-
  100	http_dispatch:handler(Path, _, _, Options),
  101	format(atom(X), '~w', [Options]).
  102
  103rt_stats_headers(key, 'Item').
  104rt_stats_headers(value, 'Current').
  105rt_stats_headers(desc, 'Description').
  106
  107rt_stats_cells(Key, key, Key) :-
  108	stats_entries(Stats),
  109	member(Key-_, Stats).
  110rt_stats_cells(Key, value, OutValue) :-
  111	ground(Key),
  112	catch(
  113	    statistics(Key, Value),
  114	    error(domain_error(_, _), _),
  115	    format(atom(Value), 'n/a', [])
  116		    ),
  117	human_value(Value, OutValue).
  118
  119rt_stats_cells(Key, desc, Desc) :-
  120	stats_entries(Stats),
  121	member(Key-Desc, Stats).
  122
  123human_value(Value, OutValue) :-
  124	float(Value),!,
  125	format(atom(OutValue), '~4g', [Value]).
  126human_value(Value, OutValue) :-
  127	integer(Value),!,
  128	format(atom(OutValue), '~D', [Value]).
  129human_value(Value, Value).
  130
  131stats_entries([
  132'agc'-'Number of atom garbage collections performed',
  133'agc_gained'-'Number of atoms removed',
  134'agc_time'-'Time spent in atom garbage collections',
  135'process_cputime'-'(User) CPU time since Prolog was started in seconds',
  136'cputime'-'(User) CPU time since thread was started in seconds',
  137'inferences'-'Total number of passes via the call and redo ports since Prolog was started',
  138'heapused'-'Bytes of heap in use by Prolog (0 if not maintained)',
  139'heap_gc'-'Number of heap garbage collections performed. Only provided if SWI-Prolog is configured with Boehm-GC. See also garbage_collect_heap/0.',
  140'c_stack'-'System (C-) stack limit. 0 if not known.',
  141'stack'-'Total memory in use for stacks in all threads',
  142'local'-'Allocated size of the local stack in bytes',
  143'localused'-'Number of bytes in use on the local stack',
  144'locallimit'-'Size to which the local stack is allowed to grow',
  145'local_shifts'-'Number of local stack expansions',
  146'global'-'Allocated size of the global stack in bytes',
  147'globalused'-'Number of bytes in use on the global stack',
  148'globallimit'-'Size to which the global stack is allowed to grow',
  149'global_shifts'-'Number of global stack expansions',
  150'trail'-'Allocated size of the trail stack in bytes',
  151'trailused'-'Number of bytes in use on the trail stack',
  152'traillimit'-'Size to which the trail stack is allowed to grow',
  153'trail_shifts'-'Number of trail stack expansions',
  154'shift_time'-'Time spent in stack-shifts',
  155'atoms'-'Total number of defined atoms',
  156'functors'-'Total number of defined name/arity pairs',
  157'clauses'-'Total number of clauses in the program',
  158'modules'-'Total number of defined modules',
  159'codes'-'Total size of (virtual) executable code in words',
  160'threads'-'MT-version: number of active threads',
  161'threads_created'-'MT-version: number of created threads',
  162'thread_cputime'-'MT-version: seconds CPU time used by finished threads. Supported on Windows-NT and later, Linux and possibly a few more. Verify it gives plausible results before using.'
  163		      ]).
  164
  165flags_cells(Key, key, Key) :-
  166	current_prolog_flag(Key, _).
  167flags_cells(Key, value, DisplayValue) :-
  168	current_prolog_flag(Key, Value),
  169	format(atom(DisplayValue), '~w', [Value])