% This LaTeX document was generated using the LaTeX backend of PlDoc,
% The SWI-Prolog documentation system



\subsection{library(http/http_header): Handling HTTP headers}

\label{sec:httpheader}

The library \file{library(http/http_header)} provides primitives for parsing
and composing HTTP headers. Its functionality is normally hidden by the
other parts of the HTTP server and client libraries.\vspace{0.7cm}

\begin{description}
    \predicate[det]{http_read_request}{2}{+FdIn:stream, -Request}
Read an HTTP request-header from \arg{FdIn} and return the broken-down
request fields as +Name(+Value) pairs in a list. \arg{Request} is
unified to \verb$end_of_file$ if \arg{FdIn} is at the end of input.

    \predicate{http_read_reply_header}{2}{+FdIn, -Reply}
Read the HTTP reply header. Throws an exception if the current
input does not contain a valid reply header.

    \predicate[det]{http_reply}{2}{+Data, +Out:stream}
\nodescription
    \predicate[det]{http_reply}{3}{+Data, +Out:stream, +HdrExtra}
\nodescription
    \predicate[det]{http_reply}{4}{+Data, +Out:stream, +HdrExtra, -Code}
\nodescription
    \predicate[det]{http_reply}{5}{+Data, +Out:stream, +HdrExtra, +Context, -Code}
\nodescription
    \predicate[det]{http_reply}{6}{+Data, +Out:stream, +HdrExtra, +Context, +Request, -Code}
Compose a complete HTTP reply from the term \arg{Data} using
additional headers from \arg{HdrExtra} to the output stream \arg{Out}.
ExtraHeader is a list of Field(Value). \arg{Data} is one of:

\begin{description}
    \termitem{html}{HTML}
\arg{HTML} tokens as produced by \dcgref{html}{1} from \file{html_write.pl}
    \termitem{file}{+MimeType, +FileName}
Reply content of \arg{FileName} using \arg{MimeType}
    \termitem{file}{+MimeType, +FileName, +Range}
Reply partial content of \arg{FileName} with given \arg{MimeType}
    \termitem{tmp_file}{+MimeType, +FileName}
Same as \const{file}, but do not include modification time
    \termitem{bytes}{+MimeType, +Bytes}
Send a sequence of \arg{Bytes} with the indicated \arg{MimeType}.
\arg{Bytes} is either a string of character codes 0..255 or
list of integers in the range 0..255. \arg{Out}-of-bound codes
result in a representation error exception.
    \termitem{stream}{+In, +Len}
Reply content of stream.
    \termitem{cgi_stream}{+In, +Len}
Reply content of stream, which should start with an
HTTP header, followed by a blank line. This is the
typical output from a CGI script.
    \termitem{\arg{Status}}{}
HTTP status report as defined by \predref{http_status_reply}{4}.
\end{description}

\begin{arguments}
\arg{HdrExtra} & provides additional reply-header fields, encoded
as Name(Value). It can also contain a field
\verb$content_length(-Len)$ to \textit{retrieve} the
value of the Content-length header that is replied. \\
\arg{Code} & is the numeric HTTP status code sent \\
\end{arguments}

\begin{tags}
    \tag{To be done}
Complete documentation
\end{tags}

    \predicate[det]{http_status_reply}{4}{+Status, +Out, +HdrExtra, -Code}
\nodescription
    \predicate[det]{http_status_reply}{5}{+Status, +Out, +HdrExtra, +Context, -Code}
\nodescription
    \predicate[det]{http_status_reply}{6}{+Status, +Out, +HdrExtra, +Context, +Request, -Code}
Emit HTML non-200 status reports. Such requests are always sent
as UTF-8 documents.

\arg{Status} can be one of the following:

\begin{description}
    \termitem{authorise}{Method}
Challenge authorization. \arg{Method} is one of

\begin{shortlist}
    \item \verb$basic(Realm)$
    \item \verb$digest(Digest)$
\end{shortlist}

    \termitem{authorise}{basic, Realm}
Same as \verb$authorise(basic(Realm))$. Deprecated.
    \termitem{bad_request}{ErrorTerm}
    \termitem{busy}{}
    \termitem{created}{Location}
    \termitem{forbidden}{Url}
    \termitem{moved}{To}
    \termitem{moved_temporary}{To}
    \termitem{no_content}{}
    \termitem{not_acceptable}{WhyHtml}
    \termitem{not_found}{Path}
    \termitem{method_not_allowed}{Method, Path}
    \termitem{not_modified}{}
    \termitem{resource_error}{ErrorTerm}
    \termitem{see_other}{To}
    \termitem{switching_protocols}{Goal, Options}
    \termitem{server_error}{ErrorTerm}
    \termitem{unavailable}{WhyHtml}
\end{description}

\qpredicate[semidet,multifile]{http}{serialize_reply}{2}{+Reply, -Body}Multifile hook to serialize the result of \qpredref{http}{status_reply}{3}
into a term

\begin{description}
    \termitem{body}{Type, Encoding, Content}
In this term, \arg{Type} is the media type, \arg{Encoding} is the
required wire encoding and \arg{Content} a string representing the
content.
\end{description}

    \predicate{http_join_headers}{3}{+Default, +Header, -Out}
Append headers from \arg{Default} to \arg{Header} if they are not
already part of it.

    \predicate{http_update_encoding}{3}{+HeaderIn, -Encoding, -HeaderOut}
Allow for rewrite of the header, adjusting the encoding. We
distinguish three options. If the user announces `text', we
always use UTF-8 encoding. If the user announces charset=utf-8
we use UTF-8 and otherwise we use octet (raw) encoding.
Alternatively we could dynamically choose for ASCII, ISO-Latin-1
or UTF-8.

\qpredicate[semidet,multifile]{http}{mime_type_encoding}{2}{+MimeType, -Encoding}\arg{Encoding} is the (default) character encoding for \arg{MimeType}. This is
used for setting the encoding for HTTP replies after the user calls
\verb$format('Content-type: <MIME type>~n')$. This hook is called before
\predref{mime_type_encoding}{2}. This default defines \const{utf8} for JSON and
Turtle derived \verb$application/$ MIME types.

    \predicate{http_update_connection}{4}{+CGIHeader, +Request, -Connection, -Header}
Merge keep-alive information from \arg{Request} and \arg{CGIHeader} into
\arg{Header}.

    \predicate{http_update_transfer}{4}{+Request, +CGIHeader, -Transfer, -Header}
Decide on the transfer encoding from the \arg{Request} and the CGI
header. The behaviour depends on the setting
http:chunked_transfer. If \const{never}, even explitic requests are
ignored. If \verb$on_request$, chunked encoding is used if requested
through the CGI header and allowed by the client. If
\verb$if_possible$, chunked encoding is used whenever the client
allows for it, which is interpreted as the client supporting
HTTP 1.1 or higher.

Chunked encoding is more space efficient and allows the client
to start processing partial results. The drawback is that errors
lead to incomplete pages instead of a nicely formatted complete
page.

    \predicate[det]{http_post_data}{3}{+Data, +Out:stream, +HdrExtra}
Send data on behalf on an HTTP POST request. This predicate is
normally called by \predref{http_post}{4} from \file{http_client.pl} to send the
POST data to the server. \arg{Data} is one of:

\begin{itemize}
    \item \verb$html(+Tokens)$
Result of \dcgref{html}{1} from \file{html_write.pl}
    \item \verb$json(+Term)$
Posting a JSON query and processing the JSON reply (or any other
reply understood by \predref{http_read_data}{3}) is simple as
\verb$http_post(URL, json(Term), Reply, [])$, where Term is a JSON
term as described in \file{json.pl} and reply is of the same format if
the server replies with JSON, when using module \verb$:- use_module(library(http/http_json))$. Note that the module is
used in both http server and http client, see
\file{library(http/http_json)}.
    \item \verb$xml(+Term)$
Post the result of \predref{xml_write}{3} using the Mime-type
\verb$text/xml$
    \item \verb$xml(+Type, +Term)$
Post the result of \predref{xml_write}{3} using the given Mime-type
and an empty option list to \predref{xml_write}{3}.
    \item \verb$xml(+Type, +Term, +Options)$
Post the result of \predref{xml_write}{3} using the given Mime-type
and option list for \predref{xml_write}{3}.
    \item \verb$file(+File)$
Send contents of a file. Mime-type is determined by
\predref{file_mime_type}{2}.
    \item \verb$file(+Type, +File)$
Send file with content of indicated mime-type.
    \item \verb$memory_file(+Type, +Handle)$
Similar to \verb$file(+Type, +File)$, but using a memory file
instead of a real file. See \predref{new_memory_file}{1}.
    \item \verb$codes(+Codes)$
As \verb$codes(text/plain, Codes)$.
    \item \verb$codes(+Type, +Codes)$
Send Codes using the indicated MIME-type.
    \item \verb$bytes(+Type, +Bytes)$
Send Bytes using the indicated MIME-type. Bytes is either a
string of character codes 0..255 or list of integers in the
range 0..255. \arg{Out}-of-bound codes result in a representation
error exception.
    \item \verb$atom(+Atom)$
As \verb$atom(text/plain, Atom)$.
    \item \verb$atom(+Type, +Atom)$
Send Atom using the indicated MIME-type.
    \item \verb$cgi_stream(+Stream, +Len)$ Read the input from Stream which,
like CGI data starts with a partial HTTP header. The fields of
this header are merged with the provided \arg{HdrExtra} fields. The
first Len characters of Stream are used.
    \item \verb$form(+ListOfParameter)$
Send data of the MIME type application/x-www-form-urlencoded as
produced by browsers issuing a POST request from an HTML form.
ListOfParameter is a list of Name=Value or Name(Value).
    \item \verb$form_data(+ListOfData)$
Send data of the MIME type \verb$multipart/form-data$ as produced
by browsers issuing a POST request from an HTML form using
enctype \verb$multipart/form-data$. ListOfData is the same as for
the List alternative described below. Below is an example.
Repository, etc. are atoms providing the value, while the last
argument provides a value from a file.

\begin{code}
...,
http_post([ protocol(http),
            host(Host),
            port(Port),
            path(ActionPath)
          ],
          form_data([ repository = Repository,
                      dataFormat = DataFormat,
                      baseURI    = BaseURI,
                      verifyData = Verify,
                      data       = file(File)
                    ]),
          _Reply,
          []),
...,
\end{code}

    \item List
If the argument is a plain list, it is sent using the MIME type
multipart/mixed and packed using \predref{mime_pack}{3}. See \predref{mime_pack}{3}
for details on the argument format.
\end{itemize}

    \predicate[det]{http_reply_header}{3}{+Out:stream, +What, +HdrExtra}
Create a reply header using \dcgref{reply_header}{3} and send it to
Stream.

    \predicate[semidet]{http_parse_header_value}{3}{+Field, +Value, -Prolog}
Translate \arg{Value} in a meaningful \arg{Prolog} term. \arg{Field} denotes the
HTTP request field for which we do the translation. Supported
fields are:

\begin{description}
    \termitem{content_length}{}
Converted into an integer
    \termitem{status}{}
Converted into an integer
    \termitem{cookie}{}
Converted into a list with Name=\arg{Value} by \dcgref{cookies}{1}.
    \termitem{set_cookie}{}
Converted into a term \verb$set_cookie(Name, Value, Options)$.
Options is a list consisting of Name=\arg{Value} or a single
atom (e.g., \const{secure})
    \termitem{host}{}
Converted to HostName:Port if applicable.
    \termitem{range}{}
Converted into \verb$bytes(From, To)$, where From is an integer
and To is either an integer or the atom \const{end}.
    \termitem{accept}{}
Parsed to a list of media descriptions. Each media is a term
\verb$media(Type, TypeParams, Quality, AcceptExts)$. The list is
sorted according to preference.
    \termitem{content_disposition}{}
Parsed into \verb$disposition(Name, Attributes)$, where Attributes is
a list of Name=\arg{Value} pairs.
    \termitem{content_type}{}
Parsed into \verb$media(Type/SubType, Attributes)$, where Attributes
is a list of Name=\arg{Value} pairs.
\end{description}

As some fields are already parsed in the \arg{Request}, this predicate
is a no-op when called on an already parsed field.

\begin{arguments}
\arg{Value} & is either an atom, a list of codes or an already parsed
header value. \\
\end{arguments}

    \predicate[det]{http_timestamp}{2}{+Time:timestamp, -Text:atom}
Generate a description of a \arg{Time} in HTTP format (RFC1123)

    \predicate[det]{http_read_header}{2}{+Fd, -Header}
Read Name: Value lines from FD until an empty line is encountered.
Field-name are converted to Prolog conventions (all lower, _ instead
of -): Content-Type: text/html \Sdcg{} \verb$content_type(text/html)$

    \predicate[det]{http_parse_header}{2}{+Text:codes, -Header:list}
\arg{Header} is a list of Name(Value)-terms representing the structure
of the HTTP header in \arg{Text}.

\begin{tags}
    \tag{Errors}
\verb$domain_error(http_request_line, Line)$
\end{tags}

\qpredicate[det,multifile]{http}{\Sidiv}{1}{http_address}HTML-rule that emits the location of the HTTP server. This hook
is called from \dcgref{address}{0} to customise the server address. The
server address is emitted on non-200-ok replies.

\qpredicate[semidet,multifile]{http}{status_page}{3}{+Status, +Context, -HTMLTokens}Hook called by \predref{http_status_reply}{4} and \predref{http_status_reply}{5} that
allows for emitting custom error pages for the following HTTP
page types:

\begin{shortlist}
    \item 201 - \verb$created(Location)$
    \item 301 - \verb$moved(To)$
    \item 302 - \verb$moved_temporary(To)$
    \item 303 - \verb$see_other(To)$
    \item 400 - \verb$bad_request(ErrorTerm)$
    \item 401 - \verb$authorise(AuthMethod)$
    \item 403 - \verb$forbidden(URL)$
    \item 404 - \verb$not_found(URL)$
    \item 405 - \verb$method_not_allowed(Method,URL)$
    \item 406 - \verb$not_acceptable(Why)$
    \item 500 - \verb$server_error(ErrorTerm)$
    \item 503 - \verb$unavailable(Why)$
\end{shortlist}

The hook is tried twice, first using the status term, e.g.,
\verb$not_found(URL)$ and than with the code, e.g. \verb$404$. The second
call is deprecated and only exists for compatibility.

\begin{arguments}
\arg{Context} & is the 4th argument of \predref{http_status_reply}{5}, which
is invoked after raising an exception of the format
\verb$http_reply(Status, HeaderExtra, Context)$. The default
context is \verb$[]$ (the empty list). \\
\arg{HTMLTokens} & is a list of tokens as produced by \dcgref{html}{1}.
It is passed to \predref{print_html}{2}. \\
\end{arguments}
\end{description}