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