Skip to content

Commit 4a2484e

Browse files
committed
ENHANCED: library(http/http_unix_daemon) to use argv_options/3 in
_guided_ mode. This simplifies adding options and defaults for applications using this library and simplifies maintenance.
1 parent e62c9a0 commit 4a2484e

File tree

1 file changed

+92
-41
lines changed

1 file changed

+92
-41
lines changed

http_unix_daemon.pl

+92-41
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
Author: Jan Wielemaker
44
55
WWW: http://www.swi-prolog.org
6-
Copyright (c) 2013-2022, University of Amsterdam
6+
Copyright (c) 2013-2023, University of Amsterdam
77
VU University Amsterdam
88
CWI, Amsterdam
99
SWI-Prolog Solutions b.v.
@@ -37,7 +37,10 @@
3737

3838
:- module(http_unix_daemon,
3939
[ http_daemon/0,
40-
http_daemon/1 % +Options
40+
http_daemon/1, % +Options
41+
http_opt_type/3, % ?Flag, ?Option, ?Type
42+
http_opt_help/2, % ?Option, ?Help
43+
http_opt_meta/2 % ?Option, ?Meta
4144
]).
4245
:- use_module(library(error)).
4346
:- use_module(library(apply)).
@@ -287,7 +290,10 @@
287290
%
288291
% http_daemon/0 is defined as below. The start code for a specific
289292
% server can use this as a starting point, for example for specifying
290-
% defaults.
293+
% defaults or additional options. This uses _guided_ options
294+
% processing from argv_options/3 from library(main). The option
295+
% definitions are available as http_opt_type/3, http_opt_help/2 and
296+
% http_opt_meta/2
291297
%
292298
% ```
293299
% http_daemon :-
@@ -303,6 +309,89 @@
303309
argv_options(Argv, _RestArgv, Options),
304310
http_daemon(Options).
305311

312+
% Option declarations for argv_options/3 from library(main).
313+
314+
opt_type(port, port, nonneg).
315+
opt_type(p, port, nonneg).
316+
opt_type(ip, ip, atom).
317+
opt_type(debug, debug, term).
318+
opt_type(syslog, syslog, atom).
319+
opt_type(user, user, atom).
320+
opt_type(group, group, atom).
321+
opt_type(pidfile, pidfile, file(write)).
322+
opt_type(output, output, file(write)).
323+
opt_type(fork, fork, boolean).
324+
opt_type(http, http, nonneg|boolean).
325+
opt_type(https, https, nonneg|boolean).
326+
opt_type(certfile, certfile, file(read)).
327+
opt_type(keyfile, keyfile, file(read)).
328+
opt_type(pwfile, pwfile, file(read)).
329+
opt_type(password, password, string).
330+
opt_type(cipherlist, cipherlist, string).
331+
opt_type(redirect, redirect, string).
332+
opt_type(interactive, interactive, boolean).
333+
opt_type(i, interactive, boolean).
334+
opt_type(gtrace, gtrace, boolean).
335+
opt_type(sighup, sighup, oneof([reload,quit])).
336+
opt_type(workers, workers, natural).
337+
opt_type(timeout, timeout, number).
338+
opt_type(keep_alive_timeout, keep_alive_timeout, number).
339+
340+
opt_help(port, "HTTP port to listen to").
341+
opt_help(ip, "Only listen to this ip (--ip=localhost)").
342+
opt_help(debug, "Print debug message for topic").
343+
opt_help(syslog, "Send output to syslog daemon as ident").
344+
opt_help(user, "Run server under this user").
345+
opt_help(group, "Run server under this group").
346+
opt_help(pidfile, "Write PID to path").
347+
opt_help(output, "Send output to file (instead of syslog)").
348+
opt_help(fork, "Do (default) or do not fork").
349+
opt_help(http, "Create HTTP server").
350+
opt_help(https, "Create HTTPS server").
351+
opt_help(certfile, "The server certificate").
352+
opt_help(keyfile, "The server private key").
353+
opt_help(pwfile, "File holding password for the private key").
354+
opt_help(password, "Password for the private key").
355+
opt_help(cipherlist, "Cipher strings separated by colons").
356+
opt_help(redirect, "Redirect all requests to a URL or port").
357+
opt_help(interactive, "Enter Prolog toplevel after starting server").
358+
opt_help(gtrace, "Start (graphical) debugger").
359+
opt_help(sighup, "Action on SIGHUP: reload (default) or quit").
360+
opt_help(workers, "Number of HTTP worker threads").
361+
opt_help(timeout, "Time to wait for client to complete request").
362+
opt_help(keep_alive_timeout, "Time to wait for a new request").
363+
364+
opt_meta(port, 'PORT').
365+
opt_meta(ip, 'IP').
366+
opt_meta(debug, 'TERM').
367+
opt_meta(http, 'PORT').
368+
opt_meta(https, 'PORT').
369+
opt_meta(syslog, 'IDENT').
370+
opt_meta(user, 'NAME').
371+
opt_meta(group, 'NAME').
372+
opt_meta(redirect, 'URL').
373+
opt_meta(sighup, 'ACTION').
374+
opt_meta(workers, 'COUNT').
375+
opt_meta(timeout, 'SECONDS').
376+
opt_meta(keep_alive_timeout, 'SECONDS').
377+
378+
%! http_opt_type(?Flag, ?Option, ?Type).
379+
%! http_opt_help(?Option, ?Help).
380+
%! http_opt_meta(?Option, ?Meta).
381+
%
382+
% Allow reusing http option processing
383+
384+
http_opt_type(Flag, Option, Type) :-
385+
opt_type(Flag, Option, Type).
386+
387+
http_opt_help(Option, Help) :-
388+
opt_help(Option, Help),
389+
Option \= help(_).
390+
391+
http_opt_meta(Option, Meta) :-
392+
opt_meta(Option, Meta).
393+
394+
306395
%! http_daemon(+Options)
307396
%
308397
% Start the HTTP server as a daemon process. This predicate processes
@@ -329,11 +418,6 @@
329418
% Helper that is started from http_daemon/1. See http_daemon/1 for
330419
% options that are processed.
331420

332-
http_daemon_guarded(Options) :-
333-
option(help(true), Options),
334-
!,
335-
print_message(information, http_daemon(help)),
336-
halt.
337421
http_daemon_guarded(Options) :-
338422
setup_debug(Options),
339423
kill_x11(Options),
@@ -898,39 +982,6 @@
898982
:- multifile
899983
prolog:message//1.
900984

901-
prolog:message(http_daemon(help)) -->
902-
[ 'Usage: <program> option ...'-[], nl,
903-
'Options:'-[], nl, nl,
904-
' --port=port HTTP port to listen to'-[], nl,
905-
' --ip=IP Only listen to this ip (--ip=localhost)'-[], nl,
906-
' --debug=topic Print debug message for topic'-[], nl,
907-
' --syslog=ident Send output to syslog daemon as ident'-[], nl,
908-
' --user=user Run server under this user'-[], nl,
909-
' --group=group Run server under this group'-[], nl,
910-
' --pidfile=path Write PID to path'-[], nl,
911-
' --output=file Send output to file (instead of syslog)'-[], nl,
912-
' --fork=bool Do/do not fork'-[], nl,
913-
' --http[=Address] Create HTTP server'-[], nl,
914-
' --https[=Address] Create HTTPS server'-[], nl,
915-
' --certfile=file The server certificate'-[], nl,
916-
' --keyfile=file The server private key'-[], nl,
917-
' --pwfile=file File holding password for the private key'-[], nl,
918-
' --password=pw Password for the private key'-[], nl,
919-
' --cipherlist=cs Cipher strings separated by colons'-[], nl,
920-
' --redirect=to Redirect all requests to a URL or port'-[], nl,
921-
' --interactive=bool Enter Prolog toplevel after starting server'-[], nl,
922-
' --gtrace=bool Start (graphical) debugger'-[], nl,
923-
' --sighup=action Action on SIGHUP: reload (default) or quit'-[], nl,
924-
' --workers=count Number of HTTP worker threads'-[], nl,
925-
' --timeout=sec Time to wait for client to complete request'-[], nl,
926-
' --keep_alive_timeout=sec'-[], nl,
927-
' Time to wait for a new request'-[], nl,
928-
nl,
929-
'Boolean options may be written without value (true) or as --no-name (false)'-[], nl,
930-
'Address is a port number or host:port, e.g., 8080 or localhost:8080'-[], nl,
931-
'Multiple servers can be started by repeating --http and --https'-[], nl,
932-
'Each server merges the options before the first --http(s) and up the next'-[]
933-
].
934985
prolog:message(http_daemon(no_root(switch_user(User)))) -->
935986
[ 'Program must be started as root to use --user=~w.'-[User] ].
936987
prolog:message(http_daemon(no_root(open_port(Port)))) -->

0 commit comments

Comments
 (0)