View source with raw comments or as raw
    1/*  Part of SWI-Prolog web site
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        jan@swi-prolog.org
    5    WWW:           https://www.swi-prolog.org
    6    Copyright (C): 2009-2025, SWI-Prolog Solutions b.v.
    7
    8    This program is free software; you can redistribute it and/or
    9    modify it under the terms of the GNU General Public License
   10    as published by the Free Software Foundation; either version 2
   11    of the License, or (at your option) any later version.
   12
   13    This program is distributed in the hope that it will be useful,
   14    but WITHOUT ANY WARRANTY; without even the implied warranty of
   15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16    GNU General Public License for more details.
   17
   18    You should have received a copy of the GNU General Public
   19    License along with this library; if not, write to the Free Software
   20    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   21
   22    As a special exception, if you link this library with other files,
   23    compiled with a Free Software compiler, to produce an executable, this
   24    library does not by itself cause the resulting executable to be covered
   25    by the GNU General Public License. This exception does not however
   26    invalidate any other reasons why the executable file might be covered by
   27    the GNU General Public License.
   28*/
   29
   30:- dynamic
   31    pre_files/1.   32:- findall(F, source_file(F), FL),
   33   assertz(pre_files(FL)).   34:- doc_collect(true).   35:- attach_packs(packs, [duplicate(replace)]).   36:- load_files([ library(pldoc/doc_library),
   37                library(thread_pool),
   38                library(http/http_session),
   39                library(http/http_unix_daemon),
   40                library(http/http_dyn_workers),
   41                library(prolog_source),
   42                well_known,
   43                plweb,
   44                examples,
   45                blog,
   46                api,
   47                wiki_edit,
   48                stats,
   49                pack,
   50                register,
   51                changelog,
   52                tagit,
   53                forum,
   54                make,
   55                test_recaptcha,
   56                watchdog
   57              ]).   58
   59:- if(exists_source(library(ssh_server))).   60:- use_module(library(ssh_server)).   61:- use_module(library(broadcast)).   62:- listen(http(pre_server_start),
   63          start_sshd).   64
   65start_sshd :-
   66    absolute_file_name(private('etc/ssh/authorized_keys'), File,
   67                       [ access(read)]),
   68    absolute_file_name(private('etc/ssh/ssh_host_ecdsa_key'), HostKey,
   69                       [ access(read)]),
   70    ssh_server([ port(2022),
   71                 bind_address(*),
   72                 authorized_keys_file(File),
   73                 host_key_file(HostKey)
   74               ]).
   75:- endif.
 read_comments(+File)
Reads PlDoc comments for a file that was already loaded before the server was started.
   82read_comments(File) :-
   83    access_file(File, read),
   84    source_file_property(File, module(M)),
   85    !,
   86    setup_call_cleanup(
   87        ( prolog_open_source(File, In),
   88          set_prolog_flag(xref, true),
   89          '$set_source_module'(Old, M)
   90        ),
   91        ( repeat,
   92            prolog_read_source_term(In, Term, _,
   93                                    [ process_comment(true)
   94                                    ]),
   95            Term == end_of_file,
   96          !
   97        ),
   98        ( '$set_source_module'(_, Old),
   99          set_prolog_flag(xref, false),
  100          prolog_close_source(In)
  101        )).
  102read_comments(_).                               % not a module, we do not care
  103
  104reload_pre_files :-
  105    pre_files(FL),
  106    forall(member(F, FL),
  107           read_comments(F)).
  108
  109:- reload_pre_files.  110:- doc_load_library.  111:- http_set_session_options([enabled(false)]).  112:- send(@(pce), catch_error_signals, @(off)).
 show_fd
Show open file descriptors. Sanity-check that works only on Linux systems.
  119show_fd :-
  120    current_prolog_flag(pid, Pid),
  121    format(string(Cmd),
  122           '/bin/sh -c "(cd /proc/~w/fd && ls -l | grep socket)"',
  123           [Pid]),
  124    shell(Cmd).
  125
  126show_pools :-
  127    format('~`-t~52|~n'),
  128    format('~w~t~20|~t~w~8+~t~w~8+~t~w~8+~t~w~8+~n',
  129           [ 'Pool name', 'Running', 'Size', 'Waiting', 'Backlog' ]),
  130    format('~`-t~52|~n'),
  131    forall(current_thread_pool(Pool), show_pool(Pool)),
  132    format('~`-t~52|~n').
  133
  134show_pool(Pool) :-
  135    findall(P, thread_pool_property(Pool, P), List),
  136    memberchk(size(Size), List),
  137    memberchk(running(Running), List),
  138    memberchk(backlog(Waiting), List),
  139    memberchk(options(Options), List),
  140    option(backlog(MaxBackLog), Options, infinite),
  141    format('~w~t~20|~t~D  ~8+~t~D ~8+~t~D  ~8+~t~w  ~8+~n',
  142           [Pool, Running, Size, Waiting, MaxBackLog]).
  143
  144stop :-
  145    halt(42)