View source with formatted comments or as raw
    1/*  Part of ClioPatria
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://cliopatria.swi-prolog.org
    6    Copyright (c)  2010-2018, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(cp_server,
   38          [ cp_server/0,
   39            cp_server/1,                % +Options
   40            cp_welcome/0,
   41            cp_after_load/1             % :Goal
   42          ]).   43
   44/** <module> ClioPatria main module
   45
   46This module loads the ClioPatria  server   as  a  library, providing the
   47public predicates defined in the header.   Before loading this file, the
   48user should set up a the search path =cliopatria=. For example:
   49
   50  ==
   51  :- dynamic
   52          user:file_search_path/2.
   53  :- multifile
   54          user:file_search_path/2.
   55
   56  user:file_search_path(cliopatria, '/usr/local/cliopatria').
   57
   58  :- use_module(cliopatria(cliopatria)).
   59  ==
   60
   61@see http://cliopatria.swi-prolog.org
   62*/
   63
   64:- dynamic
   65    user:file_search_path/2.   66:- multifile
   67    user:file_search_path/2.   68
   69:- (   user:file_search_path(cliopatria, _)
   70   ->  true
   71   ;   prolog_load_context(directory, Dir),
   72       assert(user:file_search_path(cliopatria, Dir))
   73   ).   74
   75user:file_search_path(library, cliopatria(lib)).
   76
   77:- use_module(library(version)).   78:- check_prolog_version(or(70600, 70514)).              % Demand >= 7.6.0, 7.5.14
   79:- register_git_module('ClioPatria',
   80                       [ home_url('http://cliopatria.swi-prolog.org/')
   81                       ]).   82
   83:- use_module([ parms,
   84                skin(cliopatria),                       % HTML Page layout
   85                library(option),
   86                library(bundle),
   87                library(debug),
   88                library(lists),
   89                library(settings),
   90                library(error),
   91                library(broadcast),
   92                library(thread_pool),
   93                library(apply),
   94
   95                library(semweb/rdf_db),
   96                library(semweb/rdf_persistency),
   97                library(semweb/rdf_litindex),
   98                library(semweb/rdf_ntriples),
   99
  100                library(http/http_session),
  101                library(http/http_server_files),
  102                library(http/http_dispatch),
  103                library(http/thread_httpd),
  104
  105                user(user_db),
  106                user(openid),
  107                user(preferences),
  108
  109                api(sesame),
  110                api(journal),                   % export journal information
  111                api(sparql),
  112                api(export),
  113                api(void),
  114
  115                applications(admin),
  116                applications(user),
  117                applications(browse),
  118                applications(yasgui),
  119
  120                library(conf_d),
  121                user:library(cpack/cpack)
  122              ]).  123
  124:- if(exists_source(library(http/http_dyn_workers))).  125:- use_module(library(http/http_dyn_workers)).  126:- endif.  127
  128:- http_handler(web(.), serve_files_in_directory(web), [prefix]).  129
  130:- dynamic
  131    after_load_goal/1.  132
  133%!  cp_server is det.
  134%!  cp_server(:Options) is det.
  135%
  136%   Start the HTTP server.  This predicate preforms the following
  137%   steps:
  138%
  139%       1. Load application settings from =|settings.db|=
  140%       2. Load user-data from =|users.db|=
  141%       3. Start the HTTP server
  142%       4. Load the RDF persistent database from =|RDF-store|=
  143%       5. Execute `after load' options registered using
  144%          cp_after_load/1.
  145%
  146%   Defined options are:
  147%
  148%       * port(Port)
  149%       Attach to Port instead of the port specified in the
  150%       configuration file settings.db.
  151%       * workers(+Count)
  152%       Number of worker threads to use.  Default is the setting
  153%       =|http:workers|=
  154%       * prefix(+Prefix)
  155%       Rebase the server.  See also the setting =|http:prefix|=.
  156%       * store(+Store)
  157%       Directory to use as persistent store. See also the
  158%       setting =|cliopatria:persistent_store|=.
  159%       * settings(+Settings)
  160%       Settings file.  Default is =settings.db=.
  161
  162:- meta_predicate
  163    cp_server(:).  164
  165cp_server :-
  166    current_prolog_flag(argv, [cpack|Argv]),
  167    !,
  168    load_conf_d([ 'config-enabled' ], []),
  169    cpack_control(Argv).
  170:- if(current_predicate(http_unix_daemon:http_daemon/0)).  171cp_server :-
  172    http_unix_daemon:http_daemon.
  173:- else.  174cp_server :-
  175    process_argv(Options, PrologFiles, RDFInputs),
  176    load_application(Options),
  177    user:maplist(ensure_loaded, PrologFiles),
  178    catch(cp_server([rdf_load(RDFInputs)|Options]), E, true),
  179    (   var(E)
  180    ->  set_prolog_flag(toplevel_goal, prolog) % become interactive
  181    ;   print_message(error, E),
  182        (   E = error(socket_error('Address already in use'), _)
  183        ->  print_message(error, cliopatria(use_port_option))
  184        ;   true
  185        )
  186    ).
  187:- endif.  188
  189cp_server(_Options) :-
  190    setting(http:port, DefPort),
  191    http_server_property(DefPort, goal(cp_server:http_dispatch)),
  192    !,
  193    print_message(informational,
  194                  cliopatria(server_already_running(DefPort))).
  195cp_server(Options) :-
  196    meta_options(is_meta, Options, QOptions),
  197    load_application(QOptions),
  198    option(settings(SettingsFile), QOptions, 'settings.db'),
  199    load_settings(SettingsFile),
  200    set_prefix(QOptions),
  201    attach_account_info,
  202    set_session_options,
  203    create_log_directory,
  204    setting(http:port, DefPort),
  205    setting(http:workers, DefWorkers),
  206    setting(http:worker_options, Settings),
  207    https_options(HTTPSOptions),
  208    merge_options(QOptions, Settings, HTTPOptions0),
  209    merge_options(HTTPOptions0, HTTPSOptions, HTTPOptions),
  210    option(port(Port), QOptions, DefPort),
  211    update_public_port(Port, DefPort),
  212    option(workers(Workers), QOptions, DefWorkers),
  213    http_server(http_dispatch,
  214                [ port(Port),
  215                  workers(Workers)
  216                | HTTPOptions
  217                ]),
  218    option(after_load(AfterLoad), QOptions, true),
  219    option(rdf_load(RDFInputs), QOptions, []),
  220    print_message(informational, cliopatria(server_started(Port))),
  221    setup_call_cleanup(
  222        http_handler(root(.), busy_loading,
  223                     [ priority(1000),
  224                       hide_children(true),
  225                       id(busy_loading),
  226                       prefix
  227                     ]),
  228        rdf_attach_store(QOptions, after_load(AfterLoad, RDFInputs)),
  229        http_delete_handler(id(busy_loading))).
  230
  231is_meta(after_load).
  232
  233:- public after_load/2.  234
  235:- meta_predicate
  236    after_load(0, +).  237
  238after_load(AfterLoad, RDFInputs) :-
  239    forall(member(Input, RDFInputs),
  240           call_warn(rdf_load(Input))),
  241    call(AfterLoad).
  242
  243set_prefix(Options) :-
  244    option(prefix(Prefix), Options),
  245    \+ setting(http:prefix, Prefix),
  246    !,
  247    set_setting_default(http:prefix, Prefix).
  248set_prefix(_).
  249
  250%!  update_public_port(+Port, +DefPort)
  251%
  252%   Update http:public_port if port is   changed  using --port=Port.
  253%   Without this hack it is no longer  to login after using the port
  254%   option.
  255
  256update_public_port(Port, Port) :- !.
  257update_public_port(Port, DefPort) :-
  258    setting(http:public_port, DefPort),
  259    !,
  260    set_setting_default(http:public_port, Port),
  261    assertion(setting(http:public_port, Port)).
  262update_public_port(_, _).
  263
  264
  265%!  load_application(+Options)
  266%
  267%   Load cpack and local configuration.
  268
  269:- dynamic
  270    application_loaded/0.  271:- volatile
  272    application_loaded/0.  273
  274load_application(_Options) :-
  275    application_loaded,
  276    !.
  277load_application(_Options) :-
  278    load_conf_d([ cliopatria('config-enabled'),
  279                  'config-enabled'
  280                ], []),
  281    load_local,
  282    assertz(application_loaded).
  283
  284load_local :-
  285    absolute_file_name(local, Local,
  286                       [ file_type(prolog),
  287                         access(read),
  288                         file_errors(fail)
  289                       ]),
  290    !,
  291    print_message(informational, conf_d(load(Local))),
  292    ensure_loaded(user:Local).
  293load_local.
  294
  295%!  rdf_attach_store(+Options, :AfterLoad) is det.
  296%
  297%   Attach     the     RDF     store       using     the     setting
  298%   cliopatria:persistent_store and call the `after-load' goals.
  299%
  300%   @see cp_after_load/1 for registering after-load goals.
  301
  302:- meta_predicate
  303    rdf_attach_store(+, 0),
  304    call_warn(0).  305
  306rdf_attach_store(Options, AfterLoad) :-
  307    (   option(store(Directory), Options)
  308    ->  true
  309    ;   setting(cliopatria:persistent_store, Directory)
  310    ),
  311    setup_indices,
  312    (   Directory \== ''
  313    ->  rdf_attach_db(Directory, Options)
  314    ;   true
  315    ),
  316    forall(after_load_goal(Goal),
  317           call_warn(Goal)),
  318    call_warn(AfterLoad).
  319
  320call_warn(Goal) :-
  321    (   catch(Goal, E, true)
  322    ->  (   var(E)
  323        ->  true
  324        ;   print_message(warning, E)
  325        )
  326    ;   print_message(warning, goal_failed(Goal))
  327    ).
  328
  329
  330%!  setup_indices is det.
  331%
  332%   Initialize maintenance of the full-text   indices. These indices
  333%   are created on first call and  maintained dynamically as the RDF
  334%   store changes. By initializing them  before   there  is  any RDF
  335%   loaded, they will be built while  the data is (re-)loaded, which
  336%   avoids long delays on the first  query.   Note  that most of the
  337%   work is done in a separate thread.
  338
  339setup_indices :-
  340    setting(cliopatria:pre_index_tokens, true),
  341    rdf_find_literals(not_a_token, _),
  342    fail.
  343setup_indices :-
  344    setting(cliopatria:pre_index_stems, true),
  345    rdf_find_literals(stem(not_a_stem), _),
  346    fail.
  347setup_indices.
  348
  349
  350%!  cp_after_load(:Goal) is det.
  351%
  352%   Register Goal to be executed after  reloading the RDF persistent
  353%   DB. Note that  already  registered   goals  are  not duplicated.
  354%   Running a goal after loading the   database  is commonly used to
  355%   ensure presence of relevant schemas or build additional indices.
  356%   Note that it is possible to   start  a thread for time-consuming
  357%   tasks (see thread_create/3).
  358
  359:- meta_predicate
  360    cp_after_load(0).  361
  362cp_after_load(Goal) :-
  363    (   after_load_goal(Goal)
  364    ->  true
  365    ;   assert(after_load_goal(Goal))
  366    ).
  367
  368
  369%!  busy_loading(+Request)
  370%
  371%   This HTTP handler is  pushed  to   overrule  all  actions of the
  372%   server while the server is restoring   its  persistent state. It
  373%   replies with the 503  (unavailable)   response,  indicating  the
  374%   progress of restoring the repository.
  375
  376:- dynamic
  377    loading_done/2.  378
  379busy_loading(_Request) :-
  380    rdf_statistics(triples(Triples)),
  381    (   loading_done(Nth, Total)
  382    ->  Extra = [ '; ~D of ~D graphs.'-[Nth, Total] ]
  383    ;   Extra = [ '.' ]
  384    ),
  385    HTML = p([ 'This service is currently restoring its ',
  386               'persistent database.', br([]),
  387               'Loaded ~D triples'-[Triples]
  388             | Extra
  389             ]),
  390    throw(http_reply(unavailable(HTML))).
  391
  392%!  attach_account_info
  393%
  394%   Set   the   registered   user-database     from    the   setting
  395%   cliopatria:user_data.
  396
  397attach_account_info :-
  398    setting(cliopatria:user_data, File),
  399    set_user_database(File).
  400
  401%!  set_session_options
  402%
  403%   Initialise session timeout from =|http:max_idle_time|=.
  404
  405set_session_options :-
  406    setting(http:max_idle_time, Idle),
  407    http_set_session_options([timeout(Idle)]).
  408
  409%!  create_log_directory
  410%
  411%   Create the directory in which the log files reside.
  412
  413create_log_directory :-
  414    current_setting(http:logfile),
  415    setting(http:logfile, File), File \== '',
  416    file_directory_name(File, DirName),
  417    DirName \== '.',
  418    !,
  419    catch(make_directory_path(DirName), E,
  420          print_message(warning, E)).
  421create_log_directory.
  422
  423
  424                 /*******************************
  425                 *       UPDATE SETTINGS        *
  426                 *******************************/
  427
  428update_workers(New) :-
  429    setting(http:port, Port),
  430    http_current_worker(Port, _),
  431    http_workers(Port, New).
  432
  433:- listen(settings(changed(http:max_idle_time, _, New)),
  434          http_set_session_options([timeout(New)])).  435:- listen(settings(changed(http:workers, _, New)),
  436          update_workers(New)).  437
  438
  439                 /*******************************
  440                 *             ARGV             *
  441                 *******************************/
  442
  443%!  process_argv(-Options, -PrologFiles, -RDFInputs)
  444%
  445%   Processes the ClioPatria commandline options.
  446
  447process_argv(Options, PrologFiles, RDFInputs) :-
  448    current_prolog_flag(argv, Argv),
  449    current_prolog_flag(os_argv, [Program|_]),
  450    (   Argv == ['--help']
  451    ->  usage(Program)
  452    ;   catch((   parse_options(Argv, Options, Rest),
  453                  maplist(load_argument, Rest, Load),
  454                  keysort(Load, Sorted),
  455                  group_pairs_by_key(Sorted, Keyed),
  456                  (   memberchk(prolog-PrologFiles, Keyed)
  457                  ->  true
  458                  ;   PrologFiles = []
  459                  ),
  460                  (   memberchk(rdf-RDFInputs, Keyed)
  461                  ->  true
  462                  ;   RDFInputs = []
  463                  )
  464              ),
  465              E,
  466              (   print_message(error, E),
  467                  fail
  468              ))
  469    ->  true
  470    ;   usage(Program)
  471    ).
  472
  473load_argument(URL, rdf-URL) :-
  474    (   sub_atom('http://', 0, _, _, URL)
  475    ;   sub_atom('https://', 0, _, _, URL)
  476    ),
  477    !.
  478load_argument(File, Type-File) :-
  479    file_name_extension(_Base, Ext, File),
  480    load_argument(Ext, File, Type).
  481
  482load_argument(Ext, _File, prolog) :-
  483    user:prolog_file_type(Ext, prolog),
  484    !.
  485load_argument(gz, File, rdf) :-
  486    file_name_extension(Plain, gz, File),
  487    file_name_extension(_, RDF, Plain),
  488    rdf_extension(RDF).
  489load_argument(RDF, _File, rdf) :-
  490    rdf_extension(RDF).
  491
  492rdf_extension(rdf).
  493rdf_extension(rdfs).
  494rdf_extension(owl).
  495rdf_extension(ttl).
  496rdf_extension(nt).
  497rdf_extension(ntriples).
  498
  499cmd_option(-, help,       -,                'Print command usage').
  500cmd_option(p, port,       positive_integer, 'Port to connect to').
  501cmd_option(w, workers,    positive_integer, 'Number of workers to start').
  502cmd_option(-, after_load, term,             'Goal to run after loading').
  503cmd_option(-, prefix,     atom,             'Rebase the server to prefix/').
  504cmd_option(-, store,      atom,             'Directory for persistent store').
  505% dummy to stop list_trivial_fail from warning about long_option/2.
  506cmd_option(-, -, boolean, 'Dummy') :- fail.
  507
  508usage(Program) :-
  509    format(user_error,
  510           'Run ClioPatria for interactive usage.~n~n', []),
  511    ansi_format([bold], 'Usage: ~w [options] arguments', [Program]), nl, nl,
  512    flush_output,
  513    forall(cmd_option(Short, Long, Type, Comment),
  514           describe_option(Short, Long, Type, Comment)),
  515    cpack_usage(Program),
  516    describe_argv,
  517    (   current_prolog_flag(hwnd, _)        % swipl-win.exe console
  518    ->  ansi_format([bold,hfg(red)],
  519                    '~nPress \'b\' for break, any other key to exit > ', []),
  520        get_single_char(Key),
  521        (   Key == 0'b
  522        ->  nl, nl, break
  523        ;   true
  524        ),
  525        halt
  526    ;   halt(1)
  527    ).
  528
  529describe_option(-, Long, -, Comment) :-
  530    !,
  531    format(user_error, '    --~w~t~40|~w~n', [Long, Comment]).
  532describe_option(-, Long, _, Comment) :-
  533    !,
  534    format(user_error, '    --~w=~w~t~40|~w~n', [Long, Long, Comment]).
  535describe_option(Short, Long, -, Comment) :-
  536    !,
  537    format(user_error, '    -~w, --~w~t~40|~w~n',
  538           [Short, Long, Comment]).
  539describe_option(Short, Long, _, Comment) :-
  540    !,
  541    format(user_error, '    -~w ~w, --~w=~w~t~40|~w~n',
  542           [Short, Long, Long, Long, Comment]).
  543
  544describe_argv :-
  545    current_prolog_flag(argv, Argv),
  546    (   Argv == ['--help']
  547    ->  true
  548    ;   ansi_format([fg(red)], 'Program argv: ~q~n', [Argv])
  549    ).
  550
  551cpack_usage(Program) :-
  552    nl, ansi_format([bold], 'CPACK commands', []), nl, nl,
  553    flush_output,
  554    format(user_error, '   ~w cpack install pack ...~n', [Program]),
  555    format(user_error, '   ~w cpack upgrade pack ...~n', [Program]),
  556    format(user_error, '   ~w cpack configure pack ...~n', [Program]).
  557
  558parse_options([], [], []).
  559parse_options([--|Rest], [], Rest) :- !.
  560parse_options([H|T], [Opt|OT], Rest) :-
  561    sub_atom(H, 0, _, _, --),
  562    !,
  563    (   sub_atom(H, B, _, A, =)
  564    ->  B2 is B - 2,
  565        sub_atom(H, 2, B2, _, Name),
  566        sub_atom(H, _, A,  0, Value),
  567        long_option(Name, Value, Opt)
  568    ;   sub_atom(H, 2, _, 0, Name),
  569        long_option(Name, Opt)
  570    ),
  571    parse_options(T, OT, Rest).
  572parse_options([H|T], Opts, Rest) :-
  573    atom_chars(H, [-|Opts]),
  574    !,
  575    short_options(Opts, T, Opts, Rest).
  576parse_options(Rest, [], Rest).
  577
  578short_options([], Av, Opts, Rest) :-
  579    parse_options(Av, Opts, Rest).
  580short_options([H|T], Av, [Opt|OptT], Rest) :-
  581    cmd_option(H, Name, Type, _),
  582    (   Type == (-)
  583    ->  Opt =.. [Name,true],
  584        short_options(T, Av, OptT, Rest)
  585    ;   Av = [Av0|AvT],
  586        text_to_value(Type, Av0, Value),
  587        Opt =.. [Name,Value],
  588        short_options(T, AvT, OptT, Rest)
  589    ).
  590
  591long_option(Name, Text, Opt) :-
  592    cmd_option(_, Name, Type, _),
  593    text_to_value(Type, Text, Value),
  594    Opt =.. [Name,Value].
  595
  596long_option(Name, Opt) :-
  597    atom_concat('no-', OptName, Name),
  598    cmd_option(_, OptName, boolean, _),
  599    !,
  600    Opt =.. [Name,false].
  601long_option(Name, Opt) :-
  602    cmd_option(_, Name, boolean, _),
  603    Opt =.. [Name,true].
  604
  605text_to_value(boolean, Text, Value) :-
  606    downcase_atom(Text, Lwr),
  607    boolean(Lwr, Value).
  608text_to_value(atom, Text, Text).
  609text_to_value(oneof(L), Text, Text) :-
  610    memberchk(Text, L).
  611text_to_value(integer, Text, Int) :-
  612    atom_number(Text, Int), integer(Int).
  613text_to_value(nonneg, Text, Int) :-
  614    atom_number(Text, Int), integer(Int), Int >= 0.
  615text_to_value(positive_integer, Text, Int) :-
  616    atom_number(Text, Int), integer(Int), Int > 0.
  617text_to_value(negative_integer, Text, Int) :-
  618    atom_number(Text, Int), integer(Int), Int < 0.
  619text_to_value(float, Text, Float) :-
  620    atom_number(Text, Number), Float = float(Number).
  621text_to_value(term, Text, Term) :-
  622    atom_to_term(Text, Term, _).
  623
  624boolean(true,  true).
  625boolean(yes,   true).
  626boolean(on,    true).
  627boolean(false, false).
  628boolean(no,    false).
  629boolean(off,   false).
  630
  631
  632                 /*******************************
  633                 *             CPACK            *
  634                 *******************************/
  635
  636%!  cpack_control(+Commands:list)
  637%
  638%   Execute a CPACK configuration instruction.  For example:
  639%
  640%       ./run.pl cpack install swish
  641
  642cpack_control([install|Packs]) :-
  643    !,
  644    maplist(cpack_install, Packs).
  645cpack_control([configure|Packs]) :-
  646    !,
  647    maplist(cpack_configure, Packs).
  648cpack_control([upgrade|Packs]) :-
  649    !,
  650    (   Packs == []
  651    ->  cpack_upgrade
  652    ;   maplist(cpack_upgrade, Packs)
  653    ).
  654cpack_control(Command) :-
  655    domain_error(cpack_command, Command).
  656
  657
  658                 /*******************************
  659                 *            BANNER            *
  660                 *******************************/
  661
  662%!  cp_welcome
  663%
  664%   Print welcome banner.
  665
  666cp_welcome :-
  667    setting(http:port, Port),
  668    print_message(informational, cliopatria(welcome(Port))).
  669
  670
  671                 /*******************************
  672                 *             POOLS            *
  673                 *******************************/
  674
  675:- multifile
  676    http:create_pool/1.  677
  678:- setting(cliopatria:max_clients, integer, 50,
  679           'Max number of concurrent requests in ClioPatria pool').  680:- if(current_prolog_flag(address_bits, 32)).  681:- setting(cliopatria:stack_size, integer, 128,
  682           'Stack limit in MB for ClioPatria pool').  683:- else.  684:- setting(cliopatria:stack_size, integer, 1024,
  685           'Stack limit in MB for ClioPatria pool').  686:- endif.  687
  688%!  http:create_pool(+Pool) is semidet.
  689%
  690%   Create a thread-pool on-demand.
  691
  692http:create_pool(sparql_query) :-
  693    debug(http(pool), 'Demand-creating pool ~q', [sparql_query]),
  694    setting(sparql:max_clients, Count),
  695    setting(sparql:stack_size, MB),
  696    Global is MB * 1024,
  697    Trail is MB * 1024,
  698    thread_pool_create(sparql_query,
  699                       Count,
  700                       [ global(Global),
  701                         trail(Trail)
  702                       ]).
  703http:create_pool(cliopatria) :-
  704    setting(cliopatria:max_clients, Count),
  705    setting(cliopatria:stack_size, MB),
  706    Global is MB * 1024,
  707    Trail is MB * 1024,
  708    thread_pool_create(cliopatria,
  709                       Count,
  710                       [ global(Global),
  711                         trail(Trail)
  712                       ]).
  713
  714
  715                 /*******************************
  716                 *            HTTPS             *
  717                 *******************************/
  718
  719%!  https_options(-Options) is det.
  720%
  721%   Fetch options for running an HTTPS   server.  HTTP is started if
  722%   there is a directory =https= with these files:
  723%
  724%     $ =|server-cert.pem|= :
  725%     Contains the server certificate.  This may be omitted, in
  726%     which case the =|server-key.pem|= is also passed using the
  727%     key_file(+File) option.
  728%     $ =|server-key.pem|= :
  729%     Contains the private key for the server.
  730%     % =|passwd|= :
  731%     Needs to hold the password if the private key is protected
  732%     with a password.
  733
  734https_options(Options) :-
  735    https_file('server-key.pem', KeyFile),
  736    !,
  737    (   https_file('server-cert.pem', CertFile)
  738    ->  true
  739    ;   CertFile = KeyFile
  740    ),
  741    Options = [ ssl([ certificate_file(CertFile),
  742                      key_file(KeyFile)
  743                    | PasswdOption
  744                    ])
  745              ],
  746    (   https_file(passwd, PasswordFile)
  747    ->  read_file_to_string(PasswordFile, Content, []),
  748        split_string(Content, "", " \n\r", [Passwd]),
  749        PasswdOption = [password(Passwd)]
  750    ;   PasswdOption = []
  751    ).
  752https_options([]).
  753
  754https_file(Base, File) :-
  755    absolute_file_name(config_https(Base), File,
  756                       [ access(read),
  757                         file_errors(fail)
  758                       ]).
  759
  760
  761
  762                 /*******************************
  763                 *           MESSAGES           *
  764                 *******************************/
  765
  766:- multifile
  767    prolog:message//1.  768
  769prolog:message(cliopatria(server_started(_Port))) -->
  770    [].
  771prolog:message(cliopatria(welcome(DefaultPort))) -->
  772    [ nl,
  773      'Use one of the calls below to start the ClioPatria server:', nl, nl,
  774      '  ?- cp_server.               % start at port ~w'-[DefaultPort], nl,
  775      '  ?- cp_server([port(Port)]). % start at Port'
  776    ].
  777prolog:message(cliopatria(use_port_option)) -->
  778    [ '   Could not start the HTTP server!', nl,
  779      '   Choose a different port using ./run.pl --port=<port> or', nl,
  780      '   use the network plugin to change the default port.'
  781    ].
  782prolog:message(cliopatria(server_already_running(Port))) -->
  783    { cp_host(Port, Host),
  784      cp_port(Port, PublicPort),
  785      http_location_by_id(root, Root)
  786    },
  787    [ 'CliopPatria server is already running at http://~w:~w~w'-
  788      [Host, PublicPort, Root]
  789    ].
  790
  791cp_host(_, Host) :-
  792    setting(http:public_host, Host),
  793    Host \== '',
  794    !.
  795cp_host(Host:_, Host) :- !.
  796cp_host(_,Host) :-
  797    gethostname(Host).
  798
  799cp_port(_ServerPort, PublicPort) :-
  800    setting(http:public_host, Host),
  801    Host \== '', Host \== localhost,
  802    setting(http:public_port, PublicPort),
  803    !.
  804cp_port(_Host:Port, Port) :- !.
  805cp_port(ServerPort, ServerPort).
  806
  807
  808
  809                 /*******************************
  810                 *              HOOKS           *
  811                 *******************************/
  812
  813:- multifile
  814    user:message_hook/3.  815
  816user:message_hook(rdf(restore(_, done(_DB, _T, _Count, Nth, Total))),
  817                  _Kind, _Lines) :-
  818    retractall(loading_done(_,_)),
  819    assert(loading_done(Nth, Total)),
  820    fail.
  821
  822:- multifile
  823    http_unix_daemon:http_server_hook/1. % +Options
  824
  825http_unix_daemon:http_server_hook(Options) :-
  826    cp_server(Options)