View source with raw comments or as raw
    1:- dynamic
    2	pre_files/1.    3:- findall(F, source_file(F), FL),
    4   assertz(pre_files(FL)).    5:- doc_collect(true).    6:- attach_packs(packs, [duplicate(replace)]).    7:- load_files([ library(pldoc/doc_library),
    8		library(thread_pool),
    9		library(http/http_session),
   10		library(http/http_unix_daemon),
   11		library(http/http_dyn_workers),
   12		library(prolog_source),
   13		plweb,
   14                examples,
   15                blog,
   16                api,
   17		wiki_edit,
   18		stats,
   19		pack,
   20		register,
   21		changelog,
   22		tagit,
   23		forum,
   24		make,
   25		test_recaptcha,
   26		watchdog
   27	      ],
   28	      [ silent(true)
   29	      ]).   30
   31:- if(exists_source(library(ssh_server))).   32:- use_module(library(ssh_server)).   33:- use_module(library(broadcast)).   34:- listen(http(pre_server_start),
   35          start_sshd).   36
   37start_sshd :-
   38    ssh_server([ port(2022),
   39                 authorized_keys_file('etc/ssh/authorized_keys')
   40               ]).
   41:- endif.
 read_comments(+File)
Reads PlDoc comments for a file that was already loaded before the server was started.
   48read_comments(File) :-
   49	source_file_property(File, module(M)),  !,
   50	setup_call_cleanup(
   51	    ( prolog_open_source(File, In),
   52	      set_prolog_flag(xref, true),
   53	      '$set_source_module'(Old, M)
   54	    ),
   55	    ( repeat,
   56	        prolog_read_source_term(In, Term, _,
   57					[ process_comment(true)
   58					]),
   59	        Term == end_of_file,
   60	      !
   61	    ),
   62	    ( '$set_source_module'(_, Old),
   63	      set_prolog_flag(xref, false),
   64	      prolog_close_source(In)
   65	    )).
   66read_comments(_).				% not a module, we do not care
   67
   68reload_pre_files :-
   69	pre_files(FL),
   70	forall(member(F, FL),
   71	       read_comments(F)).
   72
   73:- reload_pre_files.   74:- doc_load_library.   75:- http_set_session_options([enabled(false)]).   76:- send(@(pce), catch_error_signals, @(off)).
 show_fd
Show open file descriptors. Sanity-check that works only on Linux systems.
   83show_fd :-
   84        current_prolog_flag(pid, Pid),
   85        format(string(Cmd),
   86               '/bin/sh -c "(cd /proc/~w/fd && ls -l | grep socket)"',
   87               [Pid]),
   88        shell(Cmd).
   89
   90show_pools :-
   91	format('~`-t~52|~n'),
   92	format('~w~t~20|~t~w~8+~t~w~8+~t~w~8+~t~w~8+~n',
   93	       [ 'Pool name', 'Running', 'Size', 'Waiting', 'Backlog' ]),
   94	format('~`-t~52|~n'),
   95	forall(current_thread_pool(Pool), show_pool(Pool)),
   96	format('~`-t~52|~n').
   97
   98show_pool(Pool) :-
   99	findall(P, thread_pool_property(Pool, P), List),
  100	memberchk(size(Size), List),
  101	memberchk(running(Running), List),
  102	memberchk(backlog(Waiting), List),
  103	memberchk(options(Options), List),
  104	option(backlog(MaxBackLog), Options, infinite),
  105	format('~w~t~20|~t~D  ~8+~t~D ~8+~t~D  ~8+~t~w  ~8+~n',
  106	       [Pool, Running, Size, Waiting, MaxBackLog]).
  107
  108stop :-
  109	halt(42)