
http_wrapper.pl -- Server processing of an HTTP request
This library provides the core of the implementation of the HTTP
protocol at the server side and is mainly intended for internal use.
It is used by library(thread_httpd) and library(inet_httpd)
(deprecated).
Still, it provides a few predicates that are occasinally useful for applications:
X-Forwarded-For)
http_wrapper(:Goal, +In, +Out, -Close, +Options) is det
The goal is assumed to write the reply to current_output
preceeded by an HTTP header, closed by a blank line. The header
must contain a Content-type: <type> line. It may optionally
contain a line Transfer-encoding: chunked to request chunked
encoding.
Options:
http_wrap_spawned(:Goal, -Request, -Close) is det
http_spawned(+ThreadId)
cgi_close(+CGI, +Request, +State0, +Error, -Close) is det[private]not_modified, moved) or a request to reply with
the content of a file.
send_error(+Out, +Request, +State0, +Error, -Close)[private]current_output no
longer points to the CGI stream, but simply to the socket that
connects us to the client.
http_done(+Code, +Status, +BytesSent, +State0) is det[private]
handler_with_output_to(:Goal, +Id, +Request, +Output, -Status) is det[private]ok, the error from catch/3 or a term error(goal_failed(Goal),
_).
thread_cputime(-CPU) is det[private]
cgi_hook(+Event, +CGI) is det[private]
redirect(+Header, -Action, -RestHeader) is semidet[private]Location and optional Status headers for
formulating a HTTP redirect. Redirection is only established if
no Status is provided, or Status is 3XX.
http_send_header(+Header)
expand_request(+Request0, -Request)[private]
extend_request(+Options, +RequestIn, -Request)[private]
http_current_request(-Request) is semidet
http_peer(+Request, -PeerIP:atom) is semidetFastly-client-ipX-real-ipX-forwarded-for
http_relative_path(+AbsPath, -RelPath) is det
debug_request(+Code, +Status, +Id, +CPU0, Bytes)[private]