1:- module(bc_main, [
2 bc_main/1, 3 bc_main/2 4]).
9:- set_prolog_flag(encoding, utf8). 10
11:- use_module(bc_env). 12:- use_module(bc_dep). 13
16
17user:message_hook(Term, _, _):-
18 Term = error(bc_dep:_, _),
19 message_to_string(Term, String),
20 writeln(user_error, String),
21 halt(1).
22
24
25:- bc_check_dependencies. 26
27:- load_settings('settings.db'). 28
29:- use_module(library(dcg/basics)). 30:- use_module(library(http/thread_httpd)). 31:- use_module(library(http/http_error)). 32:- use_module(library(debug)). 33:- use_module(library(docstore)). 34:- use_module(library(arouter)). 35:- use_module(library(st/st_expr)). 36:- use_module(library(st/st_file)). 37:- use_module(library(st/st_parse)). 38
40
41:- debug(http(error)). 42
43:- use_module(bc_api). 44:- use_module(bc_router). 45:- use_module(bc_bust). 46:- use_module(bc_view). 47:- use_module(bc_admin). 48:- use_module(bc_excerpt). 49:- use_module(bc_data). 50:- use_module(bc_migrate). 51:- use_module(bc_search). 52:- use_module(bc_mail_queue). 53:- use_module(bc_analytics). 54
57
58:- if(bc_env_production). 59 :- bc_view_enable_cache. 60 :- bc_enable_expires. 61 :- bc_mail_set_behavior(send). 62:- else. 63 :- write(user_error, 'Running in development mode!'), nl(user_error). 64 :- debug(arouter). 65 :- debug(docstore). 66 :- debug(bc_data). 67 :- debug(bc_migrate). 68 :- debug(bc_router). 69 :- debug(bc_view). 70 :- debug(bc_bust). 71 :- debug(bc_main). 72 :- debug(bc_type). 73 :- debug(bc_role). 74 :- debug(bc_search). 75 :- debug(bc_mail). 76 :- debug(bc_comment). 77 :- debug(bc_action). 78 :- debug(bc_analytics). 79:- endif. 80
82
83:- st_set_function(excerpt, 2, bc_excerpt). 84
85:- dynamic(initialized/0).
92bc_main(_):-
93 initialized, !.
94
95bc_main(File):-
96 bc_data_open(File),
97 http_options(Options),
98 debug(bc_main, 'running with HTTP options: ~w', [Options]),
99 http_server(bc_route, Options),
100 asserta(initialized).
101
106
107:- setting(port, number, 80, 'Port to run on.'). 108
109:- setting(workers, number, 16, 'Number of HTTP threads.'). 110
111:- setting(ip, atom, '0.0.0.0', 'Interface to bind to.').
117http_options(Options):-
118 port_option(Port),
119 ip_option(Ip),
120 workers_option(Workers),
121 Options = [
122 port(Ip:Port),
123 workers(Workers) ].
132port_option(Port):-
133 current_prolog_flag(argv, Argv),
134 ( find_port_option(Argv, Port)
135 -> true
136 ; setting(port, Port)).
137
138find_port_option([Arg|Argv], Port):-
139 atom_codes(Arg, Codes),
140 ( phrase(port_option_parse(Port), Codes)
141 -> true
142 ; find_port_option(Argv, Port)).
143
144port_option_parse(Port) -->
145 "--port=", integer(Port), { Port > 0 }.
154workers_option(Workers):-
155 current_prolog_flag(argv, Argv),
156 ( find_workers_option(Argv, Workers)
157 -> true
158 ; setting(workers, Workers)).
159
160find_workers_option([Arg|Argv], Workers):-
161 atom_codes(Arg, Codes),
162 ( phrase(workers_option_parse(Workers), Codes)
163 -> true
164 ; find_workers_option(Argv, Workers)).
165
166workers_option_parse(Workers) -->
167 "--workers=", integer(Workers), { Workers > 0 }.
176ip_option(Ip):-
177 current_prolog_flag(argv, Argv),
178 ( find_ip_option(Argv, Ip)
179 -> true
180 ; setting(ip, Ip)).
181
182find_ip_option([Arg|Argv], Ip):-
183 atom_codes(Arg, Codes),
184 ( phrase(ip_option_parse(Ip), Codes)
185 -> true
186 ; find_ip_option(Argv, Ip)).
187
188ip_option_parse(Ip) -->
189 "--ip=", nonblanks(Codes), { atom_codes(Ip, Codes) }.
197bc_main(_, _):-
198 initialized, !.
199
200bc_main(File, Options):-
201 bc_data_open(File),
202 http_server(bc_route, Options),
203 asserta(initialized)
The main module
*/