
thread_httpd.pl -- Threaded HTTP serverThis library defines the HTTP server frontend of choice for SWI-Prolog. It is based on the multi-threading capabilities of SWI-Prolog and thus exploits multiple cores to serve requests concurrently. The server scales well and can cooperate with library(thread_pool) to control the number of concurrent requests of a given type. For example, it can be configured to handle 200 file download requests concurrently, 2 requests that potentially uses a lot of memory and 8 requests that use a lot of CPU resources.
On Unix systems, this library can be combined with library(http/http_unix_daemon) to realise a proper Unix service process that creates a web server at port 80, runs under a specific account, optionally detaches from the controlling terminal, etc.
Combined with library(http/http_ssl_plugin) from the SSL package, this library can be used to create an HTTPS server. See <plbase>/doc/packages/examples/ssl/https for an example server using a self-signed SSL certificate.
http_server(:Goal, :Options) is detmain thread.
If you need to control resource usage you may consider the
spawn option of http_handler/3 and library(thread_pool).true (default false), do not print an informational
message that the server was started.A typical initialization for an HTTP server that uses http_dispatch/1 to relay requests to predicates is:
:- use_module(library(http/thread_httpd)).
:- use_module(library(http/http_dispatch)).
start_server(Port) :-
http_server(http_dispatch, [port(Port)]).
Note that multiple servers can coexist in the same Prolog process. A notable application of this is to have both an HTTP and HTTPS server, where the HTTP server redirects to the HTTPS server for handling sensitive requests.
http_current_server(:Goal, ?Port) is nondet
http_server_property(?Port, ?Property) is nondethttp or https.
http_workers(+Port, -Workers) is det
http_add_worker(+Port, +Options) is det
http_current_worker(?Port, ?ThreadID) is nondet
http_stop_server(+Port, +Options)
http_enough_workers(+Queue, +Why, +Peer) is det
http:schedule_workers(+Data:dict) is semidet[multifile]accept for a new connection or keep_alive if a
worker tries to reschedule itself.
Note that, when called with reason:accept, we are called in
the time critical main accept loop. An implementation of this
hook shall typically send the event to thread dedicated to
dynamic worker-pool management.
thread_httpd:message_level(+Exception, -Level)[multifile]
http_requeue(+Header)
http_close_connection(+Request)
http_spawn(:Goal, +Options) is detIf a pool does not exist, this predicate calls the multifile hook create_pool/1 to create it. If this predicate succeeds the operation is retried.