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:- if(exists_source(http_exception)).   68:- autoload(http_exception,[map_exception_to_http_status/4]).   69:- endif.   70:- autoload(mimepack,[mime_pack/3]).   71:- autoload(mimetype,[file_mime_type/2]).   72:- autoload(library(apply),[maplist/2]).   73:- autoload(library(base64),[base64/2]).   74:- use_module(library(debug),[debug/3,debugging/1]).   75:- autoload(library(error),[syntax_error/1,domain_error/2]).   76:- autoload(library(lists),[append/3,member/2,select/3,delete/3]).   77:- autoload(library(memfile),
   78	    [ new_memory_file/1, open_memory_file/3,
   79	      free_memory_file/1, open_memory_file/4,
   80	      size_memory_file/3
   81	    ]).   82:- autoload(library(option),[option/3,option/2]).   83:- autoload(library(pairs),[pairs_values/2]).   84:- autoload(library(readutil),
   85	    [read_line_to_codes/2,read_line_to_codes/3]).   86:- autoload(library(sgml_write),[xml_write/3]).   87:- autoload(library(socket),[gethostname/1]).   88:- autoload(library(uri),
   89	    [ uri_components/2, uri_data/3, uri_encoded/3, uri_query_components/2
   90	    ]).   91:- autoload(library(url),[parse_url_search/2]).   92:- autoload(library(dcg/basics),
   93	    [ integer/3, atom/3, whites/2, blanks_to_nl/2, string/3,
   94	      number/3, blanks/2, float/3, nonblanks/3, eos/2
   95	    ]).   96:- use_module(library(settings),[setting/4,setting/2]).   97
   98:- multifile
   99    http:status_page/3,             % +Status, +Context, -HTML
  100    http:status_reply/3,            % +Status, -Reply, +Options
  101    http:serialize_reply/2,         % +Reply, -Body
  102    http:post_data_hook/3,          % +Data, +Out, +HdrExtra
  103    http:mime_type_encoding/2.      % +MimeType, -Encoding
  104
  105% see http_update_transfer/4.
  106
  107:- setting(http:chunked_transfer, oneof([never,on_request,if_possible]),
  108           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. */

  118:- discontiguous
  119    term_expansion/2.  120
  121
  122                 /*******************************
  123                 *          READ REQUEST        *
  124                 *******************************/
 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.
  132http_read_request(In, Request) :-
  133    catch(read_line_to_codes(In, Codes), E, true),
  134    (   var(E)
  135    ->  (   Codes == end_of_file
  136        ->  debug(http(header), 'end-of-file', []),
  137            Request = end_of_file
  138        ;   debug(http(header), 'First line: ~s', [Codes]),
  139            Request =  [input(In)|Request1],
  140            phrase(request(In, Request1), Codes),
  141            (   Request1 = [unknown(Text)|_]
  142            ->  string_codes(S, Text),
  143                syntax_error(http_request(S))
  144            ;   true
  145            )
  146        )
  147    ;   (   debugging(http(request))
  148        ->  message_to_string(E, Msg),
  149            debug(http(request), "Exception reading 1st line: ~s", [Msg])
  150        ;   true
  151        ),
  152        Request = end_of_file
  153    ).
 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.
  161http_read_reply_header(In, [input(In)|Reply]) :-
  162    read_line_to_codes(In, Codes),
  163    (   Codes == end_of_file
  164    ->  debug(http(header), 'end-of-file', []),
  165        throw(error(syntax(http_reply_header, end_of_file), _))
  166    ;   debug(http(header), 'First line: ~s~n', [Codes]),
  167        (   phrase(reply(In, Reply), Codes)
  168        ->  true
  169        ;   atom_codes(Header, Codes),
  170            syntax_error(http_reply_header(Header))
  171        )
  172    ).
  173
  174
  175                 /*******************************
  176                 *        FORMULATE REPLY       *
  177                 *******************************/
 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
  226http_reply(What, Out) :-
  227    http_reply(What, Out, [connection(close)], _).
  228
  229http_reply(Data, Out, HdrExtra) :-
  230    http_reply(Data, Out, HdrExtra, _Code).
  231
  232http_reply(Data, Out, HdrExtra, Code) :-
  233    http_reply(Data, Out, HdrExtra, [], Code).
  234
  235http_reply(Data, Out, HdrExtra, Context, Code) :-
  236    http_reply(Data, Out, HdrExtra, Context, [method(get)], Code).
  237
  238http_reply(Data, Out, HdrExtra, _Context, Request, Code) :-
  239    byte_count(Out, C0),
  240    memberchk(method(Method), Request),
  241    catch(http_reply_data(Data, Out, HdrExtra, Method, Code), E, true),
  242    !,
  243    (   var(E)
  244    ->  true
  245    ;   (   E = error(io_error(write,_), _)
  246        ;   E = error(socket_error(_,_), _)
  247        )
  248    ->  byte_count(Out, C1),
  249        Sent is C1 - C0,
  250        throw(error(http_write_short(Data, Sent), _))
  251    ;   E = error(timeout_error(write, _), _)
  252    ->  throw(E)
  253    ;   map_exception_to_http_status(E, Status, NewHdr, NewContext)
  254    ->  http_status_reply(Status, Out, NewHdr, NewContext, Request, Code)
  255    ;   throw(E)
  256    ).
  257http_reply(Status, Out, HdrExtra, Context, Request, Code) :-
  258    http_status_reply(Status, Out, HdrExtra, Context, Request, Code).
  259
  260:- if(\+current_predicate(map_exception_to_http_status/4)).  261map_exception_to_http_status(_E, _Status, _NewHdr, _NewContext) :-
  262    fail.
  263:- endif.  264
  265:- meta_predicate
  266    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.
  275http_reply_data(Data, Out, HdrExtra, Method, Code) :-
  276    http_reply_data_(Data, Out, HdrExtra, Method, Code),
  277    flush_output(Out).
  278
  279http_reply_data_(html(HTML), Out, HdrExtra, Method, Code) :-
  280    !,
  281    phrase(reply_header(html(HTML), HdrExtra, Code), Header),
  282    send_reply_header(Out, Header),
  283    if_no_head(print_html(Out, HTML), Method).
  284http_reply_data_(file(Type, File), Out, HdrExtra, Method, Code) :-
  285    !,
  286    phrase(reply_header(file(Type, File), HdrExtra, Code), Header),
  287    reply_file(Out, File, Header, Method).
  288http_reply_data_(gzip_file(Type, File), Out, HdrExtra, Method, Code) :-
  289    !,
  290    phrase(reply_header(gzip_file(Type, File), HdrExtra, Code), Header),
  291    reply_file(Out, File, Header, Method).
  292http_reply_data_(file(Type, File, Range), Out, HdrExtra, Method, Code) :-
  293    !,
  294    phrase(reply_header(file(Type, File, Range), HdrExtra, Code), Header),
  295    reply_file_range(Out, File, Header, Range, Method).
  296http_reply_data_(tmp_file(Type, File), Out, HdrExtra, Method, Code) :-
  297    !,
  298    phrase(reply_header(tmp_file(Type, File), HdrExtra, Code), Header),
  299    reply_file(Out, File, Header, Method).
  300http_reply_data_(bytes(Type, Bytes), Out, HdrExtra, Method, Code) :-
  301    !,
  302    phrase(reply_header(bytes(Type, Bytes), HdrExtra, Code), Header),
  303    send_reply_header(Out, Header),
  304    if_no_head(format(Out, '~s', [Bytes]), Method).
  305http_reply_data_(stream(In, Len), Out, HdrExtra, Method, Code) :-
  306    !,
  307    phrase(reply_header(cgi_data(Len), HdrExtra, Code), Header),
  308    copy_stream(Out, In, Header, Method, 0, end).
  309http_reply_data_(cgi_stream(In, Len), Out, HdrExtra, Method, Code) :-
  310    !,
  311    http_read_header(In, CgiHeader),
  312    seek(In, 0, current, Pos),
  313    Size is Len - Pos,
  314    http_join_headers(HdrExtra, CgiHeader, Hdr2),
  315    phrase(reply_header(cgi_data(Size), Hdr2, Code), Header),
  316    copy_stream(Out, In, Header, Method, 0, end).
  317
  318if_no_head(_, head) :-
  319    !.
  320if_no_head(Goal, _) :-
  321    call(Goal).
  322
  323reply_file(Out, _File, Header, head) :-
  324    !,
  325    send_reply_header(Out, Header).
  326reply_file(Out, File, Header, _) :-
  327    setup_call_cleanup(
  328        open(File, read, In, [type(binary)]),
  329        copy_stream(Out, In, Header, 0, end),
  330        close(In)).
  331
  332reply_file_range(Out, _File, Header, _Range, head) :-
  333    !,
  334    send_reply_header(Out, Header).
  335reply_file_range(Out, File, Header, bytes(From, To), _) :-
  336    setup_call_cleanup(
  337        open(File, read, In, [type(binary)]),
  338        copy_stream(Out, In, Header, From, To),
  339        close(In)).
  340
  341copy_stream(Out, _, Header, head, _, _) :-
  342    !,
  343    send_reply_header(Out, Header).
  344copy_stream(Out, In, Header, _, From, To) :-
  345    copy_stream(Out, In, Header, From, To).
  346
  347copy_stream(Out, In, Header, From, To) :-
  348    (   From == 0
  349    ->  true
  350    ;   seek(In, From, bof, _)
  351    ),
  352    peek_byte(In, _),
  353    send_reply_header(Out, Header),
  354    (   To == end
  355    ->  copy_stream_data(In, Out)
  356    ;   Len is To - From,
  357        copy_stream_data(In, Out, Len)
  358    ).
 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)
  392http_status_reply(Status, Out, Options) :-
  393    _{header:HdrExtra, context:Context, code:Code, method:Method} :< Options,
  394    http_status_reply(Status, Out, HdrExtra, Context, [method(Method)], Code).
  395
  396http_status_reply(Status, Out, HdrExtra, Code) :-
  397    http_status_reply(Status, Out, HdrExtra, [], Code).
  398
  399http_status_reply(Status, Out, HdrExtra, Context, Code) :-
  400    http_status_reply(Status, Out, HdrExtra, Context, [method(get)], Code).
  401
  402http_status_reply(Status, Out, HdrExtra, Context, Request, Code) :-
  403    option(method(Method), Request, get),
  404    parsed_accept(Request, Accept),
  405    status_reply_flush(Status, Out,
  406                       _{ context: Context,
  407                          method:  Method,
  408                          code:    Code,
  409                          accept:  Accept,
  410                          header:  HdrExtra
  411                        }).
  412
  413parsed_accept(Request, Accept) :-
  414    memberchk(accept(Accept0), Request),
  415    http_parse_header_value(accept, Accept0, Accept1),
  416    !,
  417    Accept = Accept1.
  418parsed_accept(_, [ media(text/html, [], 0.1,  []),
  419                   media(_,         [], 0.01, [])
  420                 ]).
  421
  422status_reply_flush(Status, Out, Options) :-
  423    status_reply(Status, Out, Options),
  424    !,
  425    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:
  438% Replies without content
  439status_reply(no_content, Out, Options) :-
  440    !,
  441    phrase(reply_header(status(no_content), Options), Header),
  442    send_reply_header(Out, Header).
  443status_reply(switching_protocols(_Goal,SwitchOptions), Out, Options) :-
  444    !,
  445    (   option(headers(Extra1), SwitchOptions)
  446    ->  true
  447    ;   option(header(Extra1), SwitchOptions, [])
  448    ),
  449    http_join_headers(Options.header, Extra1, HdrExtra),
  450    phrase(reply_header(status(switching_protocols),
  451                        Options.put(header,HdrExtra)), Header),
  452    send_reply_header(Out, Header).
  453status_reply(authorise(basic, ''), Out, Options) :-
  454    !,
  455    status_reply(authorise(basic), Out, Options).
  456status_reply(authorise(basic, Realm), Out, Options) :-
  457    !,
  458    status_reply(authorise(basic(Realm)), Out, Options).
  459status_reply(not_modified, Out, Options) :-
  460    !,
  461    phrase(reply_header(status(not_modified), Options), Header),
  462    send_reply_header(Out, Header).
  463% aliases (compatibility)
  464status_reply(busy, Out, Options) :-
  465    status_reply(service_unavailable(busy), Out, Options).
  466status_reply(unavailable(Why), Out, Options) :-
  467    status_reply(service_unavailable(Why), Out, Options).
  468status_reply(resource_error(Why), Out, Options) :-
  469    status_reply(service_unavailable(Why), Out, Options).
  470% replies with content
  471status_reply(Status, Out, Options) :-
  472    status_has_content(Status),
  473    status_page_hook(Status, Reply, Options),
  474    serialize_body(Reply, Body),
  475    Status =.. List,
  476    append(List, [Body], ExList),
  477    ExStatus =.. ExList,
  478    phrase(reply_header(ExStatus, Options), Header),
  479    send_reply_header(Out, Header),
  480    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.
  487status_has_content(created(_Location)).
  488status_has_content(moved(_To)).
  489status_has_content(moved_temporary(_To)).
  490status_has_content(gone(_URL)).
  491status_has_content(see_other(_To)).
  492status_has_content(bad_request(_ErrorTerm)).
  493status_has_content(authorise(_Method)).
  494status_has_content(forbidden(_URL)).
  495status_has_content(not_found(_URL)).
  496status_has_content(method_not_allowed(_Method, _URL)).
  497status_has_content(not_acceptable(_Why)).
  498status_has_content(server_error(_ErrorTerm)).
  499status_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.
  510serialize_body(Reply, Body) :-
  511    http:serialize_reply(Reply, Body),
  512    !.
  513serialize_body(html_tokens(Tokens), body(text/html, utf8, Content)) :-
  514    !,
  515    with_output_to(string(Content), print_html(Tokens)).
  516serialize_body(Reply, Reply) :-
  517    Reply = body(_,_,_),
  518    !.
  519serialize_body(Reply, _) :-
  520    domain_error(http_reply_body, Reply).
  521
  522reply_status_body(_, _, Options) :-
  523    Options.method == head,
  524    !.
  525reply_status_body(Out, body(_Type, Encoding, Content), _Options) :-
  526    (   Encoding == octet
  527    ->  format(Out, '~s', [Content])
  528    ;   setup_call_cleanup(
  529            set_stream(Out, encoding(Encoding)),
  530            format(Out, '~s', [Content]),
  531            set_stream(Out, encoding(octet)))
  532    ).
 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
  559status_page_hook(Term, Reply, Options) :-
  560    Context = Options.context,
  561    functor(Term, Name, _),
  562    status_number_fact(Name, Code),
  563    (   Options.code = Code,
  564        http:status_reply(Term, Reply, Options)
  565    ;   http:status_page(Term, Context, HTML),
  566        Reply = html_tokens(HTML)
  567    ;   http:status_page(Code, Context, HTML), % deprecated
  568        Reply = html_tokens(HTML)
  569    ),
  570    !.
  571status_page_hook(created(Location), html_tokens(HTML), _Options) :-
  572    phrase(page([ title('201 Created')
  573                ],
  574                [ h1('Created'),
  575                  p(['The document was created ',
  576                     a(href(Location), ' Here')
  577                    ]),
  578                  \address
  579                ]),
  580           HTML).
  581status_page_hook(moved(To), html_tokens(HTML), _Options) :-
  582    phrase(page([ title('301 Moved Permanently')
  583                ],
  584                [ h1('Moved Permanently'),
  585                  p(['The document has moved ',
  586                     a(href(To), ' Here')
  587                    ]),
  588                  \address
  589                ]),
  590           HTML).
  591status_page_hook(moved_temporary(To), html_tokens(HTML), _Options) :-
  592    phrase(page([ title('302 Moved Temporary')
  593                ],
  594                [ h1('Moved Temporary'),
  595                  p(['The document is currently ',
  596                     a(href(To), ' Here')
  597                    ]),
  598                  \address
  599                ]),
  600           HTML).
  601status_page_hook(gone(URL), html_tokens(HTML), _Options) :-
  602    phrase(page([ title('410 Resource Gone')
  603                ],
  604                [ h1('Resource Gone'),
  605                  p(['The document has been removed ',
  606                     a(href(URL), ' from here')
  607                    ]),
  608                  \address
  609                ]),
  610           HTML).
  611status_page_hook(see_other(To), html_tokens(HTML), _Options) :-
  612    phrase(page([ title('303 See Other')
  613                 ],
  614                 [ h1('See Other'),
  615                   p(['See other document ',
  616                      a(href(To), ' Here')
  617                     ]),
  618                   \address
  619                 ]),
  620            HTML).
  621status_page_hook(bad_request(ErrorTerm), html_tokens(HTML), _Options) :-
  622    '$messages':translate_message(ErrorTerm, Lines, []),
  623    phrase(page([ title('400 Bad Request')
  624                ],
  625                [ h1('Bad Request'),
  626                  p(\html_message_lines(Lines)),
  627                  \address
  628                ]),
  629           HTML).
  630status_page_hook(authorise(_Method), html_tokens(HTML), _Options):-
  631    phrase(page([ title('401 Authorization Required')
  632                ],
  633                [ h1('Authorization Required'),
  634                  p(['This server could not verify that you ',
  635                     'are authorized to access the document ',
  636                     'requested.  Either you supplied the wrong ',
  637                     'credentials (e.g., bad password), or your ',
  638                     'browser doesn\'t understand how to supply ',
  639                     'the credentials required.'
  640                    ]),
  641                  \address
  642                ]),
  643           HTML).
  644status_page_hook(forbidden(URL), html_tokens(HTML), _Options) :-
  645    phrase(page([ title('403 Forbidden')
  646                ],
  647                [ h1('Forbidden'),
  648                  p(['You don\'t have permission to access ', URL,
  649                     ' on this server'
  650                    ]),
  651                  \address
  652                ]),
  653           HTML).
  654status_page_hook(not_found(URL), html_tokens(HTML), _Options) :-
  655    phrase(page([ title('404 Not Found')
  656                ],
  657                [ h1('Not Found'),
  658                  p(['The requested URL ', tt(URL),
  659                     ' was not found on this server'
  660                    ]),
  661                  \address
  662                ]),
  663           HTML).
  664status_page_hook(method_not_allowed(Method,URL), html_tokens(HTML), _Options) :-
  665    upcase_atom(Method, UMethod),
  666    phrase(page([ title('405 Method not allowed')
  667                ],
  668                [ h1('Method not allowed'),
  669                  p(['The requested URL ', tt(URL),
  670                     ' does not support method ', tt(UMethod), '.'
  671                    ]),
  672                  \address
  673                ]),
  674           HTML).
  675status_page_hook(not_acceptable(WhyHTML), html_tokens(HTML), _Options) :-
  676    phrase(page([ title('406 Not Acceptable')
  677                ],
  678                [ h1('Not Acceptable'),
  679                  WhyHTML,
  680                  \address
  681                ]),
  682           HTML).
  683status_page_hook(server_error(ErrorTerm), html_tokens(HTML), _Options) :-
  684    '$messages':translate_message(ErrorTerm, Lines, []),
  685    phrase(page([ title('500 Internal server error')
  686                ],
  687                [ h1('Internal server error'),
  688                  p(\html_message_lines(Lines)),
  689                  \address
  690                ]),
  691           HTML).
  692status_page_hook(service_unavailable(Why), html_tokens(HTML), _Options) :-
  693    phrase(page([ title('503 Service Unavailable')
  694                ],
  695                [ h1('Service Unavailable'),
  696                  \unavailable(Why),
  697                  \address
  698                ]),
  699           HTML).
  700
  701unavailable(busy) -->
  702    html(p(['The server is temporarily out of resources, ',
  703            'please try again later'])).
  704unavailable(error(Formal,Context)) -->
  705    { '$messages':translate_message(error(Formal,Context), Lines, []) },
  706    html_message_lines(Lines).
  707unavailable(HTML) -->
  708    html(HTML).
  709
  710html_message_lines([]) -->
  711    [].
  712html_message_lines([nl|T]) -->
  713    !,
  714    html([br([])]),
  715    html_message_lines(T).
  716html_message_lines([flush]) -->
  717    [].
  718html_message_lines([ansi(_Style,Fmt,Args)|T]) -->
  719    !,
  720    { format(string(S), Fmt, Args)
  721    },
  722    html([S]),
  723    html_message_lines(T).
  724html_message_lines([url(Pos)|T]) -->
  725    !,
  726    msg_url(Pos),
  727    html_message_lines(T).
  728html_message_lines([url(URL, Label)|T]) -->
  729    !,
  730    html(a(href(URL), Label)),
  731    html_message_lines(T).
  732html_message_lines([Fmt-Args|T]) -->
  733    !,
  734    { format(string(S), Fmt, Args)
  735    },
  736    html([S]),
  737    html_message_lines(T).
  738html_message_lines([Fmt|T]) -->
  739    !,
  740    { format(string(S), Fmt, [])
  741    },
  742    html([S]),
  743    html_message_lines(T).
  744
  745msg_url(File:Line:Pos) -->
  746    !,
  747    html([File, :, Line, :, Pos]).
  748msg_url(File:Line) -->
  749    !,
  750    html([File, :, Line]).
  751msg_url(File) -->
  752    html([File]).
 http_join_headers(+Default, +Header, -Out)
Append headers from Default to Header if they are not already part of it.
  759http_join_headers([], H, H).
  760http_join_headers([H|T], Hdr0, Hdr) :-
  761    functor(H, N, A),
  762    functor(H2, N, A),
  763    member(H2, Hdr0),
  764    !,
  765    http_join_headers(T, Hdr0, Hdr).
  766http_join_headers([H|T], Hdr0, [H|Hdr]) :-
  767    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.
  779http_update_encoding(Header0, Encoding, Header) :-
  780    memberchk(content_type(Type), Header0),
  781    !,
  782    http_update_encoding(Type, Header0, Encoding, Header).
  783http_update_encoding(Header, octet, Header).
  784
  785http_update_encoding('text/event-stream', Header, utf8, Header) :-
  786    !.
  787http_update_encoding(Type0, Header0, utf8, [content_type(Type)|Header]) :-
  788    sub_atom(Type0, 0, _, _, 'text/'),
  789    !,
  790    select(content_type(_), Header0, Header),
  791    !,
  792    (   sub_atom(Type0, S, _, _, ';')
  793    ->  sub_atom(Type0, 0, S, _, B)
  794    ;   B = Type0
  795    ),
  796    atom_concat(B, '; charset=UTF-8', Type).
  797http_update_encoding(Type, Header, Encoding, Header) :-
  798    (   sub_atom_icasechk(Type, _, 'utf-8')
  799    ->  Encoding = utf8
  800    ;   http:mime_type_encoding(Type, Encoding)
  801    ->  true
  802    ;   mime_type_encoding(Type, Encoding)
  803    ->  true
  804    ;   Encoding = octet
  805    ).
 mime_type_encoding(+MimeType, -Encoding) is semidet
Encoding is the (default) character encoding for MimeType. Hooked by http:mime_type_encoding/2.
  812mime_type_encoding('application/json',                utf8).
  813mime_type_encoding('application/jsonrequest',         utf8).
  814mime_type_encoding('application/x-prolog',            utf8).
  815mime_type_encoding('application/n-quads',             utf8).
  816mime_type_encoding('application/n-triples',           utf8).
  817mime_type_encoding('application/sparql-query',        utf8).
  818mime_type_encoding('application/trig',                utf8).
  819mime_type_encoding('application/sparql-results+json', utf8).
  820mime_type_encoding('application/sparql-results+xml',  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.
  836http_update_connection(CgiHeader, Request, Connect,
  837                       [connection(Connect)|Rest]) :-
  838    select(connection(CgiConn), CgiHeader, Rest),
  839    !,
  840    connection(Request, ReqConnection),
  841    join_connection(ReqConnection, CgiConn, Connect).
  842http_update_connection(CgiHeader, Request, Connect,
  843                       [connection(Connect)|CgiHeader]) :-
  844    connection(Request, Connect).
  845
  846join_connection(Keep1, Keep2, Connection) :-
  847    (   downcase_atom(Keep1, 'keep-alive'),
  848        downcase_atom(Keep2, 'keep-alive')
  849    ->  Connection = 'Keep-Alive'
  850    ;   Connection = close
  851    ).
 connection(+Header, -Connection)
Extract the desired connection from a header.
  858connection(Header, Close) :-
  859    (   memberchk(connection(Connection), Header)
  860    ->  Close = Connection
  861    ;   memberchk(http_version(1-X), Header),
  862        X >= 1
  863    ->  Close = 'Keep-Alive'
  864    ;   Close = close
  865    ).
 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.

  884http_update_transfer(Request, CgiHeader, Transfer, Header) :-
  885    setting(http:chunked_transfer, When),
  886    http_update_transfer(When, Request, CgiHeader, Transfer, Header).
  887
  888http_update_transfer(never, _, CgiHeader, none, Header) :-
  889    !,
  890    delete(CgiHeader, transfer_encoding(_), Header).
  891http_update_transfer(_, _, CgiHeader, none, Header) :-
  892    memberchk(location(_), CgiHeader),
  893    !,
  894    delete(CgiHeader, transfer_encoding(_), Header).
  895http_update_transfer(_, Request, CgiHeader, Transfer, Header) :-
  896    select(transfer_encoding(CgiTransfer), CgiHeader, Rest),
  897    !,
  898    transfer(Request, ReqConnection),
  899    join_transfer(ReqConnection, CgiTransfer, Transfer),
  900    (   Transfer == none
  901    ->  Header = Rest
  902    ;   Header = [transfer_encoding(Transfer)|Rest]
  903    ).
  904http_update_transfer(if_possible, Request, CgiHeader, Transfer, Header) :-
  905    transfer(Request, Transfer),
  906    Transfer \== none,
  907    !,
  908    Header = [transfer_encoding(Transfer)|CgiHeader].
  909http_update_transfer(_, _, CgiHeader, event_stream, CgiHeader) :-
  910    memberchk(content_type('text/event-stream'), CgiHeader),
  911    !.
  912http_update_transfer(_, _, CgiHeader, none, CgiHeader).
  913
  914join_transfer(chunked, chunked, chunked) :- !.
  915join_transfer(_, _, none).
 transfer(+Header, -Connection)
Extract the desired connection from a header.
  922transfer(Header, Transfer) :-
  923    (   memberchk(transfer_encoding(Transfer0), Header)
  924    ->  Transfer = Transfer0
  925    ;   memberchk(http_version(1-X), Header),
  926        X >= 1
  927    ->  Transfer = chunked
  928    ;   Transfer = none
  929    ).
 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.
  938content_length_in_encoding(Enc, Stream, Bytes) :-
  939    stream_property(Stream, position(Here)),
  940    setup_call_cleanup(
  941        open_null_stream(Out),
  942        ( set_stream(Out, encoding(Enc)),
  943          catch(copy_stream_data(Stream, Out), _, fail),
  944          flush_output(Out),
  945          byte_count(Out, Bytes)
  946        ),
  947        ( close(Out, [force(true)]),
  948          set_stream_position(Stream, Here)
  949        )).
  950
  951
  952                 /*******************************
  953                 *          POST SUPPORT        *
  954                 *******************************/
 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:
 1062http_post_data(Data, Out, HdrExtra) :-
 1063    http:post_data_hook(Data, Out, HdrExtra),
 1064    !.
 1065http_post_data(html(HTML), Out, HdrExtra) :-
 1066    !,
 1067    phrase(post_header(html(HTML), HdrExtra), Header),
 1068    send_request_header(Out, Header),
 1069    print_html(Out, HTML).
 1070http_post_data(xml(XML), Out, HdrExtra) :-
 1071    !,
 1072    http_post_data(xml(text/xml, XML, []), Out, HdrExtra).
 1073http_post_data(xml(Type, XML), Out, HdrExtra) :-
 1074    !,
 1075    http_post_data(xml(Type, XML, []), Out, HdrExtra).
 1076http_post_data(xml(Type, XML, Options), Out, HdrExtra) :-
 1077    !,
 1078    setup_call_cleanup(
 1079        new_memory_file(MemFile),
 1080        (   setup_call_cleanup(
 1081                open_memory_file(MemFile, write, MemOut),
 1082                xml_write(MemOut, XML, Options),
 1083                close(MemOut)),
 1084            http_post_data(memory_file(Type, MemFile), Out, HdrExtra)
 1085        ),
 1086        free_memory_file(MemFile)).
 1087http_post_data(file(File), Out, HdrExtra) :-
 1088    !,
 1089    (   file_mime_type(File, Type)
 1090    ->  true
 1091    ;   Type = text/plain
 1092    ),
 1093    http_post_data(file(Type, File), Out, HdrExtra).
 1094http_post_data(file(Type, File), Out, HdrExtra) :-
 1095    !,
 1096    phrase(post_header(file(Type, File), HdrExtra), Header),
 1097    send_request_header(Out, Header),
 1098    setup_call_cleanup(
 1099        open(File, read, In, [type(binary)]),
 1100        copy_stream_data(In, Out),
 1101        close(In)).
 1102http_post_data(memory_file(Type, Handle), Out, HdrExtra) :-
 1103    !,
 1104    phrase(post_header(memory_file(Type, Handle), HdrExtra), Header),
 1105    send_request_header(Out, Header),
 1106    setup_call_cleanup(
 1107        open_memory_file(Handle, read, In, [encoding(octet)]),
 1108        copy_stream_data(In, Out),
 1109        close(In)).
 1110http_post_data(codes(Codes), Out, HdrExtra) :-
 1111    !,
 1112    http_post_data(codes(text/plain, Codes), Out, HdrExtra).
 1113http_post_data(codes(Type, Codes), Out, HdrExtra) :-
 1114    !,
 1115    phrase(post_header(codes(Type, Codes), HdrExtra), Header),
 1116    send_request_header(Out, Header),
 1117    setup_call_cleanup(
 1118        set_stream(Out, encoding(utf8)),
 1119        format(Out, '~s', [Codes]),
 1120        set_stream(Out, encoding(octet))).
 1121http_post_data(bytes(Type, Bytes), Out, HdrExtra) :-
 1122    !,
 1123    phrase(post_header(bytes(Type, Bytes), HdrExtra), Header),
 1124    send_request_header(Out, Header),
 1125    format(Out, '~s', [Bytes]).
 1126http_post_data(atom(Atom), Out, HdrExtra) :-
 1127    !,
 1128    http_post_data(atom(text/plain, Atom), Out, HdrExtra).
 1129http_post_data(atom(Type, Atom), Out, HdrExtra) :-
 1130    !,
 1131    phrase(post_header(atom(Type, Atom), HdrExtra), Header),
 1132    send_request_header(Out, Header),
 1133    setup_call_cleanup(
 1134        set_stream(Out, encoding(utf8)),
 1135        write(Out, Atom),
 1136        set_stream(Out, encoding(octet))).
 1137http_post_data(string(String), Out, HdrExtra) :-
 1138    !,
 1139    http_post_data(atom(text/plain, String), Out, HdrExtra).
 1140http_post_data(string(Type, String), Out, HdrExtra) :-
 1141    !,
 1142    phrase(post_header(string(Type, String), HdrExtra), Header),
 1143    send_request_header(Out, Header),
 1144    setup_call_cleanup(
 1145        set_stream(Out, encoding(utf8)),
 1146        write(Out, String),
 1147        set_stream(Out, encoding(octet))).
 1148http_post_data(cgi_stream(In, _Len), Out, HdrExtra) :-
 1149    !,
 1150    debug(obsolete, 'Obsolete 2nd argument in cgi_stream(In,Len)', []),
 1151    http_post_data(cgi_stream(In), Out, HdrExtra).
 1152http_post_data(cgi_stream(In), Out, HdrExtra) :-
 1153    !,
 1154    http_read_header(In, Header0),
 1155    http_update_encoding(Header0, Encoding, Header),
 1156    content_length_in_encoding(Encoding, In, Size),
 1157    http_join_headers(HdrExtra, Header, Hdr2),
 1158    phrase(post_header(cgi_data(Size), Hdr2), HeaderText),
 1159    send_request_header(Out, HeaderText),
 1160    setup_call_cleanup(
 1161        set_stream(Out, encoding(Encoding)),
 1162        copy_stream_data(In, Out),
 1163        set_stream(Out, encoding(octet))).
 1164http_post_data(form(Fields), Out, HdrExtra) :-
 1165    !,
 1166    parse_url_search(Codes, Fields),
 1167    length(Codes, Size),
 1168    http_join_headers(HdrExtra,
 1169                      [ content_type('application/x-www-form-urlencoded')
 1170                      ], Header),
 1171    phrase(post_header(cgi_data(Size), Header), HeaderChars),
 1172    send_request_header(Out, HeaderChars),
 1173    format(Out, '~s', [Codes]).
 1174http_post_data(form_data(Data), Out, HdrExtra) :-
 1175    !,
 1176    setup_call_cleanup(
 1177        new_memory_file(MemFile),
 1178        ( setup_call_cleanup(
 1179              open_memory_file(MemFile, write, MimeOut),
 1180              mime_pack(Data, MimeOut, Boundary),
 1181              close(MimeOut)),
 1182          size_memory_file(MemFile, Size, octet),
 1183          format(string(ContentType),
 1184                 'multipart/form-data; boundary=~w', [Boundary]),
 1185          http_join_headers(HdrExtra,
 1186                            [ mime_version('1.0'),
 1187                              content_type(ContentType)
 1188                            ], Header),
 1189          phrase(post_header(cgi_data(Size), Header), HeaderChars),
 1190          send_request_header(Out, HeaderChars),
 1191          setup_call_cleanup(
 1192              open_memory_file(MemFile, read, In, [encoding(octet)]),
 1193              copy_stream_data(In, Out),
 1194              close(In))
 1195        ),
 1196        free_memory_file(MemFile)).
 1197http_post_data(List, Out, HdrExtra) :-          % multipart-mixed
 1198    is_list(List),
 1199    !,
 1200    setup_call_cleanup(
 1201        new_memory_file(MemFile),
 1202        ( setup_call_cleanup(
 1203              open_memory_file(MemFile, write, MimeOut),
 1204              mime_pack(List, MimeOut, Boundary),
 1205              close(MimeOut)),
 1206          size_memory_file(MemFile, Size, octet),
 1207          format(string(ContentType),
 1208                 'multipart/mixed; boundary=~w', [Boundary]),
 1209          http_join_headers(HdrExtra,
 1210                            [ mime_version('1.0'),
 1211                              content_type(ContentType)
 1212                            ], Header),
 1213          phrase(post_header(cgi_data(Size), Header), HeaderChars),
 1214          send_request_header(Out, HeaderChars),
 1215          setup_call_cleanup(
 1216              open_memory_file(MemFile, read, In, [encoding(octet)]),
 1217              copy_stream_data(In, Out),
 1218              close(In))
 1219        ),
 1220        free_memory_file(MemFile)).
 post_header(+Data, +HeaderExtra)//
Generate the POST header, emitting HeaderExtra, followed by the HTTP Content-length and Content-type fields.
 1227post_header(html(Tokens), HdrExtra) -->
 1228    header_fields(HdrExtra, Len),
 1229    content_length(html(Tokens), Len),
 1230    content_type(text/html),
 1231    "\r\n".
 1232post_header(file(Type, File), HdrExtra) -->
 1233    header_fields(HdrExtra, Len),
 1234    content_length(file(File), Len),
 1235    content_type(Type),
 1236    "\r\n".
 1237post_header(memory_file(Type, File), HdrExtra) -->
 1238    header_fields(HdrExtra, Len),
 1239    content_length(memory_file(File), Len),
 1240    content_type(Type),
 1241    "\r\n".
 1242post_header(cgi_data(Size), HdrExtra) -->
 1243    header_fields(HdrExtra, Len),
 1244    content_length(Size, Len),
 1245    "\r\n".
 1246post_header(codes(Type, Codes), HdrExtra) -->
 1247    header_fields(HdrExtra, Len),
 1248    content_length(codes(Codes, utf8), Len),
 1249    content_type(Type, utf8),
 1250    "\r\n".
 1251post_header(bytes(Type, Bytes), HdrExtra) -->
 1252    header_fields(HdrExtra, Len),
 1253    content_length(bytes(Bytes), Len),
 1254    content_type(Type),
 1255    "\r\n".
 1256post_header(atom(Type, Atom), HdrExtra) -->
 1257    header_fields(HdrExtra, Len),
 1258    content_length(atom(Atom, utf8), Len),
 1259    content_type(Type, utf8),
 1260    "\r\n".
 1261post_header(string(Type, String), HdrExtra) -->
 1262    header_fields(HdrExtra, Len),
 1263    content_length(string(String, utf8), Len),
 1264    content_type(Type, utf8),
 1265    "\r\n".
 1266
 1267
 1268                 /*******************************
 1269                 *       OUTPUT HEADER DCG      *
 1270                 *******************************/
 http_reply_header(+Out:stream, +What, +HdrExtra) is det
Create a reply header using reply_header//3 and send it to Stream.
 1277http_reply_header(Out, What, HdrExtra) :-
 1278    phrase(reply_header(What, HdrExtra, _Code), String),
 1279    !,
 1280    send_reply_header(Out, 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.
 1304reply_header(Data, Dict) -->
 1305    { _{header:HdrExtra, code:Code} :< Dict },
 1306    reply_header(Data, HdrExtra, Code).
 1307
 1308reply_header(string(String), HdrExtra, Code) -->
 1309    reply_header(string(text/plain, String), HdrExtra, Code).
 1310reply_header(string(Type, String), HdrExtra, Code) -->
 1311    vstatus(ok, Code, HdrExtra),
 1312    date(now),
 1313    header_fields(HdrExtra, CLen),
 1314    content_length(codes(String, utf8), CLen),
 1315    content_type(Type, utf8),
 1316    "\r\n".
 1317reply_header(bytes(Type, Bytes), HdrExtra, Code) -->
 1318    vstatus(ok, Code, HdrExtra),
 1319    date(now),
 1320    header_fields(HdrExtra, CLen),
 1321    content_length(bytes(Bytes), CLen),
 1322    content_type(Type),
 1323    "\r\n".
 1324reply_header(html(Tokens), HdrExtra, Code) -->
 1325    vstatus(ok, Code, HdrExtra),
 1326    date(now),
 1327    header_fields(HdrExtra, CLen),
 1328    content_length(html(Tokens), CLen),
 1329    content_type(text/html),
 1330    "\r\n".
 1331reply_header(file(Type, File), HdrExtra, Code) -->
 1332    vstatus(ok, Code, HdrExtra),
 1333    date(now),
 1334    modified(file(File)),
 1335    header_fields(HdrExtra, CLen),
 1336    content_length(file(File), CLen),
 1337    content_type(Type),
 1338    "\r\n".
 1339reply_header(gzip_file(Type, File), HdrExtra, Code) -->
 1340    vstatus(ok, Code, HdrExtra),
 1341    date(now),
 1342    modified(file(File)),
 1343    header_fields(HdrExtra, CLen),
 1344    content_length(file(File), CLen),
 1345    content_type(Type),
 1346    content_encoding(gzip),
 1347    "\r\n".
 1348reply_header(file(Type, File, Range), HdrExtra, Code) -->
 1349    vstatus(partial_content, Code, HdrExtra),
 1350    date(now),
 1351    modified(file(File)),
 1352    header_fields(HdrExtra, CLen),
 1353    content_length(file(File, Range), CLen),
 1354    content_type(Type),
 1355    "\r\n".
 1356reply_header(tmp_file(Type, File), HdrExtra, Code) -->
 1357    vstatus(ok, Code, HdrExtra),
 1358    date(now),
 1359    header_fields(HdrExtra, CLen),
 1360    content_length(file(File), CLen),
 1361    content_type(Type),
 1362    "\r\n".
 1363reply_header(cgi_data(Size), HdrExtra, Code) -->
 1364    vstatus(ok, Code, HdrExtra),
 1365    date(now),
 1366    header_fields(HdrExtra, CLen),
 1367    content_length(Size, CLen),
 1368    "\r\n".
 1369reply_header(event_stream, HdrExtra, Code) -->
 1370    vstatus(ok, Code, HdrExtra),
 1371    date(now),
 1372    header_fields(HdrExtra, _),
 1373    "\r\n".
 1374reply_header(chunked_data, HdrExtra, Code) -->
 1375    vstatus(ok, Code, HdrExtra),
 1376    date(now),
 1377    header_fields(HdrExtra, _),
 1378    (   {memberchk(transfer_encoding(_), HdrExtra)}
 1379    ->  ""
 1380    ;   transfer_encoding(chunked)
 1381    ),
 1382    "\r\n".
 1383% non-200 replies without a body (e.g., 1xx, 204, 304)
 1384reply_header(status(Status), HdrExtra, Code) -->
 1385    vstatus(Status, Code),
 1386    header_fields(HdrExtra, Clen),
 1387    { Clen = 0 },
 1388    "\r\n".
 1389% non-200 replies with a body
 1390reply_header(Data, HdrExtra, Code) -->
 1391    { status_reply_headers(Data,
 1392                           body(Type, Encoding, Content),
 1393                           ReplyHeaders),
 1394      http_join_headers(ReplyHeaders, HdrExtra, Headers),
 1395      functor(Data, CodeName, _)
 1396    },
 1397    vstatus(CodeName, Code, Headers),
 1398    date(now),
 1399    header_fields(Headers, CLen),
 1400    content_length(codes(Content, Encoding), CLen),
 1401    content_type(Type, Encoding),
 1402    "\r\n".
 1403
 1404status_reply_headers(created(Location, Body), Body,
 1405                     [ location(Location) ]).
 1406status_reply_headers(moved(To, Body), Body,
 1407                     [ location(To) ]).
 1408status_reply_headers(moved_temporary(To, Body), Body,
 1409                     [ location(To) ]).
 1410status_reply_headers(gone(_URL, Body), Body, []).
 1411status_reply_headers(see_other(To, Body), Body,
 1412                     [ location(To) ]).
 1413status_reply_headers(authorise(Method, Body), Body,
 1414                     [ www_authenticate(Method) ]).
 1415status_reply_headers(not_found(_URL, Body), Body, []).
 1416status_reply_headers(forbidden(_URL, Body), Body, []).
 1417status_reply_headers(method_not_allowed(_Method, _URL, Body), Body, []).
 1418status_reply_headers(server_error(_Error, Body), Body, []).
 1419status_reply_headers(service_unavailable(_Why, Body), Body, []).
 1420status_reply_headers(not_acceptable(_Why, Body), Body, []).
 1421status_reply_headers(bad_request(_Error, Body), Body, []).
 vstatus(+Status, -Code)// is det
 vstatus(+Status, -Code, +HdrExtra)// is det
Emit the HTTP header for Status
 1429vstatus(_Status, Code, HdrExtra) -->
 1430    {memberchk(status(Code), HdrExtra)},
 1431    !,
 1432    vstatus(_NewStatus, Code).
 1433vstatus(Status, Code, _) -->
 1434    vstatus(Status, Code).
 1435
 1436vstatus(Status, Code) -->
 1437    "HTTP/1.1 ",
 1438    status_number(Status, Code),
 1439    " ",
 1440    status_comment(Status),
 1441    "\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.
 1450status_number(Status, Code) -->
 1451    { var(Status) },
 1452    !,
 1453    integer(Code),
 1454    { status_number(Status, Code) },
 1455    !.
 1456status_number(Status, Code) -->
 1457    { status_number(Status, Code) },
 1458    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.
 1472% Unrecognized status codes that are within a defined code class.
 1473% RFC 7231 states:
 1474%   "[...] a client MUST understand the class of any status code,
 1475%    as indicated by the first digit, and treat an unrecognized status code
 1476%    as being equivalent to the `x00` status code of that class [...]
 1477%   "
 1478% @see http://tools.ietf.org/html/rfc7231#section-6
 1479
 1480status_number(Status, Code) :-
 1481    nonvar(Status),
 1482    !,
 1483    status_number_fact(Status, Code).
 1484status_number(Status, Code) :-
 1485    nonvar(Code),
 1486    !,
 1487    (   between(100, 599, Code)
 1488    ->  (   status_number_fact(Status, Code)
 1489        ->  true
 1490        ;   ClassCode is Code // 100 * 100,
 1491            status_number_fact(Status, ClassCode)
 1492        )
 1493    ;   domain_error(http_code, Code)
 1494    ).
 1495
 1496status_number_fact(continue,                   100).
 1497status_number_fact(switching_protocols,        101).
 1498status_number_fact(ok,                         200).
 1499status_number_fact(created,                    201).
 1500status_number_fact(accepted,                   202).
 1501status_number_fact(non_authoritative_info,     203).
 1502status_number_fact(no_content,                 204).
 1503status_number_fact(reset_content,              205).
 1504status_number_fact(partial_content,            206).
 1505status_number_fact(multiple_choices,           300).
 1506status_number_fact(moved,                      301).
 1507status_number_fact(moved_temporary,            302).
 1508status_number_fact(see_other,                  303).
 1509status_number_fact(not_modified,               304).
 1510status_number_fact(use_proxy,                  305).
 1511status_number_fact(unused,                     306).
 1512status_number_fact(temporary_redirect,         307).
 1513status_number_fact(bad_request,                400).
 1514status_number_fact(authorise,                  401).
 1515status_number_fact(payment_required,           402).
 1516status_number_fact(forbidden,                  403).
 1517status_number_fact(not_found,                  404).
 1518status_number_fact(method_not_allowed,         405).
 1519status_number_fact(not_acceptable,             406).
 1520status_number_fact(request_timeout,            408).
 1521status_number_fact(conflict,                   409).
 1522status_number_fact(gone,                       410).
 1523status_number_fact(length_required,            411).
 1524status_number_fact(payload_too_large,          413).
 1525status_number_fact(uri_too_long,               414).
 1526status_number_fact(unsupported_media_type,     415).
 1527status_number_fact(expectation_failed,         417).
 1528status_number_fact(upgrade_required,           426).
 1529status_number_fact(server_error,               500).
 1530status_number_fact(not_implemented,            501).
 1531status_number_fact(bad_gateway,                502).
 1532status_number_fact(service_unavailable,        503).
 1533status_number_fact(gateway_timeout,            504).
 1534status_number_fact(http_version_not_supported, 505).
 status_comment(+Code:atom)// is det
Emit standard HTTP human-readable comment on the reply-status.
 1541status_comment(continue) -->
 1542    "Continue".
 1543status_comment(switching_protocols) -->
 1544    "Switching Protocols".
 1545status_comment(ok) -->
 1546    "OK".
 1547status_comment(created) -->
 1548    "Created".
 1549status_comment(accepted) -->
 1550    "Accepted".
 1551status_comment(non_authoritative_info) -->
 1552    "Non-Authoritative Information".
 1553status_comment(no_content) -->
 1554    "No Content".
 1555status_comment(reset_content) -->
 1556    "Reset Content".
 1557status_comment(created) -->
 1558    "Created".
 1559status_comment(partial_content) -->
 1560    "Partial content".
 1561status_comment(multiple_choices) -->
 1562    "Multiple Choices".
 1563status_comment(moved) -->
 1564    "Moved Permanently".
 1565status_comment(moved_temporary) -->
 1566    "Moved Temporary".
 1567status_comment(see_other) -->
 1568    "See Other".
 1569status_comment(not_modified) -->
 1570    "Not Modified".
 1571status_comment(use_proxy) -->
 1572    "Use Proxy".
 1573status_comment(unused) -->
 1574    "Unused".
 1575status_comment(temporary_redirect) -->
 1576    "Temporary Redirect".
 1577status_comment(bad_request) -->
 1578    "Bad Request".
 1579status_comment(authorise) -->
 1580    "Authorization Required".
 1581status_comment(payment_required) -->
 1582    "Payment Required".
 1583status_comment(forbidden) -->
 1584    "Forbidden".
 1585status_comment(not_found) -->
 1586    "Not Found".
 1587status_comment(method_not_allowed) -->
 1588    "Method Not Allowed".
 1589status_comment(not_acceptable) -->
 1590    "Not Acceptable".
 1591status_comment(request_timeout) -->
 1592    "Request Timeout".
 1593status_comment(conflict) -->
 1594    "Conflict".
 1595status_comment(gone) -->
 1596    "Gone".
 1597status_comment(length_required) -->
 1598    "Length Required".
 1599status_comment(payload_too_large) -->
 1600    "Payload Too Large".
 1601status_comment(uri_too_long) -->
 1602    "URI Too Long".
 1603status_comment(unsupported_media_type) -->
 1604    "Unsupported Media Type".
 1605status_comment(expectation_failed) -->
 1606    "Expectation Failed".
 1607status_comment(upgrade_required) -->
 1608    "Upgrade Required".
 1609status_comment(server_error) -->
 1610    "Internal Server Error".
 1611status_comment(not_implemented) -->
 1612    "Not Implemented".
 1613status_comment(bad_gateway) -->
 1614    "Bad Gateway".
 1615status_comment(service_unavailable) -->
 1616    "Service Unavailable".
 1617status_comment(gateway_timeout) -->
 1618    "Gateway Timeout".
 1619status_comment(http_version_not_supported) -->
 1620    "HTTP Version Not Supported".
 1621
 1622date(Time) -->
 1623    "Date: ",
 1624    (   { Time == now }
 1625    ->  now
 1626    ;   rfc_date(Time)
 1627    ),
 1628    "\r\n".
 1629
 1630modified(file(File)) -->
 1631    !,
 1632    { time_file(File, Time)
 1633    },
 1634    modified(Time).
 1635modified(Time) -->
 1636    "Last-modified: ",
 1637    (   { Time == now }
 1638    ->  now
 1639    ;   rfc_date(Time)
 1640    ),
 1641    "\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
 1651content_length(file(File, bytes(From, To)), Len) -->
 1652    !,
 1653    { size_file(File, Size),
 1654      (   To == end
 1655      ->  Len is Size - From,
 1656          RangeEnd is Size - 1
 1657      ;   Len is To+1 - From,       % To is index of last byte
 1658          RangeEnd = To
 1659      )
 1660    },
 1661    content_range(bytes, From, RangeEnd, Size),
 1662    content_length(Len, Len).
 1663content_length(Reply, Len) -->
 1664    { length_of(Reply, Len)
 1665    },
 1666    "Content-Length: ", integer(Len),
 1667    "\r\n".
 1668
 1669
 1670length_of(_, Len) :-
 1671    nonvar(Len),
 1672    !.
 1673length_of(string(String, Encoding), Len) :-
 1674    length_of(codes(String, Encoding), Len).
 1675length_of(codes(String, Encoding), Len) :-
 1676    !,
 1677    setup_call_cleanup(
 1678        open_null_stream(Out),
 1679        ( set_stream(Out, encoding(Encoding)),
 1680          format(Out, '~s', [String]),
 1681          byte_count(Out, Len)
 1682        ),
 1683        close(Out)).
 1684length_of(atom(Atom, Encoding), Len) :-
 1685    !,
 1686    setup_call_cleanup(
 1687        open_null_stream(Out),
 1688        ( set_stream(Out, encoding(Encoding)),
 1689          format(Out, '~a', [Atom]),
 1690          byte_count(Out, Len)
 1691        ),
 1692        close(Out)).
 1693length_of(file(File), Len) :-
 1694    !,
 1695    size_file(File, Len).
 1696length_of(memory_file(Handle), Len) :-
 1697    !,
 1698    size_memory_file(Handle, Len, octet).
 1699length_of(html_tokens(Tokens), Len) :-
 1700    !,
 1701    html_print_length(Tokens, Len).
 1702length_of(html(Tokens), Len) :-     % deprecated
 1703    !,
 1704    html_print_length(Tokens, Len).
 1705length_of(bytes(Bytes), Len) :-
 1706    !,
 1707    (   string(Bytes)
 1708    ->  string_length(Bytes, Len)
 1709    ;   length(Bytes, Len)          % assuming a list of 0..255
 1710    ).
 1711length_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.
 1719content_range(Unit, From, RangeEnd, Size) -->
 1720    "Content-Range: ", atom(Unit), " ",
 1721    integer(From), "-", integer(RangeEnd), "/", integer(Size),
 1722    "\r\n".
 1723
 1724content_encoding(Encoding) -->
 1725    "Content-Encoding: ", atom(Encoding), "\r\n".
 1726
 1727transfer_encoding(Encoding) -->
 1728    "Transfer-Encoding: ", atom(Encoding), "\r\n".
 1729
 1730content_type(Type) -->
 1731    content_type(Type, _).
 1732
 1733content_type(Type, Charset) -->
 1734    ctype(Type),
 1735    charset(Charset),
 1736    "\r\n".
 1737
 1738ctype(Main/Sub) -->
 1739    !,
 1740    "Content-Type: ",
 1741    atom(Main),
 1742    "/",
 1743    atom(Sub).
 1744ctype(Type) -->
 1745    !,
 1746    "Content-Type: ",
 1747    atom(Type).
 1748
 1749charset(Var) -->
 1750    { var(Var) },
 1751    !.
 1752charset(utf8) -->
 1753    !,
 1754    "; charset=UTF-8".
 1755charset(CharSet) -->
 1756    "; charset=",
 1757    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.
 1765header_field(Name, Value) -->
 1766    { var(Name) },                 % parsing
 1767    !,
 1768    field_name(Name),
 1769    ":",
 1770    whites,
 1771    read_field_value(ValueChars),
 1772    blanks_to_nl,
 1773    !,
 1774    {   field_to_prolog(Name, ValueChars, Value)
 1775    ->  true
 1776    ;   atom_codes(Value, ValueChars),
 1777        domain_error(Name, Value)
 1778    }.
 1779header_field(Name, Value) -->
 1780    field_name(Name),
 1781    ": ",
 1782    field_value(Name, Value),
 1783    "\r\n".
 read_field_value(-Codes)//
Read a field eagerly upto the next whitespace
 1789read_field_value([H|T]) -->
 1790    [H],
 1791    { \+ code_type(H, space) },
 1792    !,
 1793    read_field_value(T).
 1794read_field_value([]) -->
 1795    "".
 1796read_field_value([H|T]) -->
 1797    [H],
 1798    read_field_value(T).
 send_reply_header(+Out, +String) is det
 send_request_header(+Out, +String) is det
Low level routines to send a single HTTP request or reply line.
 1805send_reply_header(Out, String) :-
 1806    debug(http(send_reply), "< ~s", [String]),
 1807    format(Out, '~s', [String]).
 1808
 1809send_request_header(Out, String) :-
 1810    debug(http(send_request), "> ~s", [String]),
 1811    format(Out, '~s', [String]).
 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.
 1851http_parse_header_value(Field, Value, Prolog) :-
 1852    known_field(Field, _, Type),
 1853    (   already_parsed(Type, Value)
 1854    ->  Prolog = Value
 1855    ;   to_codes(Value, Codes),
 1856        parse_header_value(Field, Codes, Prolog)
 1857    ).
 1858
 1859already_parsed(integer, V)    :- !, integer(V).
 1860already_parsed(list(Type), L) :- !, is_list(L), maplist(already_parsed(Type), L).
 1861already_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.
 1869known_field(content_length,      true,  integer).
 1870known_field(status,              true,  integer).
 1871known_field(cookie,              true,  list(_=_)).
 1872known_field(set_cookie,          true,  list(set_cookie(_Name,_Value,_Options))).
 1873known_field(host,                true,  _Host:_Port).
 1874known_field(range,               maybe, bytes(_,_)).
 1875known_field(accept,              maybe, list(media(_Type, _Parms, _Q, _Exts))).
 1876known_field(content_disposition, maybe, disposition(_Name, _Attributes)).
 1877known_field(content_type,        false, media(_Type/_Sub, _Attributes)).
 1878
 1879to_codes(In, Codes) :-
 1880    (   is_list(In)
 1881    ->  Codes = In
 1882    ;   atom_codes(In, Codes)
 1883    ).
 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.
 1891field_to_prolog(Field, Codes, Prolog) :-
 1892    known_field(Field, true, _Type),
 1893    !,
 1894    (   parse_header_value(Field, Codes, Prolog0)
 1895    ->  Prolog = Prolog0
 1896    ).
 1897field_to_prolog(Field, Codes, Prolog) :-
 1898    known_field(Field, maybe, _Type),
 1899    parse_header_value(Field, Codes, Prolog0),
 1900    !,
 1901    Prolog = Prolog0.
 1902field_to_prolog(_, Codes, Atom) :-
 1903    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.
 1910parse_header_value(content_length, ValueChars, ContentLength) :-
 1911    number_codes(ContentLength, ValueChars).
 1912parse_header_value(status, ValueChars, Code) :-
 1913    (   phrase(" ", L, _),
 1914        append(Pre, L, ValueChars)
 1915    ->  number_codes(Code, Pre)
 1916    ;   number_codes(Code, ValueChars)
 1917    ).
 1918parse_header_value(cookie, ValueChars, Cookies) :-
 1919    debug(cookie, 'Cookie: ~s', [ValueChars]),
 1920    phrase(cookies(Cookies), ValueChars).
 1921parse_header_value(set_cookie, ValueChars, SetCookie) :-
 1922    debug(cookie, 'SetCookie: ~s', [ValueChars]),
 1923    phrase(set_cookie(SetCookie), ValueChars).
 1924parse_header_value(host, ValueChars, Host) :-
 1925    (   append(HostChars, [0':|PortChars], ValueChars),
 1926        catch(number_codes(Port, PortChars), _, fail)
 1927    ->  atom_codes(HostName, HostChars),
 1928        Host = HostName:Port
 1929    ;   atom_codes(Host, ValueChars)
 1930    ).
 1931parse_header_value(range, ValueChars, Range) :-
 1932    phrase(range(Range), ValueChars).
 1933parse_header_value(accept, ValueChars, Media) :-
 1934    parse_accept(ValueChars, Media).
 1935parse_header_value(content_disposition, ValueChars, Disposition) :-
 1936    phrase(content_disposition(Disposition), ValueChars).
 1937parse_header_value(content_type, ValueChars, Type) :-
 1938    phrase(parse_content_type(Type), ValueChars).
 field_value(+Name, +Value)//
 1942field_value(_, set_cookie(Name, Value, Options)) -->
 1943    !,
 1944    atom(Name), "=", atom(Value),
 1945    value_options(Options, cookie).
 1946field_value(_, disposition(Disposition, Options)) -->
 1947    !,
 1948    atom(Disposition), value_options(Options, disposition).
 1949field_value(www_authenticate, Auth) -->
 1950    auth_field_value(Auth).
 1951field_value(_, Atomic) -->
 1952    atom(Atomic).
 auth_field_value(+AuthValue)//
Emit the authentication requirements (WWW-Authenticate field).
 1958auth_field_value(negotiate(Data)) -->
 1959    "Negotiate ",
 1960    { base64(Data, DataBase64),
 1961      atom_codes(DataBase64, Codes)
 1962    },
 1963    string(Codes).
 1964auth_field_value(negotiate) -->
 1965    "Negotiate".
 1966auth_field_value(basic) -->
 1967    !,
 1968    "Basic".
 1969auth_field_value(basic(Realm)) -->
 1970    "Basic Realm=\"", atom(Realm), "\"".
 1971auth_field_value(digest) -->
 1972    !,
 1973    "Digest".
 1974auth_field_value(digest(Details)) -->
 1975    "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.
 1984value_options([], _) --> [].
 1985value_options([H|T], Field) -->
 1986    "; ", value_option(H, Field),
 1987    value_options(T, Field).
 1988
 1989value_option(secure=true, cookie) -->
 1990    !,
 1991    "secure".
 1992value_option(Name=Value, Type) -->
 1993    { string_option(Name, Type) },
 1994    !,
 1995    atom(Name), "=",
 1996    qstring(Value).
 1997value_option(Name=Value, Type) -->
 1998    { token_option(Name, Type) },
 1999    !,
 2000    atom(Name), "=", atom(Value).
 2001value_option(Name=Value, _Type) -->
 2002    atom(Name), "=",
 2003    option_value(Value).
 2004
 2005string_option(filename, disposition).
 2006
 2007token_option(path, cookie).
 2008
 2009option_value(Value) -->
 2010    { number(Value) },
 2011    !,
 2012    number(Value).
 2013option_value(Value) -->
 2014    { (   atom(Value)
 2015      ->  true
 2016      ;   string(Value)
 2017      ),
 2018      forall(string_code(_, Value, C),
 2019             token_char(C))
 2020    },
 2021    !,
 2022    atom(Value).
 2023option_value(Atomic) -->
 2024    qstring(Atomic).
 2025
 2026qstring(Atomic) -->
 2027    { string_codes(Atomic, Codes) },
 2028    "\"",
 2029    qstring_codes(Codes),
 2030    "\"".
 2031
 2032qstring_codes([]) --> [].
 2033qstring_codes([H|T]) --> qstring_code(H), qstring_codes(T).
 2034
 2035qstring_code(C) --> {qstring_esc(C)}, !, "\\", [C].
 2036qstring_code(C) --> [C].
 2037
 2038qstring_esc(0'").
 2039qstring_esc(C) :- ctl(C).
 2040
 2041
 2042                 /*******************************
 2043                 *        ACCEPT HEADERS        *
 2044                 *******************************/
 2045
 2046:- dynamic accept_cache/2. 2047:- volatile accept_cache/2. 2048
 2049parse_accept(Codes, Media) :-
 2050    atom_codes(Atom, Codes),
 2051    (   accept_cache(Atom, Media0)
 2052    ->  Media = Media0
 2053    ;   phrase(accept(Media0), Codes),
 2054        keysort(Media0, Media1),
 2055        pairs_values(Media1, Media2),
 2056        assertz(accept_cache(Atom, Media2)),
 2057        Media = Media2
 2058    ).
 accept(-Media)// is semidet
Parse an HTTP Accept: header
 2064accept([H|T]) -->
 2065    blanks,
 2066    media_range(H),
 2067    blanks,
 2068    (   ","
 2069    ->  accept(T)
 2070    ;   {T=[]}
 2071    ).
 2072
 2073media_range(s(SortQuality,Spec)-media(Type, TypeParams, Quality, AcceptExts)) -->
 2074    media_type(Type),
 2075    blanks,
 2076    (   ";"
 2077    ->  blanks,
 2078        parameters_and_quality(TypeParams, Quality, AcceptExts)
 2079    ;   { TypeParams = [],
 2080          Quality = 1.0,
 2081          AcceptExts = []
 2082        }
 2083    ),
 2084    { SortQuality is float(-Quality),
 2085      rank_specialised(Type, TypeParams, Spec)
 2086    }.
 content_disposition(-Disposition)//
Parse Content-Disposition value
 2093content_disposition(disposition(Disposition, Options)) -->
 2094    token(Disposition), blanks,
 2095    value_parameters(Options).
 parse_content_type(-Type)//
Parse Content-Type value into a term media(Type/SubType, Parameters).
 2102parse_content_type(media(Type, Parameters)) -->
 2103    media_type(Type), blanks,
 2104    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?
 2115rank_specialised(Type/SubType, TypeParams, v(VT, VS, SortVP)) :-
 2116    var_or_given(Type, VT),
 2117    var_or_given(SubType, VS),
 2118    length(TypeParams, VP),
 2119    SortVP is -VP.
 2120
 2121var_or_given(V, Val) :-
 2122    (   var(V)
 2123    ->  Val = 0
 2124    ;   Val = -1
 2125    ).
 2126
 2127media_type(Type/SubType) -->
 2128    type(Type), "/", type(SubType).
 2129
 2130type(_) -->
 2131    "*",
 2132    !.
 2133type(Type) -->
 2134    token(Type).
 2135
 2136parameters_and_quality(Params, Quality, AcceptExts) -->
 2137    token(Name),
 2138    blanks, "=", blanks,
 2139    (   { Name == q }
 2140    ->  float(Quality), blanks,
 2141        value_parameters(AcceptExts),
 2142        { Params = [] }
 2143    ;   { Params = [Name=Value|T] },
 2144        parameter_value(Value),
 2145        blanks,
 2146        (   ";"
 2147        ->  blanks,
 2148            parameters_and_quality(T, Quality, AcceptExts)
 2149        ;   { T = [],
 2150              Quality = 1.0,
 2151              AcceptExts = []
 2152            }
 2153        )
 2154    ).
 value_parameters(-Params:list) is det
Accept (";" <parameter>)*, returning a list of Name=Value, where both Name and Value are atoms.
 2161value_parameters([H|T]) -->
 2162    ";",
 2163    !,
 2164    blanks, token(Name), blanks,
 2165    (   "="
 2166    ->  blanks,
 2167        (   token(Value)
 2168        ->  []
 2169        ;   quoted_string(Value)
 2170        ),
 2171        { H = (Name=Value) }
 2172    ;   { H = Name }
 2173    ),
 2174    blanks,
 2175    value_parameters(T).
 2176value_parameters([]) -->
 2177    [].
 2178
 2179parameter_value(Value) --> token(Value), !.
 2180parameter_value(Value) --> quoted_string(Value).
 token(-Name)// is semidet
Process an HTTP header token from the input.
 2187token(Name) -->
 2188    token_char(C1),
 2189    token_chars(Cs),
 2190    { atom_codes(Name, [C1|Cs]) }.
 2191
 2192token_chars([H|T]) -->
 2193    token_char(H),
 2194    !,
 2195    token_chars(T).
 2196token_chars([]) --> [].
 2197
 2198token_char(C) :-
 2199    \+ ctl(C),
 2200    \+ separator_code(C).
 2201
 2202ctl(C) :- between(0,31,C), !.
 2203ctl(127).
 2204
 2205separator_code(0'().
 2206separator_code(0')).
 2207separator_code(0'<).
 2208separator_code(0'>).
 2209separator_code(0'@).
 2210separator_code(0',).
 2211separator_code(0';).
 2212separator_code(0':).
 2213separator_code(0'\\).
 2214separator_code(0'").
 2215separator_code(0'/).
 2216separator_code(0'[).
 2217separator_code(0']).
 2218separator_code(0'?).
 2219separator_code(0'=).
 2220separator_code(0'{).
 2221separator_code(0'}).
 2222separator_code(0'\s).
 2223separator_code(0'\t).
 2224
 2225term_expansion(token_char(x) --> [x], Clauses) :-
 2226    findall((token_char(C)-->[C]),
 2227            (   between(0, 255, C),
 2228                token_char(C)
 2229            ),
 2230            Clauses).
 2231
 2232token_char(x) --> [x].
 quoted_string(-Text)// is semidet
True if input starts with a quoted string representing Text.
 2238quoted_string(Text) -->
 2239    "\"",
 2240    quoted_text(Codes),
 2241    { atom_codes(Text, Codes) }.
 2242
 2243quoted_text([]) -->
 2244    "\"",
 2245    !.
 2246quoted_text([H|T]) -->
 2247    "\\", !, [H],
 2248    quoted_text(T).
 2249quoted_text([H|T]) -->
 2250    [H],
 2251    !,
 2252    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.
 2263header_fields([], _) --> [].
 2264header_fields([content_length(CLen)|T], CLen) -->
 2265    !,
 2266    (   { var(CLen) }
 2267    ->  ""
 2268    ;   header_field(content_length, CLen)
 2269    ),
 2270    header_fields(T, CLen).           % Continue or return first only?
 2271header_fields([status(_)|T], CLen) -->   % handled by vstatus//3.
 2272    !,
 2273    header_fields(T, CLen).
 2274header_fields([H|T], CLen) -->
 2275    { H =.. [Name, Value] },
 2276    header_field(Name, Value),
 2277    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
 2294:- public
 2295    field_name//1. 2296
 2297field_name(Name) -->
 2298    { var(Name) },
 2299    !,
 2300    rd_field_chars(Chars),
 2301    { atom_codes(Name, Chars) }.
 2302field_name(mime_version) -->
 2303    !,
 2304    "MIME-Version".
 2305field_name(www_authenticate) -->
 2306    !,
 2307    "WWW-Authenticate".
 2308field_name(Name) -->
 2309    { atom_codes(Name, Chars) },
 2310    wr_field_chars(Chars).
 2311
 2312rd_field_chars_no_fold([C|T]) -->
 2313    [C],
 2314    { rd_field_char(C, _) },
 2315    !,
 2316    rd_field_chars_no_fold(T).
 2317rd_field_chars_no_fold([]) -->
 2318    [].
 2319
 2320rd_field_chars([C0|T]) -->
 2321    [C],
 2322    { rd_field_char(C, C0) },
 2323    !,
 2324    rd_field_chars(T).
 2325rd_field_chars([]) -->
 2326    [].
 separators(-CharCodes) is det
CharCodes is a list of separators according to RFC2616
 2332separators("()<>@,;:\\\"/[]?={} \t").
 2333
 2334term_expansion(rd_field_char('expand me',_), Clauses) :-
 2335
 2336    Clauses = [ rd_field_char(0'-, 0'_)
 2337              | Cls
 2338              ],
 2339    separators(SepString),
 2340    string_codes(SepString, Seps),
 2341    findall(rd_field_char(In, Out),
 2342            (   between(32, 127, In),
 2343                \+ memberchk(In, Seps),
 2344                In \== 0'-,         % 0'
 2345                code_type(Out, to_lower(In))),
 2346            Cls).
 2347
 2348rd_field_char('expand me', _).                  % avoid recursion
 2349
 2350wr_field_chars([C|T]) -->
 2351    !,
 2352    { code_type(C, to_lower(U)) },
 2353    [U],
 2354    wr_field_chars2(T).
 2355wr_field_chars([]) -->
 2356    [].
 2357
 2358wr_field_chars2([]) --> [].
 2359wr_field_chars2([C|T]) -->              % 0'
 2360    (   { C == 0'_ }
 2361    ->  "-",
 2362        wr_field_chars(T)
 2363    ;   [C],
 2364        wr_field_chars2(T)
 2365    ).
 now//
Current time using rfc_date//1.
 2371now -->
 2372    { get_time(Time)
 2373    },
 2374    rfc_date(Time).
 rfc_date(+Time)// is det
Write time according to RFC1123 specification as required by the RFC2616 HTTP protocol specs.
 2381rfc_date(Time, String, Tail) :-
 2382    stamp_date_time(Time, Date, 'UTC'),
 2383    format_time(codes(String, Tail),
 2384                '%a, %d %b %Y %T GMT',
 2385                Date, posix).
 http_timestamp(+Time:timestamp, -Text:atom) is det
Generate a description of a Time in HTTP format (RFC1123)
 2391http_timestamp(Time, Atom) :-
 2392    stamp_date_time(Time, Date, 'UTC'),
 2393    format_time(atom(Atom),
 2394                '%a, %d %b %Y %T GMT',
 2395                Date, posix).
 2396
 2397
 2398                 /*******************************
 2399                 *         REQUEST DCG          *
 2400                 *******************************/
 2401
 2402request(Fd, [method(Method),request_uri(ReqURI)|Header]) -->
 2403    method(Method),
 2404    blanks,
 2405    nonblanks(Query),
 2406    { atom_codes(ReqURI, Query),
 2407      request_uri_parts(ReqURI, Header, Rest)
 2408    },
 2409    request_header(Fd, Rest),
 2410    !.
 2411request(Fd, [unknown(What)|Header]) -->
 2412    string(What),
 2413    eos,
 2414    !,
 2415    {   http_read_header(Fd, Header)
 2416    ->  true
 2417    ;   Header = []
 2418    }.
 2419
 2420method(get)     --> "GET", !.
 2421method(put)     --> "PUT", !.
 2422method(head)    --> "HEAD", !.
 2423method(post)    --> "POST", !.
 2424method(delete)  --> "DELETE", !.
 2425method(patch)   --> "PATCH", !.
 2426method(options) --> "OPTIONS", !.
 2427method(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.
 2441request_uri_parts(ReqURI, [path(Path)|Parts], Rest) :-
 2442    uri_components(ReqURI, Components),
 2443    uri_data(path, Components, PathText),
 2444    uri_encoded(path, Path, PathText),
 2445    phrase(uri_parts(Components), Parts, Rest).
 2446
 2447uri_parts(Components) -->
 2448    uri_search(Components),
 2449    uri_fragment(Components).
 2450
 2451uri_search(Components) -->
 2452    { uri_data(search, Components, Search),
 2453      nonvar(Search),
 2454      catch(uri_query_components(Search, Query),
 2455            error(syntax_error(_),_),
 2456            fail)
 2457    },
 2458    !,
 2459    [ search(Query) ].
 2460uri_search(_) --> [].
 2461
 2462uri_fragment(Components) -->
 2463    { uri_data(fragment, Components, String),
 2464      nonvar(String),
 2465      !,
 2466      uri_encoded(fragment, Fragment, String)
 2467    },
 2468    [ fragment(Fragment) ].
 2469uri_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.
 2476request_header(_, []) -->               % Old-style non-version header
 2477    blanks,
 2478    eos,
 2479    !.
 2480request_header(Fd, [http_version(Version)|Header]) -->
 2481    http_version(Version),
 2482    blanks,
 2483    eos,
 2484    !,
 2485    {   Version = 1-_
 2486    ->  http_read_header(Fd, Header)
 2487    ;   Header = []
 2488    }.
 2489
 2490http_version(Version) -->
 2491    blanks,
 2492    "HTTP/",
 2493    http_version_number(Version).
 2494
 2495http_version_number(Major-Minor) -->
 2496    integer(Major),
 2497    ".",
 2498    integer(Minor).
 2499
 2500
 2501                 /*******************************
 2502                 *            COOKIES           *
 2503                 *******************************/
 cookies(-List)// is semidet
Translate a cookie description into a list Name=Value.
 2509cookies([Name=Value|T]) -->
 2510    blanks,
 2511    cookie(Name, Value),
 2512    !,
 2513    blanks,
 2514    (   ";"
 2515    ->  cookies(T)
 2516    ;   { T = [] }
 2517    ).
 2518cookies(List) -->
 2519    string(Skipped),
 2520    ";",
 2521    !,
 2522    { print_message(warning, http(skipped_cookie(Skipped))) },
 2523    cookies(List).
 2524cookies([]) -->
 2525    blanks.
 2526
 2527cookie(Name, Value) -->
 2528    cookie_name(Name),
 2529    blanks, "=", blanks,
 2530    cookie_value(Value).
 2531
 2532cookie_name(Name) -->
 2533    { var(Name) },
 2534    !,
 2535    rd_field_chars_no_fold(Chars),
 2536    { atom_codes(Name, Chars) }.
 2537
 2538cookie_value(Value) -->
 2539    quoted_string(Value),
 2540    !.
 2541cookie_value(Value) -->
 2542    chars_to_semicolon_or_blank(Chars),
 2543    { atom_codes(Value, Chars)
 2544    }.
 2545
 2546chars_to_semicolon_or_blank([]), ";" -->
 2547    ";",
 2548    !.
 2549chars_to_semicolon_or_blank([]) -->
 2550    " ",
 2551    blanks,
 2552    eos,
 2553    !.
 2554chars_to_semicolon_or_blank([H|T]) -->
 2555    [H],
 2556    !,
 2557    chars_to_semicolon_or_blank(T).
 2558chars_to_semicolon_or_blank([]) -->
 2559    [].
 2560
 2561set_cookie(set_cookie(Name, Value, Options)) -->
 2562    ws,
 2563    cookie(Name, Value),
 2564    cookie_options(Options).
 2565
 2566cookie_options([H|T]) -->
 2567    ws,
 2568    ";",
 2569    ws,
 2570    cookie_option(H),
 2571    !,
 2572    cookie_options(T).
 2573cookie_options([]) -->
 2574    ws.
 2575
 2576ws --> " ", !, ws.
 2577ws --> [].
 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.
 2589cookie_option(Name=Value) -->
 2590    rd_field_chars(NameChars), ws,
 2591    { atom_codes(Name, NameChars) },
 2592    (   "="
 2593    ->  ws,
 2594        chars_to_semicolon(ValueChars),
 2595        { atom_codes(Value, ValueChars)
 2596        }
 2597    ;   { Value = true }
 2598    ).
 2599
 2600chars_to_semicolon([H|T]) -->
 2601    [H],
 2602    { H \== 32, H \== 0'; },
 2603    !,
 2604    chars_to_semicolon(T).
 2605chars_to_semicolon([]), ";" -->
 2606    ws, ";",
 2607    !.
 2608chars_to_semicolon([H|T]) -->
 2609    [H],
 2610    chars_to_semicolon(T).
 2611chars_to_semicolon([]) -->
 2612    [].
 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.
 2622range(bytes(From, To)) -->
 2623    "bytes", whites, "=", whites, integer(From), "-",
 2624    (   integer(To)
 2625    ->  ""
 2626    ;   { To = end }
 2627    ).
 2628
 2629
 2630                 /*******************************
 2631                 *           REPLY DCG          *
 2632                 *******************************/
 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.
 2649reply(Fd, [http_version(HttpVersion), status(Code, Status, Comment)|Header]) -->
 2650    http_version(HttpVersion),
 2651    blanks,
 2652    (   status_number(Status, Code)
 2653    ->  []
 2654    ;   integer(Status)
 2655    ),
 2656    blanks,
 2657    string(CommentCodes),
 2658    blanks_to_nl,
 2659    !,
 2660    blanks,
 2661    { atom_codes(Comment, CommentCodes),
 2662      http_read_header(Fd, Header)
 2663    }.
 2664
 2665
 2666                 /*******************************
 2667                 *            READ HEADER       *
 2668                 *******************************/
 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)
 2676http_read_header(Fd, Header) :-
 2677    read_header_data(Fd, Text),
 2678    http_parse_header(Text, Header).
 2679
 2680read_header_data(Fd, Header) :-
 2681    read_line_to_codes(Fd, Header, Tail),
 2682    read_header_data(Header, Fd, Tail),
 2683    debug(http(header), 'Header = ~n~s~n', [Header]).
 2684
 2685read_header_data([0'\r,0'\n], _, _) :- !.
 2686read_header_data([0'\n], _, _) :- !.
 2687read_header_data([], _, _) :- !.
 2688read_header_data(_, Fd, Tail) :-
 2689    read_line_to_codes(Fd, Tail, NewTail),
 2690    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)
 2699http_parse_header(Text, Header) :-
 2700    phrase(header(Header), Text),
 2701    debug(http(header), 'Field: ~p', [Header]).
 2702
 2703header(List) -->
 2704    header_field(Name, Value),
 2705    !,
 2706    { mkfield(Name, Value, List, Tail)
 2707    },
 2708    blanks,
 2709    header(Tail).
 2710header([]) -->
 2711    blanks,
 2712    eos,
 2713    !.
 2714header(_) -->
 2715    string(S), blanks_to_nl,
 2716    !,
 2717    { string_codes(Line, S),
 2718      syntax_error(http_parameter(Line))
 2719    }.
 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.

 2733:- multifile
 2734    http:http_address//0. 2735
 2736address -->
 2737    http:http_address,
 2738    !.
 2739address -->
 2740    { gethostname(Host) },
 2741    html(address([ a(href('http://www.swi-prolog.org'), 'SWI-Prolog'),
 2742                   ' httpd at ', Host
 2743                 ])).
 2744
 2745mkfield(host, Host:Port, [host(Host),port(Port)|Tail], Tail) :- !.
 2746mkfield(Name, Value, [Att|Tail], Tail) :-
 2747    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.
 2786                 /*******************************
 2787                 *            MESSAGES          *
 2788                 *******************************/
 2789
 2790:- multifile
 2791    prolog:message//1,
 2792    prolog:error_message//1. 2793
 2794prolog:error_message(http_write_short(Data, Sent)) -->
 2795    data(Data),
 2796    [ ': remote hangup after ~D bytes'-[Sent] ].
 2797prolog:error_message(syntax_error(http_request(Request))) -->
 2798    [ 'Illegal HTTP request: ~s'-[Request] ].
 2799prolog:error_message(syntax_error(http_parameter(Line))) -->
 2800    [ 'Illegal HTTP parameter: ~s'-[Line] ].
 2801
 2802prolog:message(http(skipped_cookie(S))) -->
 2803    [ 'Skipped illegal cookie: ~s'-[S] ].
 2804
 2805data(bytes(MimeType, _Bytes)) -->
 2806    !,
 2807    [ 'bytes(~p, ...)'-[MimeType] ].
 2808data(Data) -->
 2809    [ '~p'-[Data] ]