Most code doesn't need to use this directly; instead use
library(http/http_server), which combines this library with the
typical HTTP libraries that most servers need.
This 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 det
- Create a server at Port that calls Goal for each parsed request.
Options provide a list of options. Defined options are
- port(?Address)
- Port to bind to. Address is either a port or a term
Host:Port. The port may be a variable, causing the system
to select a free port. See tcp_bind/2.
- unix_socket(+Path)
- Instead of binding to a TCP port, bind to a Unix Domain
Socket at Path.
- entry_page(+URI)
- Affects the message printed while the server is started.
Interpreted as a URI relative to the server root.
- tcp_socket(+Socket)
- If provided, use this socket instead of the creating one and
binding it to an address. The socket must be bound to an
address. Note that this also allows binding an HTTP server to
a Unix domain socket (
AF_UNIX
). See socket_create/2.
- workers(+Count)
- Determine the number of worker threads. Default is 5. This
is fine for small scale usage. Public servers typically need
a higher number.
- timeout(+Seconds)
- Maximum time of inactivity trying to read the request after a
connection has been opened. Default is 60 seconds. See
set_stream/1 using the timeout option.
- keep_alive_timeout(+Seconds)
- Time to keep `Keep alive' connections alive. Default is
2 seconds.
- stack_limit(+Bytes)
- Stack limit to use for the workers. The default is inherited
from the
main
thread.
If you need to control resource usage you may consider the
spawn
option of http_handler/3 and library(thread_pool).
- silent(Bool)
- If
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
- True if Goal is the goal of a server at Port.
- deprecated
- - Use
http_server_property(Port, goal(Goal))
- http_server_property(?Port, ?Property) is nondet
- True if Property is a property of the HTTP server running at
Port. Defined properties are:
- goal(:Goal)
- Goal used to start the server. This is often
http_dispatch/1.
- scheme(-Scheme)
- Scheme is one of
http
or https
.
- start_time(?Time)
- Time-stamp when the server was created.
- http_workers(?Port, -Workers) is nondet
- http_workers(+Port, +Workers:int) is det
- Query or set the number of workers for the server at this port. The
number of workers is dynamically modified. Setting it to 1 (one) can
be used to profile the worker using tprofile/1.
- See also
- - library(http/http_dyn_workers) implements dynamic management of
the worker pool depending on usage.
- http_add_worker(+Port, +Options) is det
- Add a new worker to the HTTP server for port Port. Options
overrule the default queue options. The following additional
options are processed:
- max_idle_time(+Seconds)
- The created worker will automatically terminate if there is
no new work within Seconds.
- http_current_worker(?Port, ?ThreadID) is nondet
- True if ThreadID is the identifier of a Prolog thread serving
Port. This predicate is motivated to allow for the use of
arbitrary interaction with the worker thread for development and
statistics.
- http_stop_server(+Port, +Options)
- Stop the indicated HTTP server gracefully. First stops all
workers, then stops the server.
- To be done
- - Realise non-graceful stop
- http_enough_workers(+Queue, +Why, +Peer) is det
- Check that we have enough workers in our queue. If not, call the
hook http:schedule_workers/1 to extend the worker pool. This
predicate can be used by accept_hook/2.
- http:schedule_workers(+Data:dict) is semidet[multifile]
- Hook called if a new connection or a keep-alive connection
cannot be scheduled immediately to a worker. Dict contains the
following keys:
- port:Port
- Port number that identifies the server.
- reason:Reason
- One of
accept
for a new connection or keep_alive
if a
worker tries to reschedule itself.
- peer:Peer
- Identify the other end of the connection
- waiting:Size
- Number of messages waiting in the queue.
- queue:Queue
- Message queue used to dispatch accepted messages.
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.
- See also
- - http_add_worker/2 may be used to create (temporary) extra
workers.
- thread_httpd:message_level(+Exception, -Level)[multifile]
- Determine the message stream used for exceptions that may occur
during server_loop/5. Being multifile, clauses can be added by the
application to refine error handling. See also message_hook/3 for
further programming error handling.
- http_requeue(+Header)
- Re-queue a connection to the worker pool. This deals with
processing additional requests on keep-alive connections.
- http_close_connection(+Request)
- Close connection associated to Request. See also http_requeue/1.
- http_spawn(:Goal, +Options) is det
- Continue this connection on a new thread. A handler may call
http_spawn/2 to start a new thread that continues processing the
current request using Goal. The original thread returns to the
worker pool for processing new requests. Options are passed to
thread_create/3, except for:
- pool(+Pool)
- Interfaces to library(thread_pool), starting the thread
on the given pool.
If 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.