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    absolute_file_name(private('etc/ssh/authorized_keys'), File,
   39                       [ access(read)]),
   40    absolute_file_name(private('etc/ssh/ssh_host_ecdsa_key'), HostKey,
   41                       [ access(read)]),
   42    ssh_server([ port(2022),
   43                 bind_address(*),
   44                 authorized_keys_file(File),
   45                 host_key_file(HostKey)
   46               ]).
   47:- endif.
 read_comments(+File)
Reads PlDoc comments for a file that was already loaded before the server was started.
   54read_comments(File) :-
   55	source_file_property(File, module(M)),  !,
   56	setup_call_cleanup(
   57	    ( prolog_open_source(File, In),
   58	      set_prolog_flag(xref, true),
   59	      '$set_source_module'(Old, M)
   60	    ),
   61	    ( repeat,
   62	        prolog_read_source_term(In, Term, _,
   63					[ process_comment(true)
   64					]),
   65	        Term == end_of_file,
   66	      !
   67	    ),
   68	    ( '$set_source_module'(_, Old),
   69	      set_prolog_flag(xref, false),
   70	      prolog_close_source(In)
   71	    )).
   72read_comments(_).				% not a module, we do not care
   73
   74reload_pre_files :-
   75	pre_files(FL),
   76	forall(member(F, FL),
   77	       read_comments(F)).
   78
   79:- reload_pre_files.   80:- doc_load_library.   81:- http_set_session_options([enabled(false)]).   82:- send(@(pce), catch_error_signals, @(off)).
 show_fd
Show open file descriptors. Sanity-check that works only on Linux systems.
   89show_fd :-
   90        current_prolog_flag(pid, Pid),
   91        format(string(Cmd),
   92               '/bin/sh -c "(cd /proc/~w/fd && ls -l | grep socket)"',
   93               [Pid]),
   94        shell(Cmd).
   95
   96show_pools :-
   97	format('~`-t~52|~n'),
   98	format('~w~t~20|~t~w~8+~t~w~8+~t~w~8+~t~w~8+~n',
   99	       [ 'Pool name', 'Running', 'Size', 'Waiting', 'Backlog' ]),
  100	format('~`-t~52|~n'),
  101	forall(current_thread_pool(Pool), show_pool(Pool)),
  102	format('~`-t~52|~n').
  103
  104show_pool(Pool) :-
  105	findall(P, thread_pool_property(Pool, P), List),
  106	memberchk(size(Size), List),
  107	memberchk(running(Running), List),
  108	memberchk(backlog(Waiting), List),
  109	memberchk(options(Options), List),
  110	option(backlog(MaxBackLog), Options, infinite),
  111	format('~w~t~20|~t~D  ~8+~t~D ~8+~t~D  ~8+~t~w  ~8+~n',
  112	       [Pool, Running, Size, Waiting, MaxBackLog]).
  113
  114stop :-
  115	halt(42)