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