:- [mt]. % special -- needs to be before common to prevent loop!
:- use_module(library('semweb/rdf_db')).
:- ensure_loaded(common).
cvs_id('$Id: main.pl,v 1.82 2004/10/19 18:28:41 sandro Exp $').
/*
This orchestrates loading up the system and starting and stopping
the server.
*/
% order sensitive, because they define some term_expansions
% (as did "common", above)
:- ensure_loaded(library('semweb/rdf_db')).
:- ensure_loaded(library('prolog_server')).
:- ensure_loaded(fixed_ns).
% system libraries
%
% pick one httpd; "thread" is used in production, but xpce can make
% some debugging/tracing easier.
:- ensure_loaded(library('http/thread_httpd')).
% :- ensure_loaded(library('http/xpce_httpd')).
:- ensure_loaded(library(unix)).
% everything else
:- ensure_loaded(load_program).
:- print_message(informational, format('Loading remaining modules...', [])).
:- load_program.
:- print_message(informational, format('...program loaded.', [])).
% oh, and the config data. Don't call this part of the program,
% since we don't want to allow dynamic reloading. (Various bits
% of code assume config_data is static.)
:- ensure_loaded(config_data).
% this is a special dangerous bit: loading it causes calls to
% print_message/2 to be intercepted and re-directed based on
% some configuration information. Problems in this code can
% cause especially myserious results. We load it last so that
% load errors are unlikely to be hidden. It shouldn't actually
% be DOING anything yet, because we haven't read the configuration
% information it will need as guidance.
:- ensure_loaded(message_hook).
:- dynamic main_process.
% thing we can initialize before we know the IP Port number
pre_port_configure :-
get_time(StartTime),
retractall(semwalker_start_time(_)),
assert(semwalker_start_time(StartTime)),
set_prolog_flag(float_format, '%.16g'),
set_prolog_flag(unknown, error), % raise an error on unknown predicate
handle_argv,
app_db_init,
persistent_term_index_open.
% thing we need the IP Port number for
post_port_configure :-
configure_hostname,
configure_site_uri,
configure_rdfpage,
configure_self_uri,
configure_about_this_run.
:- dynamic server_down/1.
:- assert(server_down('Server Booting... Please wait.')).
serverStatusLine(['Process started ', +reltime(Start), ', ', int(Triples), ' triples paged in.']) :-
semwalker_start_time(Start),
rdf_statistics(triples(Triples)).
reply_stage_0(X) :-
( server_down(Message)
-> Head = [ title('temporary error') ],
Body = [h2(Message), p(+serverStatusLine)],
format('Content-type: text/html~n~n', []),
write_html(html(head(Head), body(Body)))
; thread_state_call(reload_program_if_safe),
thread_set_state(generating_reply),
reply_stage_1(X),
thread_set_state(transmit_and_wait)
).
init :-
( current_prolog_flag(saved_program, true)
-> print_message(informational,
format('running as saved_program', []))
; print_message(informational,
format('running with dynamic-reloading (not saved_program)', []))
),
pre_port_configure,
assert(main_process),
catch_signals,
run_unit_tests,
run_qtests(Arg, (atomic(Arg) ; Arg=anon(_))).
main :-
init,
start_prolog_console_server,
start_log_writer,
start_server,
truePID(PID),
write_status_file(pidfile, PID),
!,
% do this after writing the port file to make control easier
% there's a little window between starting the server and finishing the config
% because we may not know our port number until we start the server, and we
% may need that port number to build URIs for ourself. The server_ready flag
% at least lets us respond intelligently to requests made during that window.
post_port_configure,
!,
start_indexer,
start_harvest_threads,
start_to_monitor_transfers,
load_retrievals, % before server comes up?
retractall(server_down(_)),
( cmd_line_daemon
-> %print_message(informational,
% format('detaching IO for daemon mode', [])),
% detach_IO,
print_message(informational,
format('waiting for shutdown signal', [])),
wait_for_shutdown
; print_message(informational,
format('main/0 ending -- leaving you in prolog shell', []))
).
/*
ALAS, the fork() seems to really confuse the multithreading....
( cmd_line_daemon
-> print_message(informational, format('detaching to run daemon server.', [])),
fork(ChildId),
( ChildId = child
-> write_pid_file,
detach_IO,
start_server,
begin_precache,
wait_for_shutdown
; retract(main_process),
halt
)
; start_server,
begin_precache
).
*/
start_server :-
app_config(port, PortAtom),
( PortAtom=auto
-> true
; atom_number(PortAtom, Port),
print_message(informational,
format('starting server on port ~w...', [Port]))
),
between(1,100,_X),
( catch(
http_server(reply_stage_0, [port(Port), workers(8), timeout(10), local(32768), global(32768), trail(4096), arg(1024), stack(1024)]),
Err,
( print_message(error, format('server startup error: ~q', Err)),
fail
)
)
-> true
; print_message(warning, format('server failed; sleep and retry...', [Port])),
sleep(1),
fail
),
print_message(informational,
format('server ready on port ~a', [Port])),
atom_number(NewPortAtom, Port),
retractall(app_config(port, _)),
assert(app_config(port, NewPortAtom)),
write_status_file(portfile, Port).
catch_signals :-
on_signal(term, _, shutdown), % perhaps redundant
on_signal(usr1, _, shutdown),
on_signal(hup, _, shutdown).
wait_for_shutdown :-
catch_signals,
%print_message(informational,
% format('waiting for shutdown signal (sigUSR1)', [])),
thread_get_message(quit).
shutdown(Signal) :-
app_config(port, PortAtom),
atom_number(PortAtom, Port),
print_message(informational,
format('shutting down port ~a service in response to "~q" signal', [Port, Signal])),
http_workers(Port, 0),
get_time(Start),
( between(1, 100, Count),
http_workers(Port, W),
sleep(0.05),
get_time(Now),
Dur is Now - Start,
( W=0
-> print_message(informational,
format('all workers gone (t=~a sec); normal shutdown', [Dur])),
halt
; true
),
print_message(informational,
format('round ~a: ~w workers after ~a sec...', [Count, W, Dur])),
fail
; http_workers(Port, W),
print_message(informational,
format('~w workers remain; halting anyway', [W])),
halt
).
write_status_file(ItemName, Value) :-
( app_config_file(ItemName, FileName)
-> open_p(FileName, write, Fd, []),
format(Fd, '~a~n', [Value]),
close(Fd),
print_message(informational,
format('~a written to ~q', [Value, FileName])),
at_halt(( main_process,
delete_file(FileName),
print_message(informational,
format('halting; ~a removed.', [ItemName]))
))
; true
).
start_prolog_console_server :-
( app_config(prolog_console_port, PortSpec),
\+ PortSpec = down
-> ( PortSpec = any
-> Port = _
; Port = PortSpec
),
prolog_server(Port, []),
print_message(informational,
format('prolog console server STARTED on port ~w', [Port])),
write_status_file(prolog_console_port_file, Port)
; print_message(informational,
format('prolog console server NOT STARTED (due to config settings)', []))
).
/*
Test?
while curl -s http://127.0.0.1:7116/ -o /dev/null; do echo -n . ; done
beware:
futex(0x811b190, FUTEX_WAIT, 4, NULL <unfinished ...>
while true; do
for x in `cat uris`; do curl -s "$x" -o /dev/null; echo -n . ; done
done
*/
Webmaster