View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2002-2020, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(http_header,
   37          [ http_read_request/2,        % +Stream, -Request
   38            http_read_reply_header/2,   % +Stream, -Reply
   39            http_reply/2,               % +What, +Stream
   40            http_reply/3,               % +What, +Stream, +HdrExtra
   41            http_reply/4,               % +What, +Stream, +HdrExtra, -Code
   42            http_reply/5,               % +What, +Stream, +HdrExtra, +Context,
   43                                        % -Code
   44            http_reply/6,               % +What, +Stream, +HdrExtra, +Context,
   45                                        % +Request, -Code
   46            http_reply_header/3,        % +Stream, +What, +HdrExtra
   47            http_status_reply/4,        % +Status, +Out, +HdrExtra, -Code
   48            http_status_reply/5,        % +Status, +Out, +HdrExtra,
   49                                        % +Context, -Code
   50
   51            http_timestamp/2,           % +Time, -HTTP string
   52
   53            http_post_data/3,           % +Stream, +Data, +HdrExtra
   54
   55            http_read_header/2,         % +Fd, -Header
   56            http_parse_header/2,        % +Codes, -Header
   57            http_parse_header_value/3,  % +Header, +HeaderValue, -MediaTypes
   58            http_join_headers/3,        % +Default, +InHdr, -OutHdr
   59            http_update_encoding/3,     % +HeaderIn, -Encoding, -HeaderOut
   60            http_update_connection/4,   % +HeaderIn, +Request, -Connection, -HeaderOut
   61            http_update_transfer/4      % +HeaderIn, +Request, -Transfer, -HeaderOut
   62          ]).   63:- autoload(html_write,
   64	    [ print_html/2, print_html/1, page/4, html/3,
   65	      html_print_length/2
   66	    ]).   67:- autoload(http_exception,[map_exception_to_http_status/4]).   68:- autoload(mimepack,[mime_pack/3]).   69:- autoload(mimetype,[file_mime_type/2]).   70:- autoload(library(apply),[maplist/2]).   71:- autoload(library(base64),[base64/2]).   72:- autoload(library(debug),[debug/3,debugging/1]).   73:- autoload(library(error),[syntax_error/1,domain_error/2]).   74:- autoload(library(lists),[append/3,member/2,select/3,delete/3]).   75:- autoload(library(memfile),
   76	    [ new_memory_file/1, open_memory_file/3,
   77	      free_memory_file/1, open_memory_file/4,
   78	      size_memory_file/3
   79	    ]).   80:- autoload(library(option),[option/3,option/2]).   81:- autoload(library(pairs),[pairs_values/2]).   82:- autoload(library(readutil),
   83	    [read_line_to_codes/2,read_line_to_codes/3]).   84:- autoload(library(sgml_write),[xml_write/3]).   85:- autoload(library(socket),[gethostname/1]).   86:- autoload(library(uri),
   87	    [ uri_components/2, uri_data/3, uri_encoded/3, uri_query_components/2
   88	    ]).   89:- autoload(library(url),[parse_url_search/2]).   90:- autoload(library(dcg/basics),
   91	    [ integer/3, atom/3, whites/2, blanks_to_nl/2, string/3,
   92	      number/3, blanks/2, float/3, nonblanks/3, eos/2
   93	    ]).   94:- use_module(library(settings),[setting/4,setting/2]).   95
   96:- multifile
   97    http:status_page/3,             % +Status, +Context, -HTML
   98    http:status_reply/3,            % +Status, -Reply, +Options
   99    http:serialize_reply/2,         % +Reply, -Body
  100    http:post_data_hook/3,          % +Data, +Out, +HdrExtra
  101    http:mime_type_encoding/2.      % +MimeType, -Encoding
  102
  103% see http_update_transfer/4.
  104
  105:- setting(http:chunked_transfer, oneof([never,on_request,if_possible]),
  106           on_request, 'When to use Transfer-Encoding: Chunked').

Handling HTTP headers

The library 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. */

  116:- discontiguous
  117    term_expansion/2.  118
  119
  120                 /*******************************
  121                 *          READ REQUEST        *
  122                 *******************************/
 http_read_request(+FdIn:stream, -Request) is det
Read an HTTP request-header from FdIn and return the broken-down request fields as +Name(+Value) pairs in a list. Request is unified to end_of_file if FdIn is at the end of input.
  130http_read_request(In, Request) :-
  131    catch(read_line_to_codes(In, Codes), E, true),
  132    (   var(E)
  133    ->  (   Codes == end_of_file
  134        ->  debug(http(header), 'end-of-file', []),
  135            Request = end_of_file
  136        ;   debug(http(header), 'First line: ~s', [Codes]),
  137            Request =  [input(In)|Request1],
  138            phrase(request(In, Request1), Codes),
  139            (   Request1 = [unknown(Text)|_]
  140            ->  string_codes(S, Text),
  141                syntax_error(http_request(S))
  142            ;   true
  143            )
  144        )
  145    ;   (   debugging(http(request))
  146        ->  message_to_string(E, Msg),
  147            debug(http(request), "Exception reading 1st line: ~s", [Msg])
  148        ;   true
  149        ),
  150        Request = end_of_file
  151    ).
 http_read_reply_header(+FdIn, -Reply)
Read the HTTP reply header. Throws an exception if the current input does not contain a valid reply header.
  159http_read_reply_header(In, [input(In)|Reply]) :-
  160    read_line_to_codes(In, Codes),
  161    (   Codes == end_of_file
  162    ->  debug(http(header), 'end-of-file', []),
  163        throw(error(syntax(http_reply_header, end_of_file), _))
  164    ;   debug(http(header), 'First line: ~s~n', [Codes]),
  165        (   phrase(reply(In, Reply), Codes)
  166        ->  true
  167        ;   atom_codes(Header, Codes),
  168            syntax_error(http_reply_header(Header))
  169        )
  170    ).
  171
  172
  173                 /*******************************
  174                 *        FORMULATE REPLY       *
  175                 *******************************/
 http_reply(+Data, +Out:stream) is det
 http_reply(+Data, +Out:stream, +HdrExtra) is det
 http_reply(+Data, +Out:stream, +HdrExtra, -Code) is det
 http_reply(+Data, +Out:stream, +HdrExtra, +Context, -Code) is det
 http_reply(+Data, +Out:stream, +HdrExtra, +Context, +Request, -Code) is det
Compose a complete HTTP reply from the term Data using additional headers from HdrExtra to the output stream Out. ExtraHeader is a list of Field(Value). Data is one of:
html(HTML)
HTML tokens as produced by html//1 from html_write.pl
file(+MimeType, +FileName)
Reply content of FileName using MimeType
file(+MimeType, +FileName, +Range)
Reply partial content of FileName with given MimeType
tmp_file(+MimeType, +FileName)
Same as file, but do not include modification time
bytes(+MimeType, +Bytes)
Send a sequence of Bytes with the indicated MimeType. Bytes is either a string of character codes 0..255 or list of integers in the range 0..255. Out-of-bound codes result in a representation error exception.
stream(+In, +Len)
Reply content of stream.
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.
Status
HTTP status report as defined by http_status_reply/4.
Arguments:
HdrExtra- provides additional reply-header fields, encoded as Name(Value). It can also contain a field content_length(-Len) to retrieve the value of the Content-length header that is replied.
Code- is the numeric HTTP status code sent
To be done
- Complete documentation
  224http_reply(What, Out) :-
  225    http_reply(What, Out, [connection(close)], _).
  226
  227http_reply(Data, Out, HdrExtra) :-
  228    http_reply(Data, Out, HdrExtra, _Code).
  229
  230http_reply(Data, Out, HdrExtra, Code) :-
  231    http_reply(Data, Out, HdrExtra, [], Code).
  232
  233http_reply(Data, Out, HdrExtra, Context, Code) :-
  234    http_reply(Data, Out, HdrExtra, Context, [method(get)], Code).
  235
  236http_reply(Data, Out, HdrExtra, _Context, Request, Code) :-
  237    byte_count(Out, C0),
  238    memberchk(method(Method), Request),
  239    catch(http_reply_data(Data, Out, HdrExtra, Method, Code), E, true),
  240    !,
  241    (   var(E)
  242    ->  true
  243    ;   (   E = error(io_error(write,_), _)
  244        ;   E = error(socket_error(_,_), _)
  245        )
  246    ->  byte_count(Out, C1),
  247        Sent is C1 - C0,
  248        throw(error(http_write_short(Data, Sent), _))
  249    ;   E = error(timeout_error(write, _), _)
  250    ->  throw(E)
  251    ;   map_exception_to_http_status(E, Status, NewHdr, NewContext),
  252        http_status_reply(Status, Out, NewHdr, NewContext, Request, Code)
  253    ).
  254http_reply(Status, Out, HdrExtra, Context, Request, Code) :-
  255    http_status_reply(Status, Out, HdrExtra, Context, Request, Code).
  256
  257:- meta_predicate
  258    if_no_head(0, +).
 http_reply_data(+Data, +Out, +HdrExtra, +Method, -Code) is semidet
Fails if Data is not a defined reply-data format, but a status term. See http_reply/3 and http_status_reply/6.
Errors
- Various I/O errors.
  267http_reply_data(Data, Out, HdrExtra, Method, Code) :-
  268    http_reply_data_(Data, Out, HdrExtra, Method, Code),
  269    flush_output(Out).
  270
  271http_reply_data_(html(HTML), Out, HdrExtra, Method, Code) :-
  272    !,
  273    phrase(reply_header(html(HTML), HdrExtra, Code), Header),
  274    format(Out, '~s', [Header]),
  275    if_no_head(print_html(Out, HTML), Method).
  276http_reply_data_(file(Type, File), Out, HdrExtra, Method, Code) :-
  277    !,
  278    phrase(reply_header(file(Type, File), HdrExtra, Code), Header),
  279    reply_file(Out, File, Header, Method).
  280http_reply_data_(gzip_file(Type, File), Out, HdrExtra, Method, Code) :-
  281    !,
  282    phrase(reply_header(gzip_file(Type, File), HdrExtra, Code), Header),
  283    reply_file(Out, File, Header, Method).
  284http_reply_data_(file(Type, File, Range), Out, HdrExtra, Method, Code) :-
  285    !,
  286    phrase(reply_header(file(Type, File, Range), HdrExtra, Code), Header),
  287    reply_file_range(Out, File, Header, Range, Method).
  288http_reply_data_(tmp_file(Type, File), Out, HdrExtra, Method, Code) :-
  289    !,
  290    phrase(reply_header(tmp_file(Type, File), HdrExtra, Code), Header),
  291    reply_file(Out, File, Header, Method).
  292http_reply_data_(bytes(Type, Bytes), Out, HdrExtra, Method, Code) :-
  293    !,
  294    phrase(reply_header(bytes(Type, Bytes), HdrExtra, Code), Header),
  295    format(Out, '~s', [Header]),
  296    if_no_head(format(Out, '~s', [Bytes]), Method).
  297http_reply_data_(stream(In, Len), Out, HdrExtra, Method, Code) :-
  298    !,
  299    phrase(reply_header(cgi_data(Len), HdrExtra, Code), Header),
  300    copy_stream(Out, In, Header, Method, 0, end).
  301http_reply_data_(cgi_stream(In, Len), Out, HdrExtra, Method, Code) :-
  302    !,
  303    http_read_header(In, CgiHeader),
  304    seek(In, 0, current, Pos),
  305    Size is Len - Pos,
  306    http_join_headers(HdrExtra, CgiHeader, Hdr2),
  307    phrase(reply_header(cgi_data(Size), Hdr2, Code), Header),
  308    copy_stream(Out, In, Header, Method, 0, end).
  309
  310if_no_head(_, head) :-
  311    !.
  312if_no_head(Goal, _) :-
  313    call(Goal).
  314
  315reply_file(Out, _File, Header, head) :-
  316    !,
  317    format(Out, '~s', [Header]).
  318reply_file(Out, File, Header, _) :-
  319    setup_call_cleanup(
  320        open(File, read, In, [type(binary)]),
  321        copy_stream(Out, In, Header, 0, end),
  322        close(In)).
  323
  324reply_file_range(Out, _File, Header, _Range, head) :-
  325    !,
  326    format(Out, '~s', [Header]).
  327reply_file_range(Out, File, Header, bytes(From, To), _) :-
  328    setup_call_cleanup(
  329        open(File, read, In, [type(binary)]),
  330        copy_stream(Out, In, Header, From, To),
  331        close(In)).
  332
  333copy_stream(Out, _, Header, head, _, _) :-
  334    !,
  335    format(Out, '~s', [Header]).
  336copy_stream(Out, In, Header, _, From, To) :-
  337    copy_stream(Out, In, Header, From, To).
  338
  339copy_stream(Out, In, Header, From, To) :-
  340    (   From == 0
  341    ->  true
  342    ;   seek(In, From, bof, _)
  343    ),
  344    peek_byte(In, _),
  345    format(Out, '~s', [Header]),
  346    (   To == end
  347    ->  copy_stream_data(In, Out)
  348    ;   Len is To - From,
  349        copy_stream_data(In, Out, Len)
  350    ).
 http_status_reply(+Status, +Out, +HdrExtra, -Code) is det
 http_status_reply(+Status, +Out, +HdrExtra, +Context, -Code) is det
 http_status_reply(+Status, +Out, +HdrExtra, +Context, +Request, -Code) is det
Emit HTML non-200 status reports. Such requests are always sent as UTF-8 documents.

Status can be one of the following:

authorise(Method)
Challenge authorization. Method is one of
  • basic(Realm)
  • digest(Digest)
authorise(basic, Realm)
Same as authorise(basic(Realm)). Deprecated.
bad_request(ErrorTerm)
busy
created(Location)
forbidden(Url)
moved(To)
moved_temporary(To)
no_content
not_acceptable(WhyHtml)
not_found(Path)
method_not_allowed(Method, Path)
not_modified
resource_error(ErrorTerm)
see_other(To)
switching_protocols(Goal, Options)
server_error(ErrorTerm)
unavailable(WhyHtml)
  384http_status_reply(Status, Out, Options) :-
  385    _{header:HdrExtra, context:Context, code:Code, method:Method} :< Options,
  386    http_status_reply(Status, Out, HdrExtra, Context, [method(Method)], Code).
  387
  388http_status_reply(Status, Out, HdrExtra, Code) :-
  389    http_status_reply(Status, Out, HdrExtra, [], Code).
  390
  391http_status_reply(Status, Out, HdrExtra, Context, Code) :-
  392    http_status_reply(Status, Out, HdrExtra, Context, [method(get)], Code).
  393
  394http_status_reply(Status, Out, HdrExtra, Context, Request, Code) :-
  395    option(method(Method), Request, get),
  396    parsed_accept(Request, Accept),
  397    status_reply_flush(Status, Out,
  398                       _{ context: Context,
  399                          method:  Method,
  400                          code:    Code,
  401                          accept:  Accept,
  402                          header:  HdrExtra
  403                        }).
  404
  405parsed_accept(Request, Accept) :-
  406    memberchk(accept(Accept0), Request),
  407    http_parse_header_value(accept, Accept0, Accept1),
  408    !,
  409    Accept = Accept1.
  410parsed_accept(_, [ media(text/html, [], 0.1,  []),
  411                   media(_,         [], 0.01, [])
  412                 ]).
  413
  414status_reply_flush(Status, Out, Options) :-
  415    status_reply(Status, Out, Options),
  416    !,
  417    flush_output(Out).
 status_reply(+Status, +Out, +Options:Dict)
Formulate a non-200 reply and send it to the stream Out. Options is a dict containing:
  430% Replies without content
  431status_reply(no_content, Out, Options) :-
  432    !,
  433    phrase(reply_header(status(no_content), Options), Header),
  434    format(Out, '~s', [Header]).
  435status_reply(switching_protocols(_Goal,SwitchOptions), Out, Options) :-
  436    !,
  437    (   option(headers(Extra1), SwitchOptions)
  438    ->  true
  439    ;   option(header(Extra1), SwitchOptions, [])
  440    ),
  441    http_join_headers(Options.header, Extra1, HdrExtra),
  442    phrase(reply_header(status(switching_protocols),
  443                        Options.put(header,HdrExtra)), Header),
  444    format(Out, '~s', [Header]).
  445status_reply(authorise(basic, ''), Out, Options) :-
  446    !,
  447    status_reply(authorise(basic), Out, Options).
  448status_reply(authorise(basic, Realm), Out, Options) :-
  449    !,
  450    status_reply(authorise(basic(Realm)), Out, Options).
  451status_reply(not_modified, Out, Options) :-
  452    !,
  453    phrase(reply_header(status(not_modified), Options), Header),
  454    format(Out, '~s', [Header]).
  455% aliases (compatibility)
  456status_reply(busy, Out, Options) :-
  457    status_reply(service_unavailable(busy), Out, Options).
  458status_reply(unavailable(Why), Out, Options) :-
  459    status_reply(service_unavailable(Why), Out, Options).
  460status_reply(resource_error(Why), Out, Options) :-
  461    status_reply(service_unavailable(Why), Out, Options).
  462% replies with content
  463status_reply(Status, Out, Options) :-
  464    status_has_content(Status),
  465    status_page_hook(Status, Reply, Options),
  466    serialize_body(Reply, Body),
  467    Status =.. List,
  468    append(List, [Body], ExList),
  469    ExStatus =.. ExList,
  470    phrase(reply_header(ExStatus, Options), Header),
  471    format(Out, '~s', [Header]),
  472    reply_status_body(Out, Body, Options).
 status_has_content(+StatusTerm, -HTTPCode)
True when StatusTerm is a status that usually comes with an expanatory content message.
  479status_has_content(created(_Location)).
  480status_has_content(moved(_To)).
  481status_has_content(moved_temporary(_To)).
  482status_has_content(see_other(_To)).
  483status_has_content(bad_request(_ErrorTerm)).
  484status_has_content(authorise(_Method)).
  485status_has_content(forbidden(_URL)).
  486status_has_content(not_found(_URL)).
  487status_has_content(method_not_allowed(_Method, _URL)).
  488status_has_content(not_acceptable(_Why)).
  489status_has_content(server_error(_ErrorTerm)).
  490status_has_content(service_unavailable(_Why)).
 serialize_body(+Reply, -Body) is det
Serialize the reply as returned by status_page_hook/3 into a term:
body(Type, Encoding, Content)
In this term, Type is the media type, Encoding is the required wire encoding and Content a string representing the content.
  501serialize_body(Reply, Body) :-
  502    http:serialize_reply(Reply, Body),
  503    !.
  504serialize_body(html_tokens(Tokens), body(text/html, utf8, Content)) :-
  505    !,
  506    with_output_to(string(Content), print_html(Tokens)).
  507serialize_body(Reply, Reply) :-
  508    Reply = body(_,_,_),
  509    !.
  510serialize_body(Reply, _) :-
  511    domain_error(http_reply_body, Reply).
  512
  513reply_status_body(_, _, Options) :-
  514    Options.method == head,
  515    !.
  516reply_status_body(Out, body(_Type, Encoding, Content), _Options) :-
  517    (   Encoding == octet
  518    ->  format(Out, '~s', [Content])
  519    ;   setup_call_cleanup(
  520            set_stream(Out, encoding(Encoding)),
  521            format(Out, '~s', [Content]),
  522            set_stream(Out, encoding(octet)))
  523    ).
 http:serialize_reply(+Reply, -Body) is semidet
Multifile hook to serialize the result of status_reply/3 into a term
body(Type, Encoding, Content)
In this term, Type is the media type, Encoding is the required wire encoding and Content a string representing the content.
 status_page_hook(+Term, -Reply, +Options) is det
Calls the following two hooks to generate an HTML page from a status reply.
http:status_reply(+Term, -Reply, +Options)
Provide non-HTML description of the (non-200) reply. The term Reply is handed to serialize_body/2, calling the hook http:serialize_reply/2.
http:status_page(+Term, +Context, -HTML)
http:status_page(+Code, +Context, -HTML)
Arguments:
Term- is the status term, e.g., not_found(URL)
See also
- http:status_page/3
  550status_page_hook(Term, Reply, Options) :-
  551    Context = Options.context,
  552    functor(Term, Name, _),
  553    status_number_fact(Name, Code),
  554    (   Options.code = Code,
  555        http:status_reply(Term, Reply, Options)
  556    ;   http:status_page(Term, Context, HTML),
  557        Reply = html_tokens(HTML)
  558    ;   http:status_page(Code, Context, HTML), % deprecated
  559        Reply = html_tokens(HTML)
  560    ),
  561    !.
  562status_page_hook(created(Location), html_tokens(HTML), _Options) :-
  563    phrase(page([ title('201 Created')
  564                ],
  565                [ h1('Created'),
  566                  p(['The document was created ',
  567                     a(href(Location), ' Here')
  568                    ]),
  569                  \address
  570                ]),
  571           HTML).
  572status_page_hook(moved(To), html_tokens(HTML), _Options) :-
  573    phrase(page([ title('301 Moved Permanently')
  574                ],
  575                [ h1('Moved Permanently'),
  576                  p(['The document has moved ',
  577                     a(href(To), ' Here')
  578                    ]),
  579                  \address
  580                ]),
  581           HTML).
  582status_page_hook(moved_temporary(To), html_tokens(HTML), _Options) :-
  583    phrase(page([ title('302 Moved Temporary')
  584                ],
  585                [ h1('Moved Temporary'),
  586                  p(['The document is currently ',
  587                     a(href(To), ' Here')
  588                    ]),
  589                  \address
  590                ]),
  591           HTML).
  592status_page_hook(see_other(To), html_tokens(HTML), _Options) :-
  593    phrase(page([ title('303 See Other')
  594                 ],
  595                 [ h1('See Other'),
  596                   p(['See other document ',
  597                      a(href(To), ' Here')
  598                     ]),
  599                   \address
  600                 ]),
  601            HTML).
  602status_page_hook(bad_request(ErrorTerm), html_tokens(HTML), _Options) :-
  603    '$messages':translate_message(ErrorTerm, Lines, []),
  604    phrase(page([ title('400 Bad Request')
  605                ],
  606                [ h1('Bad Request'),
  607                  p(\html_message_lines(Lines)),
  608                  \address
  609                ]),
  610           HTML).
  611status_page_hook(authorise(_Method), html_tokens(HTML), _Options):-
  612    phrase(page([ title('401 Authorization Required')
  613                ],
  614                [ h1('Authorization Required'),
  615                  p(['This server could not verify that you ',
  616                     'are authorized to access the document ',
  617                     'requested.  Either you supplied the wrong ',
  618                     'credentials (e.g., bad password), or your ',
  619                     'browser doesn\'t understand how to supply ',
  620                     'the credentials required.'
  621                    ]),
  622                  \address
  623                ]),
  624           HTML).
  625status_page_hook(forbidden(URL), html_tokens(HTML), _Options) :-
  626    phrase(page([ title('403 Forbidden')
  627                ],
  628                [ h1('Forbidden'),
  629                  p(['You don\'t have permission to access ', URL,
  630                     ' on this server'
  631                    ]),
  632                  \address
  633                ]),
  634           HTML).
  635status_page_hook(not_found(URL), html_tokens(HTML), _Options) :-
  636    phrase(page([ title('404 Not Found')
  637                ],
  638                [ h1('Not Found'),
  639                  p(['The requested URL ', tt(URL),
  640                     ' was not found on this server'
  641                    ]),
  642                  \address
  643                ]),
  644           HTML).
  645status_page_hook(method_not_allowed(Method,URL), html_tokens(HTML), _Options) :-
  646    upcase_atom(Method, UMethod),
  647    phrase(page([ title('405 Method not allowed')
  648                ],
  649                [ h1('Method not allowed'),
  650                  p(['The requested URL ', tt(URL),
  651                     ' does not support method ', tt(UMethod), '.'
  652                    ]),
  653                  \address
  654                ]),
  655           HTML).
  656status_page_hook(not_acceptable(WhyHTML), html_tokens(HTML), _Options) :-
  657    phrase(page([ title('406 Not Acceptable')
  658                ],
  659                [ h1('Not Acceptable'),
  660                  WhyHTML,
  661                  \address
  662                ]),
  663           HTML).
  664status_page_hook(server_error(ErrorTerm), html_tokens(HTML), _Options) :-
  665    '$messages':translate_message(ErrorTerm, Lines, []),
  666    phrase(page([ title('500 Internal server error')
  667                ],
  668                [ h1('Internal server error'),
  669                  p(\html_message_lines(Lines)),
  670                  \address
  671                ]),
  672           HTML).
  673status_page_hook(service_unavailable(Why), html_tokens(HTML), _Options) :-
  674    phrase(page([ title('503 Service Unavailable')
  675                ],
  676                [ h1('Service Unavailable'),
  677                  \unavailable(Why),
  678                  \address
  679                ]),
  680           HTML).
  681
  682unavailable(busy) -->
  683    html(p(['The server is temporarily out of resources, ',
  684            'please try again later'])).
  685unavailable(error(Formal,Context)) -->
  686    { '$messages':translate_message(error(Formal,Context), Lines, []) },
  687    html_message_lines(Lines).
  688unavailable(HTML) -->
  689    html(HTML).
  690
  691html_message_lines([]) -->
  692    [].
  693html_message_lines([nl|T]) -->
  694    !,
  695    html([br([])]),
  696    html_message_lines(T).
  697html_message_lines([flush]) -->
  698    [].
  699html_message_lines([Fmt-Args|T]) -->
  700    !,
  701    { format(string(S), Fmt, Args)
  702    },
  703    html([S]),
  704    html_message_lines(T).
  705html_message_lines([Fmt|T]) -->
  706    !,
  707    { format(string(S), Fmt, [])
  708    },
  709    html([S]),
  710    html_message_lines(T).
 http_join_headers(+Default, +Header, -Out)
Append headers from Default to Header if they are not already part of it.
  717http_join_headers([], H, H).
  718http_join_headers([H|T], Hdr0, Hdr) :-
  719    functor(H, N, A),
  720    functor(H2, N, A),
  721    member(H2, Hdr0),
  722    !,
  723    http_join_headers(T, Hdr0, Hdr).
  724http_join_headers([H|T], Hdr0, [H|Hdr]) :-
  725    http_join_headers(T, Hdr0, Hdr).
 http_update_encoding(+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.
  737http_update_encoding(Header0, utf8, [content_type(Type)|Header]) :-
  738    select(content_type(Type0), Header0, Header),
  739    sub_atom(Type0, 0, _, _, 'text/'),
  740    !,
  741    (   sub_atom(Type0, S, _, _, ';')
  742    ->  sub_atom(Type0, 0, S, _, B)
  743    ;   B = Type0
  744    ),
  745    atom_concat(B, '; charset=UTF-8', Type).
  746http_update_encoding(Header, Encoding, Header) :-
  747    memberchk(content_type(Type), Header),
  748    (   (   sub_atom(Type, _, _, _, 'UTF-8')
  749        ;   sub_atom(Type, _, _, _, 'utf-8')
  750        )
  751    ->  Encoding = utf8
  752    ;   http:mime_type_encoding(Type, Encoding)
  753    ->  true
  754    ;   mime_type_encoding(Type, Encoding)
  755    ).
  756http_update_encoding(Header, octet, Header).
 mime_type_encoding(+MimeType, -Encoding) is semidet
Encoding is the (default) character encoding for MimeType. Hooked by http:mime_type_encoding/2.
  763mime_type_encoding('application/json',         utf8).
  764mime_type_encoding('application/jsonrequest',  utf8).
  765mime_type_encoding('application/x-prolog',     utf8).
  766mime_type_encoding('application/n-quads',      utf8).
  767mime_type_encoding('application/n-triples',    utf8).
  768mime_type_encoding('application/sparql-query', utf8).
  769mime_type_encoding('application/trig',         utf8).
 http:mime_type_encoding(+MimeType, -Encoding) is semidet
Encoding is the (default) character encoding for MimeType. This is used for setting the encoding for HTTP replies after the user calls format('Content-type: <MIME type>~n'). This hook is called before mime_type_encoding/2. This default defines utf8 for JSON and Turtle derived application/ MIME types.
 http_update_connection(+CGIHeader, +Request, -Connection, -Header)
Merge keep-alive information from Request and CGIHeader into Header.
  785http_update_connection(CgiHeader, Request, Connect,
  786                       [connection(Connect)|Rest]) :-
  787    select(connection(CgiConn), CgiHeader, Rest),
  788    !,
  789    connection(Request, ReqConnection),
  790    join_connection(ReqConnection, CgiConn, Connect).
  791http_update_connection(CgiHeader, Request, Connect,
  792                       [connection(Connect)|CgiHeader]) :-
  793    connection(Request, Connect).
  794
  795join_connection(Keep1, Keep2, Connection) :-
  796    (   downcase_atom(Keep1, 'keep-alive'),
  797        downcase_atom(Keep2, 'keep-alive')
  798    ->  Connection = 'Keep-Alive'
  799    ;   Connection = close
  800    ).
 connection(+Header, -Connection)
Extract the desired connection from a header.
  807connection(Header, Close) :-
  808    (   memberchk(connection(Connection), Header)
  809    ->  Close = Connection
  810    ;   memberchk(http_version(1-X), Header),
  811        X >= 1
  812    ->  Close = 'Keep-Alive'
  813    ;   Close = close
  814    ).
 http_update_transfer(+Request, +CGIHeader, -Transfer, -Header)
Decide on the transfer encoding from the Request and the CGI header. The behaviour depends on the setting http:chunked_transfer. If never, even explitic requests are ignored. If on_request, chunked encoding is used if requested through the CGI header and allowed by the client. If 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.

  833http_update_transfer(Request, CgiHeader, Transfer, Header) :-
  834    setting(http:chunked_transfer, When),
  835    http_update_transfer(When, Request, CgiHeader, Transfer, Header).
  836
  837http_update_transfer(never, _, CgiHeader, none, Header) :-
  838    !,
  839    delete(CgiHeader, transfer_encoding(_), Header).
  840http_update_transfer(_, _, CgiHeader, none, Header) :-
  841    memberchk(location(_), CgiHeader),
  842    !,
  843    delete(CgiHeader, transfer_encoding(_), Header).
  844http_update_transfer(_, Request, CgiHeader, Transfer, Header) :-
  845    select(transfer_encoding(CgiTransfer), CgiHeader, Rest),
  846    !,
  847    transfer(Request, ReqConnection),
  848    join_transfer(ReqConnection, CgiTransfer, Transfer),
  849    (   Transfer == none
  850    ->  Header = Rest
  851    ;   Header = [transfer_encoding(Transfer)|Rest]
  852    ).
  853http_update_transfer(if_possible, Request, CgiHeader, Transfer, Header) :-
  854    transfer(Request, Transfer),
  855    Transfer \== none,
  856    !,
  857    Header = [transfer_encoding(Transfer)|CgiHeader].
  858http_update_transfer(_, _, CgiHeader, none, CgiHeader).
  859
  860join_transfer(chunked, chunked, chunked) :- !.
  861join_transfer(_, _, none).
 transfer(+Header, -Connection)
Extract the desired connection from a header.
  868transfer(Header, Transfer) :-
  869    (   memberchk(transfer_encoding(Transfer0), Header)
  870    ->  Transfer = Transfer0
  871    ;   memberchk(http_version(1-X), Header),
  872        X >= 1
  873    ->  Transfer = chunked
  874    ;   Transfer = none
  875    ).
 content_length_in_encoding(+Encoding, +In, -Bytes)
Determine hom many bytes are required to represent the data from stream In using the given encoding. Fails if the data cannot be represented with the given encoding.
  884content_length_in_encoding(Enc, Stream, Bytes) :-
  885    stream_property(Stream, position(Here)),
  886    setup_call_cleanup(
  887        open_null_stream(Out),
  888        ( set_stream(Out, encoding(Enc)),
  889          catch(copy_stream_data(Stream, Out), _, fail),
  890          flush_output(Out),
  891          byte_count(Out, Bytes)
  892        ),
  893        ( close(Out, [force(true)]),
  894          set_stream_position(Stream, Here)
  895        )).
  896
  897
  898                 /*******************************
  899                 *          POST SUPPORT        *
  900                 *******************************/
 http_post_data(+Data, +Out:stream, +HdrExtra) is det
Send data on behalf on an HTTP POST request. This predicate is normally called by http_post/4 from http_client.pl to send the POST data to the server. Data is one of:
  993http_post_data(Data, Out, HdrExtra) :-
  994    http:post_data_hook(Data, Out, HdrExtra),
  995    !.
  996http_post_data(html(HTML), Out, HdrExtra) :-
  997    !,
  998    phrase(post_header(html(HTML), HdrExtra), Header),
  999    format(Out, '~s', [Header]),
 1000    print_html(Out, HTML).
 1001http_post_data(xml(XML), Out, HdrExtra) :-
 1002    !,
 1003    http_post_data(xml(text/xml, XML, []), Out, HdrExtra).
 1004http_post_data(xml(Type, XML), Out, HdrExtra) :-
 1005    !,
 1006    http_post_data(xml(Type, XML, []), Out, HdrExtra).
 1007http_post_data(xml(Type, XML, Options), Out, HdrExtra) :-
 1008    !,
 1009    setup_call_cleanup(
 1010        new_memory_file(MemFile),
 1011        (   setup_call_cleanup(
 1012                open_memory_file(MemFile, write, MemOut),
 1013                xml_write(MemOut, XML, Options),
 1014                close(MemOut)),
 1015            http_post_data(memory_file(Type, MemFile), Out, HdrExtra)
 1016        ),
 1017        free_memory_file(MemFile)).
 1018http_post_data(file(File), Out, HdrExtra) :-
 1019    !,
 1020    (   file_mime_type(File, Type)
 1021    ->  true
 1022    ;   Type = text/plain
 1023    ),
 1024    http_post_data(file(Type, File), Out, HdrExtra).
 1025http_post_data(file(Type, File), Out, HdrExtra) :-
 1026    !,
 1027    phrase(post_header(file(Type, File), HdrExtra), Header),
 1028    format(Out, '~s', [Header]),
 1029    setup_call_cleanup(
 1030        open(File, read, In, [type(binary)]),
 1031        copy_stream_data(In, Out),
 1032        close(In)).
 1033http_post_data(memory_file(Type, Handle), Out, HdrExtra) :-
 1034    !,
 1035    phrase(post_header(memory_file(Type, Handle), HdrExtra), Header),
 1036    format(Out, '~s', [Header]),
 1037    setup_call_cleanup(
 1038        open_memory_file(Handle, read, In, [encoding(octet)]),
 1039        copy_stream_data(In, Out),
 1040        close(In)).
 1041http_post_data(codes(Codes), Out, HdrExtra) :-
 1042    !,
 1043    http_post_data(codes(text/plain, Codes), Out, HdrExtra).
 1044http_post_data(codes(Type, Codes), Out, HdrExtra) :-
 1045    !,
 1046    phrase(post_header(codes(Type, Codes), HdrExtra), Header),
 1047    format(Out, '~s', [Header]),
 1048    setup_call_cleanup(
 1049        set_stream(Out, encoding(utf8)),
 1050        format(Out, '~s', [Codes]),
 1051        set_stream(Out, encoding(octet))).
 1052http_post_data(bytes(Type, Bytes), Out, HdrExtra) :-
 1053    !,
 1054    phrase(post_header(bytes(Type, Bytes), HdrExtra), Header),
 1055    format(Out, '~s~s', [Header, Bytes]).
 1056http_post_data(atom(Atom), Out, HdrExtra) :-
 1057    !,
 1058    http_post_data(atom(text/plain, Atom), Out, HdrExtra).
 1059http_post_data(atom(Type, Atom), Out, HdrExtra) :-
 1060    !,
 1061    phrase(post_header(atom(Type, Atom), HdrExtra), Header),
 1062    format(Out, '~s', [Header]),
 1063    setup_call_cleanup(
 1064        set_stream(Out, encoding(utf8)),
 1065        write(Out, Atom),
 1066        set_stream(Out, encoding(octet))).
 1067http_post_data(cgi_stream(In, _Len), Out, HdrExtra) :-
 1068    !,
 1069    debug(obsolete, 'Obsolete 2nd argument in cgi_stream(In,Len)', []),
 1070    http_post_data(cgi_stream(In), Out, HdrExtra).
 1071http_post_data(cgi_stream(In), Out, HdrExtra) :-
 1072    !,
 1073    http_read_header(In, Header0),
 1074    http_update_encoding(Header0, Encoding, Header),
 1075    content_length_in_encoding(Encoding, In, Size),
 1076    http_join_headers(HdrExtra, Header, Hdr2),
 1077    phrase(post_header(cgi_data(Size), Hdr2), HeaderText),
 1078    format(Out, '~s', [HeaderText]),
 1079    setup_call_cleanup(
 1080        set_stream(Out, encoding(Encoding)),
 1081        copy_stream_data(In, Out),
 1082        set_stream(Out, encoding(octet))).
 1083http_post_data(form(Fields), Out, HdrExtra) :-
 1084    !,
 1085    parse_url_search(Codes, Fields),
 1086    length(Codes, Size),
 1087    http_join_headers(HdrExtra,
 1088                      [ content_type('application/x-www-form-urlencoded')
 1089                      ], Header),
 1090    phrase(post_header(cgi_data(Size), Header), HeaderChars),
 1091    format(Out, '~s', [HeaderChars]),
 1092    format(Out, '~s', [Codes]).
 1093http_post_data(form_data(Data), Out, HdrExtra) :-
 1094    !,
 1095    setup_call_cleanup(
 1096        new_memory_file(MemFile),
 1097        ( setup_call_cleanup(
 1098              open_memory_file(MemFile, write, MimeOut),
 1099              mime_pack(Data, MimeOut, Boundary),
 1100              close(MimeOut)),
 1101          size_memory_file(MemFile, Size, octet),
 1102          format(string(ContentType),
 1103                 'multipart/form-data; boundary=~w', [Boundary]),
 1104          http_join_headers(HdrExtra,
 1105                            [ mime_version('1.0'),
 1106                              content_type(ContentType)
 1107                            ], Header),
 1108          phrase(post_header(cgi_data(Size), Header), HeaderChars),
 1109          format(Out, '~s', [HeaderChars]),
 1110          setup_call_cleanup(
 1111              open_memory_file(MemFile, read, In, [encoding(octet)]),
 1112              copy_stream_data(In, Out),
 1113              close(In))
 1114        ),
 1115        free_memory_file(MemFile)).
 1116http_post_data(List, Out, HdrExtra) :-          % multipart-mixed
 1117    is_list(List),
 1118    !,
 1119    setup_call_cleanup(
 1120        new_memory_file(MemFile),
 1121        ( setup_call_cleanup(
 1122              open_memory_file(MemFile, write, MimeOut),
 1123              mime_pack(List, MimeOut, Boundary),
 1124              close(MimeOut)),
 1125          size_memory_file(MemFile, Size, octet),
 1126          format(string(ContentType),
 1127                 'multipart/mixed; boundary=~w', [Boundary]),
 1128          http_join_headers(HdrExtra,
 1129                            [ mime_version('1.0'),
 1130                              content_type(ContentType)
 1131                            ], Header),
 1132          phrase(post_header(cgi_data(Size), Header), HeaderChars),
 1133          format(Out, '~s', [HeaderChars]),
 1134          setup_call_cleanup(
 1135              open_memory_file(MemFile, read, In, [encoding(octet)]),
 1136              copy_stream_data(In, Out),
 1137              close(In))
 1138        ),
 1139        free_memory_file(MemFile)).
 post_header(+Data, +HeaderExtra)//
Generate the POST header, emitting HeaderExtra, followed by the HTTP Content-length and Content-type fields.
 1146post_header(html(Tokens), HdrExtra) -->
 1147    header_fields(HdrExtra, Len),
 1148    content_length(html(Tokens), Len),
 1149    content_type(text/html),
 1150    "\r\n".
 1151post_header(file(Type, File), HdrExtra) -->
 1152    header_fields(HdrExtra, Len),
 1153    content_length(file(File), Len),
 1154    content_type(Type),
 1155    "\r\n".
 1156post_header(memory_file(Type, File), HdrExtra) -->
 1157    header_fields(HdrExtra, Len),
 1158    content_length(memory_file(File), Len),
 1159    content_type(Type),
 1160    "\r\n".
 1161post_header(cgi_data(Size), HdrExtra) -->
 1162    header_fields(HdrExtra, Len),
 1163    content_length(Size, Len),
 1164    "\r\n".
 1165post_header(codes(Type, Codes), HdrExtra) -->
 1166    header_fields(HdrExtra, Len),
 1167    content_length(codes(Codes, utf8), Len),
 1168    content_type(Type, utf8),
 1169    "\r\n".
 1170post_header(bytes(Type, Bytes), HdrExtra) -->
 1171    header_fields(HdrExtra, Len),
 1172    content_length(bytes(Bytes), Len),
 1173    content_type(Type),
 1174    "\r\n".
 1175post_header(atom(Type, Atom), HdrExtra) -->
 1176    header_fields(HdrExtra, Len),
 1177    content_length(atom(Atom, utf8), Len),
 1178    content_type(Type, utf8),
 1179    "\r\n".
 1180
 1181
 1182                 /*******************************
 1183                 *       OUTPUT HEADER DCG      *
 1184                 *******************************/
 http_reply_header(+Out:stream, +What, +HdrExtra) is det
Create a reply header using reply_header//3 and send it to Stream.
 1191http_reply_header(Out, What, HdrExtra) :-
 1192    phrase(reply_header(What, HdrExtra, _Code), String),
 1193    !,
 1194    format(Out, '~s', [String]).
 reply_header(+Data, +HdrExtra, -Code)// is det
Grammar that realises the HTTP handler for sending Data. Data is a real data object as described with http_reply/2 or a not-200-ok HTTP status reply. The following status replies are defined.
See also
- http_status_reply/4 formulates the not-200-ok HTTP replies.
 1218reply_header(Data, Dict) -->
 1219    { _{header:HdrExtra, code:Code} :< Dict },
 1220    reply_header(Data, HdrExtra, Code).
 1221
 1222reply_header(string(String), HdrExtra, Code) -->
 1223    reply_header(string(text/plain, String), HdrExtra, Code).
 1224reply_header(string(Type, String), HdrExtra, Code) -->
 1225    vstatus(ok, Code, HdrExtra),
 1226    date(now),
 1227    header_fields(HdrExtra, CLen),
 1228    content_length(codes(String, utf8), CLen),
 1229    content_type(Type, utf8),
 1230    "\r\n".
 1231reply_header(bytes(Type, Bytes), HdrExtra, Code) -->
 1232    vstatus(ok, Code, HdrExtra),
 1233    date(now),
 1234    header_fields(HdrExtra, CLen),
 1235    content_length(bytes(Bytes), CLen),
 1236    content_type(Type),
 1237    "\r\n".
 1238reply_header(html(Tokens), HdrExtra, Code) -->
 1239    vstatus(ok, Code, HdrExtra),
 1240    date(now),
 1241    header_fields(HdrExtra, CLen),
 1242    content_length(html(Tokens), CLen),
 1243    content_type(text/html),
 1244    "\r\n".
 1245reply_header(file(Type, File), HdrExtra, Code) -->
 1246    vstatus(ok, Code, HdrExtra),
 1247    date(now),
 1248    modified(file(File)),
 1249    header_fields(HdrExtra, CLen),
 1250    content_length(file(File), CLen),
 1251    content_type(Type),
 1252    "\r\n".
 1253reply_header(gzip_file(Type, File), HdrExtra, Code) -->
 1254    vstatus(ok, Code, HdrExtra),
 1255    date(now),
 1256    modified(file(File)),
 1257    header_fields(HdrExtra, CLen),
 1258    content_length(file(File), CLen),
 1259    content_type(Type),
 1260    content_encoding(gzip),
 1261    "\r\n".
 1262reply_header(file(Type, File, Range), HdrExtra, Code) -->
 1263    vstatus(partial_content, Code, HdrExtra),
 1264    date(now),
 1265    modified(file(File)),
 1266    header_fields(HdrExtra, CLen),
 1267    content_length(file(File, Range), CLen),
 1268    content_type(Type),
 1269    "\r\n".
 1270reply_header(tmp_file(Type, File), HdrExtra, Code) -->
 1271    vstatus(ok, Code, HdrExtra),
 1272    date(now),
 1273    header_fields(HdrExtra, CLen),
 1274    content_length(file(File), CLen),
 1275    content_type(Type),
 1276    "\r\n".
 1277reply_header(cgi_data(Size), HdrExtra, Code) -->
 1278    vstatus(ok, Code, HdrExtra),
 1279    date(now),
 1280    header_fields(HdrExtra, CLen),
 1281    content_length(Size, CLen),
 1282    "\r\n".
 1283reply_header(chunked_data, HdrExtra, Code) -->
 1284    vstatus(ok, Code, HdrExtra),
 1285    date(now),
 1286    header_fields(HdrExtra, _),
 1287    (   {memberchk(transfer_encoding(_), HdrExtra)}
 1288    ->  ""
 1289    ;   transfer_encoding(chunked)
 1290    ),
 1291    "\r\n".
 1292% non-200 replies without a body (e.g., 1xx, 204, 304)
 1293reply_header(status(Status), HdrExtra, Code) -->
 1294    vstatus(Status, Code),
 1295    header_fields(HdrExtra, Clen),
 1296    { Clen = 0 },
 1297    "\r\n".
 1298% non-200 replies with a body
 1299reply_header(Data, HdrExtra, Code) -->
 1300    { status_reply_headers(Data,
 1301                           body(Type, Encoding, Content),
 1302                           ReplyHeaders),
 1303      http_join_headers(ReplyHeaders, HdrExtra, Headers),
 1304      functor(Data, CodeName, _)
 1305    },
 1306    vstatus(CodeName, Code, Headers),
 1307    date(now),
 1308    header_fields(Headers, CLen),
 1309    content_length(codes(Content, Encoding), CLen),
 1310    content_type(Type, Encoding),
 1311    "\r\n".
 1312
 1313status_reply_headers(created(Location, Body), Body,
 1314                     [ location(Location) ]).
 1315status_reply_headers(moved(To, Body), Body,
 1316                     [ location(To) ]).
 1317status_reply_headers(moved_temporary(To, Body), Body,
 1318                     [ location(To) ]).
 1319status_reply_headers(see_other(To, Body), Body,
 1320                     [ location(To) ]).
 1321status_reply_headers(authorise(Method, Body), Body,
 1322                     [ www_authenticate(Method) ]).
 1323status_reply_headers(not_found(_URL, Body), Body, []).
 1324status_reply_headers(forbidden(_URL, Body), Body, []).
 1325status_reply_headers(method_not_allowed(_Method, _URL, Body), Body, []).
 1326status_reply_headers(server_error(_Error, Body), Body, []).
 1327status_reply_headers(service_unavailable(_Why, Body), Body, []).
 1328status_reply_headers(not_acceptable(_Why, Body), Body, []).
 1329status_reply_headers(bad_request(_Error, Body), Body, []).
 vstatus(+Status, -Code)// is det
 vstatus(+Status, -Code, +HdrExtra)// is det
Emit the HTTP header for Status
 1337vstatus(_Status, Code, HdrExtra) -->
 1338    {memberchk(status(Code), HdrExtra)},
 1339    !,
 1340    vstatus(_NewStatus, Code).
 1341vstatus(Status, Code, _) -->
 1342    vstatus(Status, Code).
 1343
 1344vstatus(Status, Code) -->
 1345    "HTTP/1.1 ",
 1346    status_number(Status, Code),
 1347    " ",
 1348    status_comment(Status),
 1349    "\r\n".
 status_number(?Status, ?Code)// is semidet
Parse/generate the HTTP status numbers and map them to the proper name.
See also
- See the source code for supported status names and codes.
 1358status_number(Status, Code) -->
 1359    { var(Status) },
 1360    !,
 1361    integer(Code),
 1362    { status_number(Status, Code) },
 1363    !.
 1364status_number(Status, Code) -->
 1365    { status_number(Status, Code) },
 1366    integer(Code).
 status_number(+Status:atom, -Code:nonneg) is det
status_number(-Status:atom, +Code:nonneg) is det
Relates a symbolic HTTP status names to their integer Code. Each code also needs a rule for status_comment//1.
throws
- type_error If Code is instantiated with something other than an integer.
- domain_error If Code is instantiated with an integer outside of the range [100-599] of defined HTTP status codes.
 1380% Unrecognized status codes that are within a defined code class.
 1381% RFC 7231 states:
 1382%   "[...] a client MUST understand the class of any status code,
 1383%    as indicated by the first digit, and treat an unrecognized status code
 1384%    as being equivalent to the `x00` status code of that class [...]
 1385%   "
 1386% @see http://tools.ietf.org/html/rfc7231#section-6
 1387
 1388status_number(Status, Code) :-
 1389    nonvar(Status),
 1390    !,
 1391    status_number_fact(Status, Code).
 1392status_number(Status, Code) :-
 1393    nonvar(Code),
 1394    !,
 1395    (   between(100, 599, Code)
 1396    ->  (   status_number_fact(Status, Code)
 1397        ->  true
 1398        ;   ClassCode is Code // 100 * 100,
 1399            status_number_fact(Status, ClassCode)
 1400        )
 1401    ;   domain_error(http_code, Code)
 1402    ).
 1403
 1404status_number_fact(continue,                   100).
 1405status_number_fact(switching_protocols,        101).
 1406status_number_fact(ok,                         200).
 1407status_number_fact(created,                    201).
 1408status_number_fact(accepted,                   202).
 1409status_number_fact(non_authoritative_info,     203).
 1410status_number_fact(no_content,                 204).
 1411status_number_fact(reset_content,              205).
 1412status_number_fact(partial_content,            206).
 1413status_number_fact(multiple_choices,           300).
 1414status_number_fact(moved,                      301).
 1415status_number_fact(moved_temporary,            302).
 1416status_number_fact(see_other,                  303).
 1417status_number_fact(not_modified,               304).
 1418status_number_fact(use_proxy,                  305).
 1419status_number_fact(unused,                     306).
 1420status_number_fact(temporary_redirect,         307).
 1421status_number_fact(bad_request,                400).
 1422status_number_fact(authorise,                  401).
 1423status_number_fact(payment_required,           402).
 1424status_number_fact(forbidden,                  403).
 1425status_number_fact(not_found,                  404).
 1426status_number_fact(method_not_allowed,         405).
 1427status_number_fact(not_acceptable,             406).
 1428status_number_fact(request_timeout,            408).
 1429status_number_fact(conflict,                   409).
 1430status_number_fact(gone,                       410).
 1431status_number_fact(length_required,            411).
 1432status_number_fact(payload_too_large,          413).
 1433status_number_fact(uri_too_long,               414).
 1434status_number_fact(unsupported_media_type,     415).
 1435status_number_fact(expectation_failed,         417).
 1436status_number_fact(upgrade_required,           426).
 1437status_number_fact(server_error,               500).
 1438status_number_fact(not_implemented,            501).
 1439status_number_fact(bad_gateway,                502).
 1440status_number_fact(service_unavailable,        503).
 1441status_number_fact(gateway_timeout,            504).
 1442status_number_fact(http_version_not_supported, 505).
 status_comment(+Code:atom)// is det
Emit standard HTTP human-readable comment on the reply-status.
 1449status_comment(continue) -->
 1450    "Continue".
 1451status_comment(switching_protocols) -->
 1452    "Switching Protocols".
 1453status_comment(ok) -->
 1454    "OK".
 1455status_comment(created) -->
 1456    "Created".
 1457status_comment(accepted) -->
 1458    "Accepted".
 1459status_comment(non_authoritative_info) -->
 1460    "Non-Authoritative Information".
 1461status_comment(no_content) -->
 1462    "No Content".
 1463status_comment(reset_content) -->
 1464    "Reset Content".
 1465status_comment(created) -->
 1466    "Created".
 1467status_comment(partial_content) -->
 1468    "Partial content".
 1469status_comment(multiple_choices) -->
 1470    "Multiple Choices".
 1471status_comment(moved) -->
 1472    "Moved Permanently".
 1473status_comment(moved_temporary) -->
 1474    "Moved Temporary".
 1475status_comment(see_other) -->
 1476    "See Other".
 1477status_comment(not_modified) -->
 1478    "Not Modified".
 1479status_comment(use_proxy) -->
 1480    "Use Proxy".
 1481status_comment(unused) -->
 1482    "Unused".
 1483status_comment(temporary_redirect) -->
 1484    "Temporary Redirect".
 1485status_comment(bad_request) -->
 1486    "Bad Request".
 1487status_comment(authorise) -->
 1488    "Authorization Required".
 1489status_comment(payment_required) -->
 1490    "Payment Required".
 1491status_comment(forbidden) -->
 1492    "Forbidden".
 1493status_comment(not_found) -->
 1494    "Not Found".
 1495status_comment(method_not_allowed) -->
 1496    "Method Not Allowed".
 1497status_comment(not_acceptable) -->
 1498    "Not Acceptable".
 1499status_comment(request_timeout) -->
 1500    "Request Timeout".
 1501status_comment(conflict) -->
 1502    "Conflict".
 1503status_comment(gone) -->
 1504    "Gone".
 1505status_comment(length_required) -->
 1506    "Length Required".
 1507status_comment(payload_too_large) -->
 1508    "Payload Too Large".
 1509status_comment(uri_too_long) -->
 1510    "URI Too Long".
 1511status_comment(unsupported_media_type) -->
 1512    "Unsupported Media Type".
 1513status_comment(expectation_failed) -->
 1514    "Expectation Failed".
 1515status_comment(upgrade_required) -->
 1516    "Upgrade Required".
 1517status_comment(server_error) -->
 1518    "Internal Server Error".
 1519status_comment(not_implemented) -->
 1520    "Not Implemented".
 1521status_comment(bad_gateway) -->
 1522    "Bad Gateway".
 1523status_comment(service_unavailable) -->
 1524    "Service Unavailable".
 1525status_comment(gateway_timeout) -->
 1526    "Gateway Timeout".
 1527status_comment(http_version_not_supported) -->
 1528    "HTTP Version Not Supported".
 1529
 1530date(Time) -->
 1531    "Date: ",
 1532    (   { Time == now }
 1533    ->  now
 1534    ;   rfc_date(Time)
 1535    ),
 1536    "\r\n".
 1537
 1538modified(file(File)) -->
 1539    !,
 1540    { time_file(File, Time)
 1541    },
 1542    modified(Time).
 1543modified(Time) -->
 1544    "Last-modified: ",
 1545    (   { Time == now }
 1546    ->  now
 1547    ;   rfc_date(Time)
 1548    ),
 1549    "\r\n".
 content_length(+Object, ?Len)// is det
Emit the content-length field and (optionally) the content-range field.
Arguments:
Len- Number of bytes specified
 1559content_length(file(File, bytes(From, To)), Len) -->
 1560    !,
 1561    { size_file(File, Size),
 1562      (   To == end
 1563      ->  Len is Size - From,
 1564          RangeEnd is Size - 1
 1565      ;   Len is To+1 - From,       % To is index of last byte
 1566          RangeEnd = To
 1567      )
 1568    },
 1569    content_range(bytes, From, RangeEnd, Size),
 1570    content_length(Len, Len).
 1571content_length(Reply, Len) -->
 1572    { length_of(Reply, Len)
 1573    },
 1574    "Content-Length: ", integer(Len),
 1575    "\r\n".
 1576
 1577
 1578length_of(_, Len) :-
 1579    nonvar(Len),
 1580    !.
 1581length_of(codes(String, Encoding), Len) :-
 1582    !,
 1583    setup_call_cleanup(
 1584        open_null_stream(Out),
 1585        ( set_stream(Out, encoding(Encoding)),
 1586          format(Out, '~s', [String]),
 1587          byte_count(Out, Len)
 1588        ),
 1589        close(Out)).
 1590length_of(atom(Atom, Encoding), Len) :-
 1591    !,
 1592    setup_call_cleanup(
 1593        open_null_stream(Out),
 1594        ( set_stream(Out, encoding(Encoding)),
 1595          format(Out, '~a', [Atom]),
 1596          byte_count(Out, Len)
 1597        ),
 1598        close(Out)).
 1599length_of(file(File), Len) :-
 1600    !,
 1601    size_file(File, Len).
 1602length_of(memory_file(Handle), Len) :-
 1603    !,
 1604    size_memory_file(Handle, Len, octet).
 1605length_of(html_tokens(Tokens), Len) :-
 1606    !,
 1607    html_print_length(Tokens, Len).
 1608length_of(html(Tokens), Len) :-     % deprecated
 1609    !,
 1610    html_print_length(Tokens, Len).
 1611length_of(bytes(Bytes), Len) :-
 1612    !,
 1613    (   string(Bytes)
 1614    ->  string_length(Bytes, Len)
 1615    ;   length(Bytes, Len)          % assuming a list of 0..255
 1616    ).
 1617length_of(Len, Len).
 content_range(+Unit:atom, +From:int, +RangeEnd:int, +Size:int)// is det
Emit the Content-Range header for partial content (206) replies.
 1625content_range(Unit, From, RangeEnd, Size) -->
 1626    "Content-Range: ", atom(Unit), " ",
 1627    integer(From), "-", integer(RangeEnd), "/", integer(Size),
 1628    "\r\n".
 1629
 1630content_encoding(Encoding) -->
 1631    "Content-Encoding: ", atom(Encoding), "\r\n".
 1632
 1633transfer_encoding(Encoding) -->
 1634    "Transfer-Encoding: ", atom(Encoding), "\r\n".
 1635
 1636content_type(Type) -->
 1637    content_type(Type, _).
 1638
 1639content_type(Type, Charset) -->
 1640    ctype(Type),
 1641    charset(Charset),
 1642    "\r\n".
 1643
 1644ctype(Main/Sub) -->
 1645    !,
 1646    "Content-Type: ",
 1647    atom(Main),
 1648    "/",
 1649    atom(Sub).
 1650ctype(Type) -->
 1651    !,
 1652    "Content-Type: ",
 1653    atom(Type).
 1654
 1655charset(Var) -->
 1656    { var(Var) },
 1657    !.
 1658charset(utf8) -->
 1659    !,
 1660    "; charset=UTF-8".
 1661charset(CharSet) -->
 1662    "; charset=",
 1663    atom(CharSet).
 header_field(-Name, -Value)// is det
 header_field(+Name, +Value) is det
Process an HTTP request property. Request properties appear as a single line in an HTTP header.
 1671header_field(Name, Value) -->
 1672    { var(Name) },                 % parsing
 1673    !,
 1674    field_name(Name),
 1675    ":",
 1676    whites,
 1677    read_field_value(ValueChars),
 1678    blanks_to_nl,
 1679    !,
 1680    {   field_to_prolog(Name, ValueChars, Value)
 1681    ->  true
 1682    ;   atom_codes(Value, ValueChars),
 1683        domain_error(Name, Value)
 1684    }.
 1685header_field(Name, Value) -->
 1686    field_name(Name),
 1687    ": ",
 1688    field_value(Name, Value),
 1689    "\r\n".
 read_field_value(-Codes)//
Read a field eagerly upto the next whitespace
 1695read_field_value([H|T]) -->
 1696    [H],
 1697    { \+ code_type(H, space) },
 1698    !,
 1699    read_field_value(T).
 1700read_field_value([]) -->
 1701    "".
 1702read_field_value([H|T]) -->
 1703    [H],
 1704    read_field_value(T).
 http_parse_header_value(+Field, +Value, -Prolog) is semidet
Translate Value in a meaningful Prolog term. Field denotes the HTTP request field for which we do the translation. Supported fields are:
content_length
Converted into an integer
status
Converted into an integer
cookie
Converted into a list with Name=Value by cookies//1.
set_cookie
Converted into a term set_cookie(Name, Value, Options). Options is a list consisting of Name=Value or a single atom (e.g., secure)
host
Converted to HostName:Port if applicable.
range
Converted into bytes(From, To), where From is an integer and To is either an integer or the atom end.
accept
Parsed to a list of media descriptions. Each media is a term media(Type, TypeParams, Quality, AcceptExts). The list is sorted according to preference.
content_disposition
Parsed into disposition(Name, Attributes), where Attributes is a list of Name=Value pairs.
content_type
Parsed into media(Type/SubType, Attributes), where Attributes is a list of Name=Value pairs.

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

Arguments:
Value- is either an atom, a list of codes or an already parsed header value.
 1745http_parse_header_value(Field, Value, Prolog) :-
 1746    known_field(Field, _, Type),
 1747    (   already_parsed(Type, Value)
 1748    ->  Prolog = Value
 1749    ;   to_codes(Value, Codes),
 1750        parse_header_value(Field, Codes, Prolog)
 1751    ).
 1752
 1753already_parsed(integer, V)    :- !, integer(V).
 1754already_parsed(list(Type), L) :- !, is_list(L), maplist(already_parsed(Type), L).
 1755already_parsed(Term, V)       :- subsumes_term(Term, V).
 known_field(?FieldName, ?AutoConvert, -Type)
True if the value of FieldName is by default translated into a Prolog data structure.
 1763known_field(content_length,      true,  integer).
 1764known_field(status,              true,  integer).
 1765known_field(cookie,              true,  list(_=_)).
 1766known_field(set_cookie,          true,  list(set_cookie(_Name,_Value,_Options))).
 1767known_field(host,                true,  _Host:_Port).
 1768known_field(range,               maybe, bytes(_,_)).
 1769known_field(accept,              maybe, list(media(_Type, _Parms, _Q, _Exts))).
 1770known_field(content_disposition, maybe, disposition(_Name, _Attributes)).
 1771known_field(content_type,        false, media(_Type/_Sub, _Attributes)).
 1772
 1773to_codes(In, Codes) :-
 1774    (   is_list(In)
 1775    ->  Codes = In
 1776    ;   atom_codes(In, Codes)
 1777    ).
 field_to_prolog(+Field, +ValueCodes, -Prolog) is semidet
Translate the value string into a sensible Prolog term. For known_fields(_,true), this must succeed. For maybe, we just return the atom if the translation fails.
 1785field_to_prolog(Field, Codes, Prolog) :-
 1786    known_field(Field, true, _Type),
 1787    !,
 1788    (   parse_header_value(Field, Codes, Prolog0)
 1789    ->  Prolog = Prolog0
 1790    ).
 1791field_to_prolog(Field, Codes, Prolog) :-
 1792    known_field(Field, maybe, _Type),
 1793    parse_header_value(Field, Codes, Prolog0),
 1794    !,
 1795    Prolog = Prolog0.
 1796field_to_prolog(_, Codes, Atom) :-
 1797    atom_codes(Atom, Codes).
 parse_header_value(+Field, +ValueCodes, -Value) is semidet
Parse the value text of an HTTP field into a meaningful Prolog representation.
 1804parse_header_value(content_length, ValueChars, ContentLength) :-
 1805    number_codes(ContentLength, ValueChars).
 1806parse_header_value(status, ValueChars, Code) :-
 1807    (   phrase(" ", L, _),
 1808        append(Pre, L, ValueChars)
 1809    ->  number_codes(Code, Pre)
 1810    ;   number_codes(Code, ValueChars)
 1811    ).
 1812parse_header_value(cookie, ValueChars, Cookies) :-
 1813    debug(cookie, 'Cookie: ~s', [ValueChars]),
 1814    phrase(cookies(Cookies), ValueChars).
 1815parse_header_value(set_cookie, ValueChars, SetCookie) :-
 1816    debug(cookie, 'SetCookie: ~s', [ValueChars]),
 1817    phrase(set_cookie(SetCookie), ValueChars).
 1818parse_header_value(host, ValueChars, Host) :-
 1819    (   append(HostChars, [0':|PortChars], ValueChars),
 1820        catch(number_codes(Port, PortChars), _, fail)
 1821    ->  atom_codes(HostName, HostChars),
 1822        Host = HostName:Port
 1823    ;   atom_codes(Host, ValueChars)
 1824    ).
 1825parse_header_value(range, ValueChars, Range) :-
 1826    phrase(range(Range), ValueChars).
 1827parse_header_value(accept, ValueChars, Media) :-
 1828    parse_accept(ValueChars, Media).
 1829parse_header_value(content_disposition, ValueChars, Disposition) :-
 1830    phrase(content_disposition(Disposition), ValueChars).
 1831parse_header_value(content_type, ValueChars, Type) :-
 1832    phrase(parse_content_type(Type), ValueChars).
 field_value(+Name, +Value)//
 1836field_value(_, set_cookie(Name, Value, Options)) -->
 1837    !,
 1838    atom(Name), "=", atom(Value),
 1839    value_options(Options, cookie).
 1840field_value(_, disposition(Disposition, Options)) -->
 1841    !,
 1842    atom(Disposition), value_options(Options, disposition).
 1843field_value(www_authenticate, Auth) -->
 1844    auth_field_value(Auth).
 1845field_value(_, Atomic) -->
 1846    atom(Atomic).
 auth_field_value(+AuthValue)//
Emit the authentication requirements (WWW-Authenticate field).
 1852auth_field_value(negotiate(Data)) -->
 1853    "Negotiate ",
 1854    { base64(Data, DataBase64),
 1855      atom_codes(DataBase64, Codes)
 1856    },
 1857    string(Codes).
 1858auth_field_value(negotiate) -->
 1859    "Negotiate".
 1860auth_field_value(basic) -->
 1861    !,
 1862    "Basic".
 1863auth_field_value(basic(Realm)) -->
 1864    "Basic Realm=\"", atom(Realm), "\"".
 1865auth_field_value(digest) -->
 1866    !,
 1867    "Digest".
 1868auth_field_value(digest(Details)) -->
 1869    "Digest ", atom(Details).
 value_options(+List, +Field)//
Emit field parameters such as ; charset=UTF-8. There are three versions: a plain key (secure), token values and quoted string values. Seems we cannot deduce that from the actual value.
 1878value_options([], _) --> [].
 1879value_options([H|T], Field) -->
 1880    "; ", value_option(H, Field),
 1881    value_options(T, Field).
 1882
 1883value_option(secure=true, cookie) -->
 1884    !,
 1885    "secure".
 1886value_option(Name=Value, Type) -->
 1887    { string_option(Name, Type) },
 1888    !,
 1889    atom(Name), "=",
 1890    qstring(Value).
 1891value_option(Name=Value, Type) -->
 1892    { token_option(Name, Type) },
 1893    !,
 1894    atom(Name), "=", atom(Value).
 1895value_option(Name=Value, _Type) -->
 1896    atom(Name), "=",
 1897    option_value(Value).
 1898
 1899string_option(filename, disposition).
 1900
 1901token_option(path, cookie).
 1902
 1903option_value(Value) -->
 1904    { number(Value) },
 1905    !,
 1906    number(Value).
 1907option_value(Value) -->
 1908    { (   atom(Value)
 1909      ->  true
 1910      ;   string(Value)
 1911      ),
 1912      forall(string_code(_, Value, C),
 1913             token_char(C))
 1914    },
 1915    !,
 1916    atom(Value).
 1917option_value(Atomic) -->
 1918    qstring(Atomic).
 1919
 1920qstring(Atomic) -->
 1921    { string_codes(Atomic, Codes) },
 1922    "\"",
 1923    qstring_codes(Codes),
 1924    "\"".
 1925
 1926qstring_codes([]) --> [].
 1927qstring_codes([H|T]) --> qstring_code(H), qstring_codes(T).
 1928
 1929qstring_code(C) --> {qstring_esc(C)}, !, "\\", [C].
 1930qstring_code(C) --> [C].
 1931
 1932qstring_esc(0'").
 1933qstring_esc(C) :- ctl(C).
 1934
 1935
 1936                 /*******************************
 1937                 *        ACCEPT HEADERS        *
 1938                 *******************************/
 1939
 1940:- dynamic accept_cache/2. 1941:- volatile accept_cache/2. 1942
 1943parse_accept(Codes, Media) :-
 1944    atom_codes(Atom, Codes),
 1945    (   accept_cache(Atom, Media0)
 1946    ->  Media = Media0
 1947    ;   phrase(accept(Media0), Codes),
 1948        keysort(Media0, Media1),
 1949        pairs_values(Media1, Media2),
 1950        assertz(accept_cache(Atom, Media2)),
 1951        Media = Media2
 1952    ).
 accept(-Media)// is semidet
Parse an HTTP Accept: header
 1958accept([H|T]) -->
 1959    blanks,
 1960    media_range(H),
 1961    blanks,
 1962    (   ","
 1963    ->  accept(T)
 1964    ;   {T=[]}
 1965    ).
 1966
 1967media_range(s(SortQuality,Spec)-media(Type, TypeParams, Quality, AcceptExts)) -->
 1968    media_type(Type),
 1969    blanks,
 1970    (   ";"
 1971    ->  blanks,
 1972        parameters_and_quality(TypeParams, Quality, AcceptExts)
 1973    ;   { TypeParams = [],
 1974          Quality = 1.0,
 1975          AcceptExts = []
 1976        }
 1977    ),
 1978    { SortQuality is float(-Quality),
 1979      rank_specialised(Type, TypeParams, Spec)
 1980    }.
 content_disposition(-Disposition)//
Parse Content-Disposition value
 1987content_disposition(disposition(Disposition, Options)) -->
 1988    token(Disposition), blanks,
 1989    value_parameters(Options).
 parse_content_type(-Type)//
Parse Content-Type value into a term media(Type/SubType, Parameters).
 1996parse_content_type(media(Type, Parameters)) -->
 1997    media_type(Type), blanks,
 1998    value_parameters(Parameters).
 rank_specialised(+Type, +TypeParam, -Key) is det
Although the specification linked above is unclear, it seems that more specialised types must be preferred over less specialized ones.
To be done
- Is there an official specification of this?
 2009rank_specialised(Type/SubType, TypeParams, v(VT, VS, SortVP)) :-
 2010    var_or_given(Type, VT),
 2011    var_or_given(SubType, VS),
 2012    length(TypeParams, VP),
 2013    SortVP is -VP.
 2014
 2015var_or_given(V, Val) :-
 2016    (   var(V)
 2017    ->  Val = 0
 2018    ;   Val = -1
 2019    ).
 2020
 2021media_type(Type/SubType) -->
 2022    type(Type), "/", type(SubType).
 2023
 2024type(_) -->
 2025    "*",
 2026    !.
 2027type(Type) -->
 2028    token(Type).
 2029
 2030parameters_and_quality(Params, Quality, AcceptExts) -->
 2031    token(Name),
 2032    blanks, "=", blanks,
 2033    (   { Name == q }
 2034    ->  float(Quality), blanks,
 2035        value_parameters(AcceptExts),
 2036        { Params = [] }
 2037    ;   { Params = [Name=Value|T] },
 2038        parameter_value(Value),
 2039        blanks,
 2040        (   ";"
 2041        ->  blanks,
 2042            parameters_and_quality(T, Quality, AcceptExts)
 2043        ;   { T = [],
 2044              Quality = 1.0,
 2045              AcceptExts = []
 2046            }
 2047        )
 2048    ).
 value_parameters(-Params:list) is det
Accept (";" <parameter>)*, returning a list of Name=Value, where both Name and Value are atoms.
 2055value_parameters([H|T]) -->
 2056    ";",
 2057    !,
 2058    blanks, token(Name), blanks,
 2059    (   "="
 2060    ->  blanks,
 2061        (   token(Value)
 2062        ->  []
 2063        ;   quoted_string(Value)
 2064        ),
 2065        { H = (Name=Value) }
 2066    ;   { H = Name }
 2067    ),
 2068    blanks,
 2069    value_parameters(T).
 2070value_parameters([]) -->
 2071    [].
 2072
 2073parameter_value(Value) --> token(Value), !.
 2074parameter_value(Value) --> quoted_string(Value).
 token(-Name)// is semidet
Process an HTTP header token from the input.
 2081token(Name) -->
 2082    token_char(C1),
 2083    token_chars(Cs),
 2084    { atom_codes(Name, [C1|Cs]) }.
 2085
 2086token_chars([H|T]) -->
 2087    token_char(H),
 2088    !,
 2089    token_chars(T).
 2090token_chars([]) --> [].
 2091
 2092token_char(C) :-
 2093    \+ ctl(C),
 2094    \+ separator_code(C).
 2095
 2096ctl(C) :- between(0,31,C), !.
 2097ctl(127).
 2098
 2099separator_code(0'().
 2100separator_code(0')).
 2101separator_code(0'<).
 2102separator_code(0'>).
 2103separator_code(0'@).
 2104separator_code(0',).
 2105separator_code(0';).
 2106separator_code(0':).
 2107separator_code(0'\\).
 2108separator_code(0'").
 2109separator_code(0'/).
 2110separator_code(0'[).
 2111separator_code(0']).
 2112separator_code(0'?).
 2113separator_code(0'=).
 2114separator_code(0'{).
 2115separator_code(0'}).
 2116separator_code(0'\s).
 2117separator_code(0'\t).
 2118
 2119term_expansion(token_char(x) --> [x], Clauses) :-
 2120    findall((token_char(C)-->[C]),
 2121            (   between(0, 255, C),
 2122                token_char(C)
 2123            ),
 2124            Clauses).
 2125
 2126token_char(x) --> [x].
 quoted_string(-Text)// is semidet
True if input starts with a quoted string representing Text.
 2132quoted_string(Text) -->
 2133    "\"",
 2134    quoted_text(Codes),
 2135    { atom_codes(Text, Codes) }.
 2136
 2137quoted_text([]) -->
 2138    "\"",
 2139    !.
 2140quoted_text([H|T]) -->
 2141    "\\", !, [H],
 2142    quoted_text(T).
 2143quoted_text([H|T]) -->
 2144    [H],
 2145    !,
 2146    quoted_text(T).
 header_fields(+Fields, ?ContentLength)// is det
Process a sequence of [Name(Value), ...] attributes for the header. A term content_length(Len) is special. If instantiated it emits the header. If not it just unifies ContentLength with the argument of the content_length(Len) term. This allows for both sending and retrieving the content-length.
 2157header_fields([], _) --> [].
 2158header_fields([content_length(CLen)|T], CLen) -->
 2159    !,
 2160    (   { var(CLen) }
 2161    ->  ""
 2162    ;   header_field(content_length, CLen)
 2163    ),
 2164    header_fields(T, CLen).           % Continue or return first only?
 2165header_fields([status(_)|T], CLen) -->   % handled by vstatus//3.
 2166    !,
 2167    header_fields(T, CLen).
 2168header_fields([H|T], CLen) -->
 2169    { H =.. [Name, Value] },
 2170    header_field(Name, Value),
 2171    header_fields(T, CLen).
 field_name(?PrologName)
Convert between prolog_name and HttpName. Field names are, according to RFC 2616, considered tokens and covered by the following definition:
token          = 1*<any CHAR except CTLs or separators>
separators     = "(" | ")" | "<" | ">" | "@"
               | "," | ";" | ":" | "\" | <">
               | "/" | "[" | "]" | "?" | "="
               | "{" | "}" | SP | HT
 2188:- public
 2189    field_name//1. 2190
 2191field_name(Name) -->
 2192    { var(Name) },
 2193    !,
 2194    rd_field_chars(Chars),
 2195    { atom_codes(Name, Chars) }.
 2196field_name(mime_version) -->
 2197    !,
 2198    "MIME-Version".
 2199field_name(www_authenticate) -->
 2200    !,
 2201    "WWW-Authenticate".
 2202field_name(Name) -->
 2203    { atom_codes(Name, Chars) },
 2204    wr_field_chars(Chars).
 2205
 2206rd_field_chars_no_fold([C|T]) -->
 2207    [C],
 2208    { rd_field_char(C, _) },
 2209    !,
 2210    rd_field_chars_no_fold(T).
 2211rd_field_chars_no_fold([]) -->
 2212    [].
 2213
 2214rd_field_chars([C0|T]) -->
 2215    [C],
 2216    { rd_field_char(C, C0) },
 2217    !,
 2218    rd_field_chars(T).
 2219rd_field_chars([]) -->
 2220    [].
 separators(-CharCodes) is det
CharCodes is a list of separators according to RFC2616
 2226separators("()<>@,;:\\\"/[]?={} \t").
 2227
 2228term_expansion(rd_field_char('expand me',_), Clauses) :-
 2229
 2230    Clauses = [ rd_field_char(0'-, 0'_)
 2231              | Cls
 2232              ],
 2233    separators(SepString),
 2234    string_codes(SepString, Seps),
 2235    findall(rd_field_char(In, Out),
 2236            (   between(32, 127, In),
 2237                \+ memberchk(In, Seps),
 2238                In \== 0'-,         % 0'
 2239                code_type(Out, to_lower(In))),
 2240            Cls).
 2241
 2242rd_field_char('expand me', _).                  % avoid recursion
 2243
 2244wr_field_chars([C|T]) -->
 2245    !,
 2246    { code_type(C, to_lower(U)) },
 2247    [U],
 2248    wr_field_chars2(T).
 2249wr_field_chars([]) -->
 2250    [].
 2251
 2252wr_field_chars2([]) --> [].
 2253wr_field_chars2([C|T]) -->              % 0'
 2254    (   { C == 0'_ }
 2255    ->  "-",
 2256        wr_field_chars(T)
 2257    ;   [C],
 2258        wr_field_chars2(T)
 2259    ).
 now//
Current time using rfc_date//1.
 2265now -->
 2266    { get_time(Time)
 2267    },
 2268    rfc_date(Time).
 rfc_date(+Time)// is det
Write time according to RFC1123 specification as required by the RFC2616 HTTP protocol specs.
 2275rfc_date(Time, String, Tail) :-
 2276    stamp_date_time(Time, Date, 'UTC'),
 2277    format_time(codes(String, Tail),
 2278                '%a, %d %b %Y %T GMT',
 2279                Date, posix).
 http_timestamp(+Time:timestamp, -Text:atom) is det
Generate a description of a Time in HTTP format (RFC1123)
 2285http_timestamp(Time, Atom) :-
 2286    stamp_date_time(Time, Date, 'UTC'),
 2287    format_time(atom(Atom),
 2288                '%a, %d %b %Y %T GMT',
 2289                Date, posix).
 2290
 2291
 2292                 /*******************************
 2293                 *         REQUEST DCG          *
 2294                 *******************************/
 2295
 2296request(Fd, [method(Method),request_uri(ReqURI)|Header]) -->
 2297    method(Method),
 2298    blanks,
 2299    nonblanks(Query),
 2300    { atom_codes(ReqURI, Query),
 2301      request_uri_parts(ReqURI, Header, Rest)
 2302    },
 2303    request_header(Fd, Rest),
 2304    !.
 2305request(Fd, [unknown(What)|Header]) -->
 2306    string(What),
 2307    eos,
 2308    !,
 2309    {   http_read_header(Fd, Header)
 2310    ->  true
 2311    ;   Header = []
 2312    }.
 2313
 2314method(get)     --> "GET", !.
 2315method(put)     --> "PUT", !.
 2316method(head)    --> "HEAD", !.
 2317method(post)    --> "POST", !.
 2318method(delete)  --> "DELETE", !.
 2319method(patch)   --> "PATCH", !.
 2320method(options) --> "OPTIONS", !.
 2321method(trace)   --> "TRACE", !.
 request_uri_parts(+RequestURI, -Parts, ?Tail) is det
Process the request-uri, producing the following parts:
path(-Path)
Decode path information (always present)
search(-QueryParams)
Present if there is a ?name=value&... part of the request uri. QueryParams is a Name=Value list.
fragment(-Fragment)
Present if there is a #Fragment.
 2335request_uri_parts(ReqURI, [path(Path)|Parts], Rest) :-
 2336    uri_components(ReqURI, Components),
 2337    uri_data(path, Components, PathText),
 2338    uri_encoded(path, Path, PathText),
 2339    phrase(uri_parts(Components), Parts, Rest).
 2340
 2341uri_parts(Components) -->
 2342    uri_search(Components),
 2343    uri_fragment(Components).
 2344
 2345uri_search(Components) -->
 2346    { uri_data(search, Components, Search),
 2347      nonvar(Search),
 2348      catch(uri_query_components(Search, Query),
 2349            error(syntax_error(_),_),
 2350            fail)
 2351    },
 2352    !,
 2353    [ search(Query) ].
 2354uri_search(_) --> [].
 2355
 2356uri_fragment(Components) -->
 2357    { uri_data(fragment, Components, String),
 2358      nonvar(String),
 2359      !,
 2360      uri_encoded(fragment, Fragment, String)
 2361    },
 2362    [ fragment(Fragment) ].
 2363uri_fragment(_) --> [].
 request_header(+In:stream, -Header:list) is det
Read the remainder (after the request-uri) of the HTTP header and return it as a Name(Value) list.
 2370request_header(_, []) -->               % Old-style non-version header
 2371    blanks,
 2372    eos,
 2373    !.
 2374request_header(Fd, [http_version(Version)|Header]) -->
 2375    http_version(Version),
 2376    blanks,
 2377    eos,
 2378    !,
 2379    {   Version = 1-_
 2380    ->  http_read_header(Fd, Header)
 2381    ;   Header = []
 2382    }.
 2383
 2384http_version(Version) -->
 2385    blanks,
 2386    "HTTP/",
 2387    http_version_number(Version).
 2388
 2389http_version_number(Major-Minor) -->
 2390    integer(Major),
 2391    ".",
 2392    integer(Minor).
 2393
 2394
 2395                 /*******************************
 2396                 *            COOKIES           *
 2397                 *******************************/
 cookies(-List)// is semidet
Translate a cookie description into a list Name=Value.
 2403cookies([Name=Value|T]) -->
 2404    blanks,
 2405    cookie(Name, Value),
 2406    !,
 2407    blanks,
 2408    (   ";"
 2409    ->  cookies(T)
 2410    ;   { T = [] }
 2411    ).
 2412cookies(List) -->
 2413    string(Skipped),
 2414    ";",
 2415    !,
 2416    { print_message(warning, http(skipped_cookie(Skipped))) },
 2417    cookies(List).
 2418cookies([]) -->
 2419    blanks.
 2420
 2421cookie(Name, Value) -->
 2422    cookie_name(Name),
 2423    blanks, "=", blanks,
 2424    cookie_value(Value).
 2425
 2426cookie_name(Name) -->
 2427    { var(Name) },
 2428    !,
 2429    rd_field_chars_no_fold(Chars),
 2430    { atom_codes(Name, Chars) }.
 2431
 2432cookie_value(Value) -->
 2433    quoted_string(Value),
 2434    !.
 2435cookie_value(Value) -->
 2436    chars_to_semicolon_or_blank(Chars),
 2437    { atom_codes(Value, Chars)
 2438    }.
 2439
 2440chars_to_semicolon_or_blank([]), ";" -->
 2441    ";",
 2442    !.
 2443chars_to_semicolon_or_blank([]) -->
 2444    " ",
 2445    blanks,
 2446    eos,
 2447    !.
 2448chars_to_semicolon_or_blank([H|T]) -->
 2449    [H],
 2450    !,
 2451    chars_to_semicolon_or_blank(T).
 2452chars_to_semicolon_or_blank([]) -->
 2453    [].
 2454
 2455set_cookie(set_cookie(Name, Value, Options)) -->
 2456    ws,
 2457    cookie(Name, Value),
 2458    cookie_options(Options).
 2459
 2460cookie_options([H|T]) -->
 2461    ws,
 2462    ";",
 2463    ws,
 2464    cookie_option(H),
 2465    !,
 2466    cookie_options(T).
 2467cookie_options([]) -->
 2468    ws.
 2469
 2470ws --> " ", !, ws.
 2471ws --> [].
 cookie_option(-Option)// is semidet
True if input represents a valid Cookie option. Officially, all cookie options use the syntax <name>=<value>, except for Secure and HttpOnly.
Arguments:
Option- Term of the form Name=Value
bug
- Incorrectly accepts options without = for M$ compatibility.
 2483cookie_option(Name=Value) -->
 2484    rd_field_chars(NameChars), ws,
 2485    { atom_codes(Name, NameChars) },
 2486    (   "="
 2487    ->  ws,
 2488        chars_to_semicolon(ValueChars),
 2489        { atom_codes(Value, ValueChars)
 2490        }
 2491    ;   { Value = true }
 2492    ).
 2493
 2494chars_to_semicolon([H|T]) -->
 2495    [H],
 2496    { H \== 32, H \== 0'; },
 2497    !,
 2498    chars_to_semicolon(T).
 2499chars_to_semicolon([]), ";" -->
 2500    ws, ";",
 2501    !.
 2502chars_to_semicolon([H|T]) -->
 2503    [H],
 2504    chars_to_semicolon(T).
 2505chars_to_semicolon([]) -->
 2506    [].
 range(-Range)// is semidet
Process the range header value. Range is currently defined as:
bytes(From, To)
Where From is an integer and To is either an integer or the atom end.
 2516range(bytes(From, To)) -->
 2517    "bytes", whites, "=", whites, integer(From), "-",
 2518    (   integer(To)
 2519    ->  ""
 2520    ;   { To = end }
 2521    ).
 2522
 2523
 2524                 /*******************************
 2525                 *           REPLY DCG          *
 2526                 *******************************/
 reply(+In, -Reply:list)// is semidet
Process the first line of an HTTP reply. After that, read the remainder of the header and parse it. After successful completion, Reply contains the following fields, followed by the fields produced by http_read_header/2.
http_version(Major-Minor)
status(Code, Status, Comment)
Code is an integer between 100 and 599. Status is a Prolog internal name. Comment is the comment following the code as it appears in the reply's HTTP status line. @see status_number//2.
 2543reply(Fd, [http_version(HttpVersion), status(Code, Status, Comment)|Header]) -->
 2544    http_version(HttpVersion),
 2545    blanks,
 2546    (   status_number(Status, Code)
 2547    ->  []
 2548    ;   integer(Status)
 2549    ),
 2550    blanks,
 2551    string(CommentCodes),
 2552    blanks_to_nl,
 2553    !,
 2554    blanks,
 2555    { atom_codes(Comment, CommentCodes),
 2556      http_read_header(Fd, Header)
 2557    }.
 2558
 2559
 2560                 /*******************************
 2561                 *            READ HEADER       *
 2562                 *******************************/
 http_read_header(+Fd, -Header) is det
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 --> content_type(text/html)
 2570http_read_header(Fd, Header) :-
 2571    read_header_data(Fd, Text),
 2572    http_parse_header(Text, Header).
 2573
 2574read_header_data(Fd, Header) :-
 2575    read_line_to_codes(Fd, Header, Tail),
 2576    read_header_data(Header, Fd, Tail),
 2577    debug(http(header), 'Header = ~n~s~n', [Header]).
 2578
 2579read_header_data([0'\r,0'\n], _, _) :- !.
 2580read_header_data([0'\n], _, _) :- !.
 2581read_header_data([], _, _) :- !.
 2582read_header_data(_, Fd, Tail) :-
 2583    read_line_to_codes(Fd, Tail, NewTail),
 2584    read_header_data(Tail, Fd, NewTail).
 http_parse_header(+Text:codes, -Header:list) is det
Header is a list of Name(Value)-terms representing the structure of the HTTP header in Text.
Errors
- domain_error(http_request_line, Line)
 2593http_parse_header(Text, Header) :-
 2594    phrase(header(Header), Text),
 2595    debug(http(header), 'Field: ~p', [Header]).
 2596
 2597header(List) -->
 2598    header_field(Name, Value),
 2599    !,
 2600    { mkfield(Name, Value, List, Tail)
 2601    },
 2602    blanks,
 2603    header(Tail).
 2604header([]) -->
 2605    blanks,
 2606    eos,
 2607    !.
 2608header(_) -->
 2609    string(S), blanks_to_nl,
 2610    !,
 2611    { string_codes(Line, S),
 2612      syntax_error(http_parameter(Line))
 2613    }.
 address//
Emit the HTML for the server address on behalve of error and status messages (non-200 replies). Default is
SWI-Prolog httpd at <hostname>

The address can be modified by providing a definition for the multifile predicate http:http_address//0.

 2627:- multifile
 2628    http:http_address//0. 2629
 2630address -->
 2631    http:http_address,
 2632    !.
 2633address -->
 2634    { gethostname(Host) },
 2635    html(address([ a(href('http://www.swi-prolog.org'), 'SWI-Prolog'),
 2636                   ' httpd at ', Host
 2637                 ])).
 2638
 2639mkfield(host, Host:Port, [host(Host),port(Port)|Tail], Tail) :- !.
 2640mkfield(Name, Value, [Att|Tail], Tail) :-
 2641    Att =.. [Name, Value].
 http:http_address// is det
HTML-rule that emits the location of the HTTP server. This hook is called from address//0 to customise the server address. The server address is emitted on non-200-ok replies.
 http:status_page(+Status, +Context, -HTMLTokens) is semidet
Hook called by http_status_reply/4 and http_status_reply/5 that allows for emitting custom error pages for the following HTTP page types:

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

Arguments:
Context- is the 4th argument of http_status_reply/5, which is invoked after raising an exception of the format http_reply(Status, HeaderExtra, Context). The default context is [] (the empty list).
HTMLTokens- is a list of tokens as produced by html//1. It is passed to print_html/2.
 2680                 /*******************************
 2681                 *            MESSAGES          *
 2682                 *******************************/
 2683
 2684:- multifile
 2685    prolog:message//1,
 2686    prolog:error_message//1. 2687
 2688prolog:error_message(http_write_short(Data, Sent)) -->
 2689    data(Data),
 2690    [ ': remote hangup after ~D bytes'-[Sent] ].
 2691prolog:error_message(syntax_error(http_request(Request))) -->
 2692    [ 'Illegal HTTP request: ~s'-[Request] ].
 2693prolog:error_message(syntax_error(http_parameter(Line))) -->
 2694    [ 'Illegal HTTP parameter: ~s'-[Line] ].
 2695
 2696prolog:message(http(skipped_cookie(S))) -->
 2697    [ 'Skipped illegal cookie: ~s'-[S] ].
 2698
 2699data(bytes(MimeType, _Bytes)) -->
 2700    !,
 2701    [ 'bytes(~p, ...)'-[MimeType] ].
 2702data(Data) -->
 2703    [ '~p'-[Data] ]