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-2023, University of Amsterdam 7 VU University Amsterdam 8 CWI, Amsterdam 9 SWI-Prolog Solutions b.v. 10 All rights reserved. 11 12 Redistribution and use in source and binary forms, with or without 13 modification, are permitted provided that the following conditions 14 are met: 15 16 1. Redistributions of source code must retain the above copyright 17 notice, this list of conditions and the following disclaimer. 18 19 2. Redistributions in binary form must reproduce the above copyright 20 notice, this list of conditions and the following disclaimer in 21 the documentation and/or other materials provided with the 22 distribution. 23 24 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 25 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 26 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 27 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 28 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 29 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 30 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 31 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 32 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 33 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 34 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 35 POSSIBILITY OF SUCH DAMAGE. 36*/ 37 38:- module(http_open, 39 [ http_open/3, % +URL, -Stream, +Options 40 http_set_authorization/2, % +URL, +Authorization 41 http_close_keep_alive/1 % +Address 42 ]). 43:- autoload(library(aggregate),[aggregate_all/3]). 44:- autoload(library(apply),[foldl/4,include/3]). 45:- autoload(library(base64),[base64/3]). 46:- autoload(library(debug),[debug/3,debugging/1]). 47:- autoload(library(error), 48 [ domain_error/2, must_be/2, existence_error/2, instantiation_error/1 49 ]). 50:- autoload(library(lists),[last/2,member/2]). 51:- autoload(library(option), 52 [ meta_options/3, option/2, select_option/4, merge_options/3, 53 option/3, select_option/3 54 ]). 55:- autoload(library(readutil),[read_line_to_codes/2]). 56:- autoload(library(uri), 57 [ uri_resolve/3, uri_components/2, uri_data/3, 58 uri_authority_components/2, uri_authority_data/3, 59 uri_encoded/3, uri_query_components/2, uri_is_global/1 60 ]). 61:- autoload(library(http/http_header), 62 [ http_parse_header/2, http_post_data/3 ]). 63:- autoload(library(http/http_stream),[stream_range_open/3]). 64:- if(exists_source(library(ssl))). 65:- autoload(library(ssl), [ssl_upgrade_legacy_options/2]). 66:- endif. 67:- use_module(library(socket)).
174:- multifile 175 http:encoding_filter/3, % +Encoding, +In0, -In 176 http:current_transfer_encoding/1, % ?Encoding 177 http:disable_encoding_filter/1, % +ContentType 178 http:http_protocol_hook/5, % +Protocol, +Parts, +StreamPair, 179 % -NewStreamPair, +Options 180 http:open_options/2, % +Parts, -Options 181 http:write_cookies/3, % +Out, +Parts, +Options 182 http:update_cookies/3, % +CookieLine, +Parts, +Options 183 http:authenticate_client/2, % +URL, +Action 184 http:http_connection_over_proxy/6. 185 186:- meta_predicate 187 http_open( , , ). 188 189:- predicate_options(http_open/3, 3, 190 [ authorization(compound), 191 final_url(-atom), 192 header(+atom, -atom), 193 headers(-list), 194 raw_headers(-list(string)), 195 connection(+atom), 196 method(oneof([delete,get,put,head,post,patch,options])), 197 size(-integer), 198 status_code(-integer), 199 output(-stream), 200 timeout(number), 201 unix_socket(+atom), 202 proxy(atom, integer), 203 proxy_authorization(compound), 204 bypass_proxy(boolean), 205 request_header(any), 206 user_agent(atom), 207 version(-compound), 208 % The option below applies if library(http/http_header) is loaded 209 post(any), 210 % The options below apply if library(http/http_ssl_plugin)) is loaded 211 pem_password_hook(callable), 212 cacert_file(atom), 213 cert_verify_hook(callable) 214 ]).
User-Agent
, can be overruled using the
option user_agent(Agent)
of http_open/3.
221user_agent('SWI-Prolog').
false
(default true
), do not try to automatically
authenticate the client if a 401 (Unauthorized) status code
is received.curl(1)
's option
`--unix-socket`.Connection
header. Default is close
. The
alternative is Keep-alive
. This maintains a pool of
available connections as determined by keep_connection/1.
The library(http/websockets)
uses Keep-alive, Upgrade
.
Keep-alive connections can be closed explicitly using
http_close_keep_alive/1. Keep-alive connections may
significantly improve repetitive requests on the same server,
especially if the IP route is long, HTTPS is used or the
connection uses a proxy.header(Name,Value)
option. A pseudo header status_code(Code)
is added to provide
the HTTP status as an integer. See also raw_headers(-List)
which provides the entire HTTP reply header in unparsed
representation.get
(default), head
, delete
, post
, put
or
patch
.
The head
message can be
used in combination with the header(Name, Value)
option to
access information on the resource without actually fetching
the resource itself. The returned stream must be closed
immediately.
If post(Data)
is provided, the default is post
.
Content-Length
in the reply header.Major-Minor
, where Major and Minor
are integers representing the HTTP version in the reply header.end
. HTTP 1.1 only supports Unit = bytes
. E.g.,
to ask for bytes 1000-1999, use the option
range(bytes(1000,1999))
raw_encoding('applocation/gzip')
the system will not
decompress the stream if it is compressed using gzip
.headers(-List)
.false
(default true
), do not automatically redirect
if a 3XX code is received. Must be combined with
status_code(Code)
and one of the header options to read the
redirect reply. In particular, without status_code(Code)
a
redirect is mapped to an exception.infinite
).POST
request on the HTTP server. Data is
handed to http_post_data/3.proxy(+Host:Port)
. Deprecated.authorization
option.true
, bypass proxy hooks. Default is false
.infinite
.
The default value is 10
.User-Agent
field of the HTTP
header. Default is SWI-Prolog
.
The hook http:open_options/2 can be used to provide default
options based on the broken-down URL. The option
status_code(-Code)
is particularly useful to query REST
interfaces that commonly return status codes other than 200
that need to be be processed by the client code.
423:- multifile 424 socket:proxy_for_url/3. % +URL, +Host, -ProxyList 425 426http_open(URL, Stream, QOptions) :- 427 meta_options(is_meta, QOptions, Options0), 428 ( atomic(URL) 429 -> parse_url_ex(URL, Parts) 430 ; Parts = URL 431 ), 432 autoload_https(Parts), 433 upgrade_ssl_options(Parts, Options0, Options), 434 add_authorization(Parts, Options, Options1), 435 findall(HostOptions, hooked_options(Parts, HostOptions), AllHostOptions), 436 foldl(merge_options_rev, AllHostOptions, Options1, Options2), 437 ( option(bypass_proxy(true), Options) 438 -> try_http_proxy(direct, Parts, Stream, Options2) 439 ; term_variables(Options2, Vars2), 440 findall(Result-Vars2, 441 try_a_proxy(Parts, Result, Options2), 442 ResultList), 443 last(ResultList, Status-Vars2) 444 -> ( Status = true(_Proxy, Stream) 445 -> true 446 ; throw(error(proxy_error(tried(ResultList)), _)) 447 ) 448 ; try_http_proxy(direct, Parts, Stream, Options2) 449 ). 450 451try_a_proxy(Parts, Result, Options) :- 452 parts_uri(Parts, AtomicURL), 453 option(host(Host), Parts), 454 ( option(unix_socket(Path), Options) 455 -> Proxy = unix_socket(Path) 456 ; ( option(proxy(ProxyHost:ProxyPort), Options) 457 ; is_list(Options), 458 memberchk(proxy(ProxyHost,ProxyPort), Options) 459 ) 460 -> Proxy = proxy(ProxyHost, ProxyPort) 461 ; socket:proxy_for_url(AtomicURL, Host, Proxy) 462 ), 463 debug(http(proxy), 464 'http_open: Connecting via ~w to ~w', [Proxy, AtomicURL]), 465 ( catch(try_http_proxy(Proxy, Parts, Stream, Options), E, true) 466 -> ( var(E) 467 -> !, Result = true(Proxy, Stream) 468 ; Result = error(Proxy, E) 469 ) 470 ; Result = false(Proxy) 471 ), 472 debug(http(proxy), 'http_open: ~w: ~p', [Proxy, Result]). 473 474try_http_proxy(Method, Parts, Stream, Options0) :- 475 option(host(Host), Parts), 476 proxy_request_uri(Method, Parts, RequestURI), 477 select_option(visited(Visited0), Options0, OptionsV, []), 478 Options = [visited([Parts|Visited0])|OptionsV], 479 parts_scheme(Parts, Scheme), 480 default_port(Scheme, DefPort), 481 url_part(port(Port), Parts, DefPort), 482 host_and_port(Host, DefPort, Port, HostPort), 483 ( option(connection(Connection), Options0), 484 keep_alive(Connection), 485 get_from_pool(Host:Port, StreamPair), 486 debug(http(connection), 'Trying Keep-alive to ~p using ~p', 487 [ Host:Port, StreamPair ]), 488 catch(send_rec_header(StreamPair, Stream, HostPort, 489 RequestURI, Parts, Options), 490 Error, 491 keep_alive_error(Error, StreamPair)) 492 -> true 493 ; http:http_connection_over_proxy(Method, Parts, Host:Port, 494 SocketStreamPair, Options, Options1), 495 ( catch(http:http_protocol_hook(Scheme, Parts, 496 SocketStreamPair, 497 StreamPair, Options), 498 Error, 499 ( close(SocketStreamPair, [force(true)]), 500 throw(Error))) 501 -> true 502 ; StreamPair = SocketStreamPair 503 ), 504 send_rec_header(StreamPair, Stream, HostPort, 505 RequestURI, Parts, Options1) 506 ), 507 return_final_url(Options). 508 509proxy_request_uri(direct, Parts, RequestURI) :- 510 !, 511 parts_request_uri(Parts, RequestURI). 512proxy_request_uri(unix_socket(_), Parts, RequestURI) :- 513 !, 514 parts_request_uri(Parts, RequestURI). 515proxy_request_uri(_, Parts, RequestURI) :- 516 parts_uri(Parts, RequestURI). 517 518httphttp_connection_over_proxy(unix_socket(Path), _, _, 519 StreamPair, Options, Options) :- 520 !, 521 unix_domain_socket(Socket), 522 tcp_connect(Socket, Path), 523 tcp_open_socket(Socket, In, Out), 524 stream_pair(StreamPair, In, Out). 525httphttp_connection_over_proxy(direct, _, Host:Port, 526 StreamPair, Options, Options) :- 527 !, 528 open_socket(Host:Port, StreamPair, Options). 529httphttp_connection_over_proxy(proxy(ProxyHost, ProxyPort), Parts, _, 530 StreamPair, Options, Options) :- 531 \+ ( memberchk(scheme(Scheme), Parts), 532 secure_scheme(Scheme) 533 ), 534 !, 535 % We do not want any /more/ proxy after this 536 open_socket(ProxyHost:ProxyPort, StreamPair, 537 [bypass_proxy(true)|Options]). 538httphttp_connection_over_proxy(socks(SocksHost, SocksPort), _Parts, Host:Port, 539 StreamPair, Options, Options) :- 540 !, 541 tcp_connect(SocksHost:SocksPort, StreamPair, [bypass_proxy(true)]), 542 catch(negotiate_socks_connection(Host:Port, StreamPair), 543 Error, 544 ( close(StreamPair, [force(true)]), 545 throw(Error) 546 )).
cacerts_file(File)
option to a cacerts(List)
option to ensure proper
merging of options.554hooked_options(Parts, Options) :- 555 http:open_options(Parts, Options0), 556 upgrade_ssl_options(Parts, Options0, Options). 557 558:- if(current_predicate(ssl_upgrade_legacy_options/2)). 559upgrade_ssl_options(Parts, Options0, Options) :- 560 requires_ssl(Parts), 561 !, 562 ssl_upgrade_legacy_options(Options0, Options). 563:- endif. 564upgrade_ssl_options(_, Options, Options). 565 566merge_options_rev(Old, New, Merged) :- 567 merge_options(New, Old, Merged). 568 569is_meta(pem_password_hook). % SSL plugin callbacks 570is_meta(cert_verify_hook). 571 572 573httphttp_protocol_hook(http, _, StreamPair, StreamPair, _). 574 575default_port(https, 443) :- !. 576default_port(wss, 443) :- !. 577default_port(_, 80). 578 579host_and_port(Host, DefPort, DefPort, Host) :- !. 580host_and_port(Host, _, Port, Host:Port).
586autoload_https(Parts) :- 587 requires_ssl(Parts), 588 memberchk(scheme(S), Parts), 589 \+ clause(http:http_protocol_hook(S, _, StreamPair, StreamPair, _),_), 590 exists_source(library(http/http_ssl_plugin)), 591 !, 592 use_module(library(http/http_ssl_plugin)). 593autoload_https(_). 594 595requires_ssl(Parts) :- 596 memberchk(scheme(S), Parts), 597 secure_scheme(S). 598 599secure_scheme(https). 600secure_scheme(wss).
608send_rec_header(StreamPair, Stream, Host, RequestURI, Parts, Options) :- 609 ( catch(guarded_send_rec_header(StreamPair, Stream, 610 Host, RequestURI, Parts, Options), 611 E, true) 612 -> ( var(E) 613 -> ( option(output(StreamPair), Options) 614 -> true 615 ; true 616 ) 617 ; close(StreamPair, [force(true)]), 618 throw(E) 619 ) 620 ; close(StreamPair, [force(true)]), 621 fail 622 ). 623 624guarded_send_rec_header(StreamPair, Stream, Host, RequestURI, Parts, Options) :- 625 user_agent(Agent, Options), 626 method(Options, MNAME), 627 http_version(Version), 628 option(connection(Connection), Options, close), 629 debug(http(send_request), "> ~w ~w HTTP/~w", [MNAME, RequestURI, Version]), 630 debug(http(send_request), "> Host: ~w", [Host]), 631 debug(http(send_request), "> User-Agent: ~w", [Agent]), 632 debug(http(send_request), "> Connection: ~w", [Connection]), 633 format(StreamPair, 634 '~w ~w HTTP/~w\r\n\c 635 Host: ~w\r\n\c 636 User-Agent: ~w\r\n\c 637 Connection: ~w\r\n', 638 [MNAME, RequestURI, Version, Host, Agent, Connection]), 639 parts_uri(Parts, URI), 640 x_headers(Options, URI, StreamPair), 641 write_cookies(StreamPair, Parts, Options), 642 ( option(post(PostData), Options) 643 -> http_post_data(PostData, StreamPair, []) 644 ; format(StreamPair, '\r\n', []) 645 ), 646 flush_output(StreamPair), 647 % read the reply header 648 read_header(StreamPair, Parts, ReplyVersion, Code, Comment, Lines), 649 update_cookies(Lines, Parts, Options), 650 reply_header(Lines, Options), 651 do_open(ReplyVersion, Code, Comment, Lines, Options, Parts, Host, 652 StreamPair, Stream).
660http_version('1.1') :- 661 http:current_transfer_encoding(chunked), 662 !. 663http_version('1.1') :- 664 autoload_encoding(chunked), 665 !. 666http_version('1.0'). 667 668method(Options, MNAME) :- 669 option(post(_), Options), 670 !, 671 option(method(M), Options, post), 672 ( map_method(M, MNAME0) 673 -> MNAME = MNAME0 674 ; domain_error(method, M) 675 ). 676method(Options, MNAME) :- 677 option(method(M), Options, get), 678 ( map_method(M, MNAME0) 679 -> MNAME = MNAME0 680 ; map_method(_, M) 681 -> MNAME = M 682 ; domain_error(method, M) 683 ).
METHOD
keywords. Default are the official
HTTP methods as defined by the various RFCs.690:- multifile 691 map_method/2. 692 693map_method(delete, 'DELETE'). 694map_method(get, 'GET'). 695map_method(head, 'HEAD'). 696map_method(post, 'POST'). 697map_method(put, 'PUT'). 698map_method(patch, 'PATCH'). 699map_method(options, 'OPTIONS').
request_header(Name=Value)
options in
Options.
708x_headers(Options, URI, Out) :- 709 x_headers_(Options, [url(URI)|Options], Out). 710 711x_headers_([], _, _). 712x_headers_([H|T], Options, Out) :- 713 x_header(H, Options, Out), 714 x_headers_(T, Options, Out). 715 716x_header(request_header(Name=Value), _, Out) :- 717 !, 718 debug(http(send_request), "> ~w: ~w", [Name, Value]), 719 format(Out, '~w: ~w\r\n', [Name, Value]). 720x_header(proxy_authorization(ProxyAuthorization), Options, Out) :- 721 !, 722 auth_header(ProxyAuthorization, Options, 'Proxy-Authorization', Out). 723x_header(authorization(Authorization), Options, Out) :- 724 !, 725 auth_header(Authorization, Options, 'Authorization', Out). 726x_header(range(Spec), _, Out) :- 727 !, 728 Spec =.. [Unit, From, To], 729 ( To == end 730 -> ToT = '' 731 ; must_be(integer, To), 732 ToT = To 733 ), 734 debug(http(send_request), "> Range: ~w=~d-~w", [Unit, From, ToT]), 735 format(Out, 'Range: ~w=~d-~w\r\n', [Unit, From, ToT]). 736x_header(_, _, _).
740auth_header(basic(User, Password), _, Header, Out) :- 741 !, 742 format(codes(Codes), '~w:~w', [User, Password]), 743 phrase(base64(Codes), Base64Codes), 744 debug(http(send_request), "> ~w: Basic ~s", [Header, Base64Codes]), 745 format(Out, '~w: Basic ~s\r\n', [Header, Base64Codes]). 746auth_header(bearer(Token), _, Header, Out) :- 747 !, 748 debug(http(send_request), "> ~w: Bearer ~w", [Header,Token]), 749 format(Out, '~w: Bearer ~w\r\n', [Header, Token]). 750auth_header(Auth, Options, _, Out) :- 751 option(url(URL), Options), 752 add_method(Options, Options1), 753 http:authenticate_client(URL, send_auth_header(Auth, Out, Options1)), 754 !. 755auth_header(Auth, _, _, _) :- 756 domain_error(authorization, Auth). 757 758user_agent(Agent, Options) :- 759 ( option(user_agent(Agent), Options) 760 -> true 761 ; user_agent(Agent) 762 ). 763 764add_method(Options0, Options) :- 765 option(method(_), Options0), 766 !, 767 Options = Options0. 768add_method(Options0, Options) :- 769 option(post(_), Options0), 770 !, 771 Options = [method(post)|Options0]. 772add_method(Options0, [method(get)|Options0]).
783 % Redirections 784do_open(_, Code, _, Lines, Options0, Parts, _, In, Stream) :- 785 redirect_code(Code), 786 option(redirect(true), Options0, true), 787 location(Lines, RequestURI), 788 !, 789 debug(http(redirect), 'http_open: redirecting to ~w', [RequestURI]), 790 close(In), 791 parts_uri(Parts, Base), 792 uri_resolve(RequestURI, Base, Redirected), 793 parse_url_ex(Redirected, RedirectedParts), 794 ( redirect_limit_exceeded(Options0, Max) 795 -> format(atom(Comment), 'max_redirect (~w) limit exceeded', [Max]), 796 throw(error(permission_error(redirect, http, Redirected), 797 context(_, Comment))) 798 ; redirect_loop(RedirectedParts, Options0) 799 -> throw(error(permission_error(redirect, http, Redirected), 800 context(_, 'Redirection loop'))) 801 ; true 802 ), 803 redirect_options(Parts, RedirectedParts, Options0, Options), 804 http_open(RedirectedParts, Stream, Options). 805 % Need authentication 806do_open(_Version, Code, _Comment, Lines, Options0, Parts, _Host, In0, Stream) :- 807 authenticate_code(Code), 808 option(authenticate(true), Options0, true), 809 parts_uri(Parts, URI), 810 parse_headers(Lines, Headers), 811 http:authenticate_client( 812 URI, 813 auth_reponse(Headers, Options0, Options)), 814 !, 815 close(In0), 816 http_open(Parts, Stream, Options). 817 % Accepted codes 818do_open(Version, Code, _, Lines, Options, Parts, Host, In0, In) :- 819 ( option(status_code(Code), Options), 820 Lines \== [] 821 -> true 822 ; successful_code(Code) 823 ), 824 !, 825 parts_uri(Parts, URI), 826 parse_headers(Lines, Headers), 827 return_version(Options, Version), 828 return_size(Options, Headers), 829 return_fields(Options, Headers), 830 return_headers(Options, [status_code(Code)|Headers]), 831 consider_keep_alive(Lines, Parts, Host, In0, In1, Options), 832 transfer_encoding_filter(Lines, In1, In, Options), 833 % properly re-initialise the stream 834 set_stream(In, file_name(URI)), 835 set_stream(In, record_position(true)). 836do_open(_, _, _, [], Options, _, _, _, _) :- 837 option(connection(Connection), Options), 838 keep_alive(Connection), 839 !, 840 throw(error(keep_alive(closed),_)). 841 % report anything else as error 842do_open(_Version, Code, Comment, _, _, Parts, _, _, _) :- 843 parts_uri(Parts, URI), 844 ( map_error_code(Code, Error) 845 -> Formal =.. [Error, url, URI] 846 ; Formal = existence_error(url, URI) 847 ), 848 throw(error(Formal, context(_, status(Code, Comment)))). 849 850 851successful_code(Code) :- 852 between(200, 299, Code).
858redirect_limit_exceeded(Options, Max) :-
859 option(visited(Visited), Options, []),
860 length(Visited, N),
861 option(max_redirect(Max), Options, 10),
862 (Max == infinite -> fail ; N > Max).
872redirect_loop(Parts, Options) :-
873 option(visited(Visited), Options, []),
874 include(==(Parts), Visited, Same),
875 length(Same, Count),
876 Count > 2.
method(post)
and post(Data)
options from
the original option-list.
If we are connecting over a Unix domain socket we drop this option if the redirect host does not match the initial host.
888redirect_options(Parts, RedirectedParts, Options0, Options) :- 889 select_option(unix_socket(_), Options0, Options1), 890 memberchk(host(Host), Parts), 891 memberchk(host(RHost), RedirectedParts), 892 debug(http(redirect), 'http_open: redirecting AF_UNIX ~w to ~w', 893 [Host, RHost]), 894 Host \== RHost, 895 !, 896 redirect_options(Options1, Options). 897redirect_options(_, _, Options0, Options) :- 898 redirect_options(Options0, Options). 899 900redirect_options(Options0, Options) :- 901 ( select_option(post(_), Options0, Options1) 902 -> true 903 ; Options1 = Options0 904 ), 905 ( select_option(method(Method), Options1, Options), 906 \+ redirect_method(Method) 907 -> true 908 ; Options = Options1 909 ). 910 911redirect_method(delete). 912redirect_method(get). 913redirect_method(head).
923map_error_code(401, permission_error). 924map_error_code(403, permission_error). 925map_error_code(404, existence_error). 926map_error_code(405, permission_error). 927map_error_code(407, permission_error). 928map_error_code(410, existence_error). 929 930redirect_code(301). % Moved Permanently 931redirect_code(302). % Found (previously "Moved Temporary") 932redirect_code(303). % See Other 933redirect_code(307). % Temporary Redirect 934 935authenticate_code(401).
948open_socket(Address, StreamPair, Options) :- 949 debug(http(open), 'http_open: Connecting to ~p ...', [Address]), 950 tcp_connect(Address, StreamPair, Options), 951 stream_pair(StreamPair, In, Out), 952 debug(http(open), '\tok ~p ---> ~p', [In, Out]), 953 set_stream(In, record_position(false)), 954 ( option(timeout(Timeout), Options) 955 -> set_stream(In, timeout(Timeout)) 956 ; true 957 ). 958 959 960return_version(Options, Major-Minor) :- 961 option(version(Major-Minor), Options, _). 962 963return_size(Options, Headers) :- 964 ( memberchk(content_length(Size), Headers) 965 -> option(size(Size), Options, _) 966 ; true 967 ). 968 969return_fields([], _). 970return_fields([header(Name, Value)|T], Headers) :- 971 !, 972 ( Term =.. [Name,Value], 973 memberchk(Term, Headers) 974 -> true 975 ; Value = '' 976 ), 977 return_fields(T, Headers). 978return_fields([_|T], Lines) :- 979 return_fields(T, Lines). 980 981return_headers(Options, Headers) :- 982 option(headers(Headers), Options, _).
headers(-List)
option. Invalid
header lines are skipped, printing a warning using
pring_message/2.990parse_headers([], []) :- !. 991parse_headers([Line|Lines], Headers) :- 992 catch(http_parse_header(Line, [Header]), Error, true), 993 ( var(Error) 994 -> Headers = [Header|More] 995 ; print_message(warning, Error), 996 Headers = More 997 ), 998 parse_headers(Lines, More).
final_url(URL)
, unify URL with the final
URL after redirections.1006return_final_url(Options) :- 1007 option(final_url(URL), Options), 1008 var(URL), 1009 !, 1010 option(visited([Parts|_]), Options), 1011 parts_uri(Parts, URL). 1012return_final_url(_).
1024transfer_encoding_filter(Lines, In0, In, Options) :- 1025 transfer_encoding(Lines, Encoding), 1026 !, 1027 transfer_encoding_filter_(Encoding, In0, In, Options). 1028transfer_encoding_filter(Lines, In0, In, Options) :- 1029 content_encoding(Lines, Encoding), 1030 content_type(Lines, Type), 1031 \+ http:disable_encoding_filter(Type), 1032 !, 1033 transfer_encoding_filter_(Encoding, In0, In, Options). 1034transfer_encoding_filter(_, In, In, _Options). 1035 1036transfer_encoding_filter_(Encoding, In0, In, Options) :- 1037 option(raw_encoding(Encoding), Options), 1038 !, 1039 In = In0. 1040transfer_encoding_filter_(Encoding, In0, In, _Options) :- 1041 stream_pair(In0, In1, Out), 1042 ( nonvar(Out) 1043 -> close(Out) 1044 ; true 1045 ), 1046 ( http:encoding_filter(Encoding, In1, In) 1047 -> true 1048 ; autoload_encoding(Encoding), 1049 http:encoding_filter(Encoding, In1, In) 1050 -> true 1051 ; domain_error(http_encoding, Encoding) 1052 ). 1053 1054:- multifile 1055 autoload_encoding/1. 1056 1057:- if(exists_source(library(zlib))). 1058autoload_encoding(gzip) :- 1059 use_module(library(zlib)). 1060:- endif. 1061:- if(exists_source(library(http/http_stream))). 1062autoload_encoding(chunked) :- 1063 use_module(library(http/http_stream)). 1064:- endif. 1065 1066content_type(Lines, Type) :- 1067 member(Line, Lines), 1068 phrase(field('content-type'), Line, Rest), 1069 !, 1070 atom_codes(Type, Rest).
Content-encoding
as Transfer-encoding
encoding for specific values of ContentType. This predicate is
multifile and can thus be extended by the user.1078httpdisable_encoding_filter('application/x-gzip'). 1079httpdisable_encoding_filter('application/x-tar'). 1080httpdisable_encoding_filter('x-world/x-vrml'). 1081httpdisable_encoding_filter('application/zip'). 1082httpdisable_encoding_filter('application/x-gzip'). 1083httpdisable_encoding_filter('application/x-zip-compressed'). 1084httpdisable_encoding_filter('application/x-compress'). 1085httpdisable_encoding_filter('application/x-compressed'). 1086httpdisable_encoding_filter('application/x-spoon').
Transfer-encoding
header.1093transfer_encoding(Lines, Encoding) :- 1094 what_encoding(transfer_encoding, Lines, Encoding). 1095 1096what_encoding(What, Lines, Encoding) :- 1097 member(Line, Lines), 1098 phrase(encoding_(What, Debug), Line, Rest), 1099 !, 1100 atom_codes(Encoding, Rest), 1101 debug(http(What), '~w: ~p', [Debug, Rest]). 1102 1103encoding_(content_encoding, 'Content-encoding') --> 1104 field('content-encoding'). 1105encoding_(transfer_encoding, 'Transfer-encoding') --> 1106 field('transfer-encoding').
Content-encoding
header.
1113content_encoding(Lines, Encoding) :-
1114 what_encoding(content_encoding, Lines, Encoding).
Invalid reply header
.
1133read_header(In, Parts, Major-Minor, Code, Comment, Lines) :- 1134 read_line_to_codes(In, Line), 1135 ( Line == end_of_file 1136 -> parts_uri(Parts, Uri), 1137 existence_error(http_reply,Uri) 1138 ; true 1139 ), 1140 Line \== end_of_file, 1141 phrase(first_line(Major-Minor, Code, Comment), Line), 1142 debug(http(open), 'HTTP/~d.~d ~w ~w', [Major, Minor, Code, Comment]), 1143 read_line_to_codes(In, Line2), 1144 rest_header(Line2, In, Lines), 1145 !, 1146 ( debugging(http(open)) 1147 -> forall(member(HL, Lines), 1148 debug(http(open), '~s', [HL])) 1149 ; true 1150 ). 1151read_header(_, _, 1-1, 500, 'Invalid reply header', []). 1152 1153rest_header([], _, []) :- !. % blank line: end of header 1154rest_header(L0, In, [L0|L]) :- 1155 read_line_to_codes(In, L1), 1156 rest_header(L1, In, L).
1162content_length(Lines, Length) :- 1163 member(Line, Lines), 1164 phrase(content_length(Length0), Line), 1165 !, 1166 Length = Length0. 1167 1168location(Lines, RequestURI) :- 1169 member(Line, Lines), 1170 phrase(atom_field(location, RequestURI), Line), 1171 !. 1172 1173connection(Lines, Connection) :- 1174 member(Line, Lines), 1175 phrase(atom_field(connection, Connection0), Line), 1176 !, 1177 Connection = Connection0. 1178 1179first_line(Major-Minor, Code, Comment) --> 1180 "HTTP/", integer(Major), ".", integer(Minor), 1181 skip_blanks, 1182 integer(Code), 1183 skip_blanks, 1184 rest(Comment). 1185 1186atom_field(Name, Value) --> 1187 field(Name), 1188 rest(Value). 1189 1190content_length(Len) --> 1191 field('content-length'), 1192 integer(Len). 1193 1194field(Name) --> 1195 { atom_codes(Name, Codes) }, 1196 field_codes(Codes). 1197 1198field_codes([]) --> 1199 ":", 1200 skip_blanks. 1201field_codes([H|T]) --> 1202 [C], 1203 { match_header_char(H, C) 1204 }, 1205 field_codes(T). 1206 1207match_header_char(C, C) :- !. 1208match_header_char(C, U) :- 1209 code_type(C, to_lower(U)), 1210 !. 1211match_header_char(0'_, 0'-). 1212 1213 1214skip_blanks --> 1215 [C], 1216 { code_type(C, white) 1217 }, 1218 !, 1219 skip_blanks. 1220skip_blanks --> 1221 [].
1227integer(Code) --> 1228 digit(D0), 1229 digits(D), 1230 { number_codes(Code, [D0|D]) 1231 }. 1232 1233digit(C) --> 1234 [C], 1235 { code_type(C, digit) 1236 }. 1237 1238digits([D0|D]) --> 1239 digit(D0), 1240 !, 1241 digits(D). 1242digits([]) --> 1243 [].
1249rest(Atom) --> call(rest_(Atom)). 1250 1251rest_(Atom, L, []) :- 1252 atom_codes(Atom, L).
raw_headers(-Headers)
.1260reply_header(Lines, Options) :- 1261 option(raw_headers(Headers), Options), 1262 !, 1263 maplist(string_codes, Headers, Lines). 1264reply_header(_, _). 1265 1266 1267 /******************************* 1268 * AUTHORIZATION MANAGEMENT * 1269 *******************************/
-
, possibly defined
authorization is cleared. For example:
?- http_set_authorization('http://www.example.com/private/', basic('John', 'Secret'))
1285:- dynamic 1286 stored_authorization/2, 1287 cached_authorization/2. 1288 1289http_set_authorization(URL, Authorization) :- 1290 must_be(atom, URL), 1291 retractall(stored_authorization(URL, _)), 1292 ( Authorization = (-) 1293 -> true 1294 ; check_authorization(Authorization), 1295 assert(stored_authorization(URL, Authorization)) 1296 ), 1297 retractall(cached_authorization(_,_)). 1298 Var) (:- 1300 var(Var), 1301 !, 1302 instantiation_error(Var). 1303check_authorization(basic(User, Password)) :- 1304 must_be(atom, User), 1305 must_be(text, Password). 1306check_authorization(digest(User, Password)) :- 1307 must_be(atom, User), 1308 must_be(text, Password).
1316authorization(_, _) :- 1317 \+ stored_authorization(_, _), 1318 !, 1319 fail. 1320authorization(URL, Authorization) :- 1321 cached_authorization(URL, Authorization), 1322 !, 1323 Authorization \== (-). 1324authorization(URL, Authorization) :- 1325 ( stored_authorization(Prefix, Authorization), 1326 sub_atom(URL, 0, _, _, Prefix) 1327 -> assert(cached_authorization(URL, Authorization)) 1328 ; assert(cached_authorization(URL, -)), 1329 fail 1330 ). 1331 _, Options, Options) (:- 1333 option(authorization(_), Options), 1334 !. 1335add_authorization(Parts, Options0, Options) :- 1336 url_part(user(User), Parts), 1337 url_part(password(Passwd), Parts), 1338 !, 1339 Options = [authorization(basic(User,Passwd))|Options0]. 1340add_authorization(Parts, Options0, Options) :- 1341 stored_authorization(_, _) -> % quick test to avoid work 1342 parts_uri(Parts, URL), 1343 authorization(URL, Auth), 1344 !, 1345 Options = [authorization(Auth)|Options0]. 1346add_authorization(_, Options, Options).
1354parse_url_ex(URL, [uri(URL)|Parts]) :- 1355 uri_components(URL, Components), 1356 phrase(components(Components), Parts), 1357 ( option(host(_), Parts) 1358 -> true 1359 ; domain_error(url, URL) 1360 ). 1361 1362components(Components) --> 1363 uri_scheme(Components), 1364 uri_path(Components), 1365 uri_authority(Components), 1366 uri_request_uri(Components). 1367 1368uri_scheme(Components) --> 1369 { uri_data(scheme, Components, Scheme), nonvar(Scheme) }, 1370 !, 1371 [ scheme(Scheme) 1372 ]. 1373uri_scheme(_) --> []. 1374 1375uri_path(Components) --> 1376 { uri_data(path, Components, Path0), nonvar(Path0), 1377 ( Path0 == '' 1378 -> Path = (/) 1379 ; Path = Path0 1380 ) 1381 }, 1382 !, 1383 [ path(Path) 1384 ]. 1385uri_path(_) --> []. 1386 Components) (--> 1388 { uri_data(authority, Components, Auth), nonvar(Auth), 1389 !, 1390 uri_authority_components(Auth, Data) 1391 }, 1392 [ authority(Auth) ], 1393 auth_field(user, Data), 1394 auth_field(password, Data), 1395 auth_field(host, Data), 1396 auth_field(port, Data). 1397uri_authority(_) --> []. 1398 1399auth_field(Field, Data) --> 1400 { uri_authority_data(Field, Data, EncValue), nonvar(EncValue), 1401 !, 1402 ( atom(EncValue) 1403 -> uri_encoded(query_value, Value, EncValue) 1404 ; Value = EncValue 1405 ), 1406 Part =.. [Field,Value] 1407 }, 1408 [ Part ]. 1409auth_field(_, _) --> []. 1410 1411uri_request_uri(Components) --> 1412 { uri_data(path, Components, Path0), 1413 uri_data(search, Components, Search), 1414 ( Path0 == '' 1415 -> Path = (/) 1416 ; Path = Path0 1417 ), 1418 uri_data(path, Components2, Path), 1419 uri_data(search, Components2, Search), 1420 uri_components(RequestURI, Components2) 1421 }, 1422 [ request_uri(RequestURI) 1423 ].
1431parts_scheme(Parts, Scheme) :- 1432 url_part(scheme(Scheme), Parts), 1433 !. 1434parts_scheme(Parts, Scheme) :- % compatibility with library(url) 1435 url_part(protocol(Scheme), Parts), 1436 !. 1437parts_scheme(_, http). 1438 1439parts_authority(Parts, Auth) :- 1440 url_part(authority(Auth), Parts), 1441 !. 1442parts_authority(Parts, Auth) :- 1443 url_part(host(Host), Parts, _), 1444 url_part(port(Port), Parts, _), 1445 url_part(user(User), Parts, _), 1446 url_part(password(Password), Parts, _), 1447 uri_authority_components(Auth, 1448 uri_authority(User, Password, Host, Port)). 1449 1450parts_request_uri(Parts, RequestURI) :- 1451 option(request_uri(RequestURI), Parts), 1452 !. 1453parts_request_uri(Parts, RequestURI) :- 1454 url_part(path(Path), Parts, /), 1455 ignore(parts_search(Parts, Search)), 1456 uri_data(path, Data, Path), 1457 uri_data(search, Data, Search), 1458 uri_components(RequestURI, Data). 1459 1460parts_search(Parts, Search) :- 1461 option(query_string(Search), Parts), 1462 !. 1463parts_search(Parts, Search) :- 1464 option(search(Fields), Parts), 1465 !, 1466 uri_query_components(Search, Fields). 1467 1468 1469parts_uri(Parts, URI) :- 1470 option(uri(URI), Parts), 1471 !. 1472parts_uri(Parts, URI) :- 1473 parts_scheme(Parts, Scheme), 1474 ignore(parts_authority(Parts, Auth)), 1475 parts_request_uri(Parts, RequestURI), 1476 uri_components(RequestURI, Data), 1477 uri_data(scheme, Data, Scheme), 1478 uri_data(authority, Data, Auth), 1479 uri_components(URI, Data). 1480 1481parts_port(Parts, Port) :- 1482 parts_scheme(Parts, Scheme), 1483 default_port(Scheme, DefPort), 1484 url_part(port(Port), Parts, DefPort). 1485 1486url_part(Part, Parts) :- 1487 Part =.. [Name,Value], 1488 Gen =.. [Name,RawValue], 1489 option(Gen, Parts), 1490 !, 1491 Value = RawValue. 1492 1493url_part(Part, Parts, Default) :- 1494 Part =.. [Name,Value], 1495 Gen =.. [Name,RawValue], 1496 ( option(Gen, Parts) 1497 -> Value = RawValue 1498 ; Value = Default 1499 ). 1500 1501 1502 /******************************* 1503 * COOKIES * 1504 *******************************/ 1505 Out, Parts, Options) (:- 1507 http:write_cookies(Out, Parts, Options), 1508 !. 1509write_cookies(_, _, _). 1510 _, _, _) (:- 1512 predicate_property(http:update_cookies(_,_,_), number_of_clauses(0)), 1513 !. 1514update_cookies(Lines, Parts, Options) :- 1515 ( member(Line, Lines), 1516 phrase(atom_field('set_cookie', CookieData), Line), 1517 http:update_cookies(CookieData, Parts, Options), 1518 fail 1519 ; true 1520 ). 1521 1522 1523 /******************************* 1524 * OPEN ANY * 1525 *******************************/ 1526 1527:- multifile iostream:open_hook/6.
http
and
https
URLs for Mode == read
.1535iostreamopen_hook(URL, read, Stream, Close, Options0, Options) :- 1536 (atom(URL) -> true ; string(URL)), 1537 uri_is_global(URL), 1538 uri_components(URL, Components), 1539 uri_data(scheme, Components, Scheme), 1540 http_scheme(Scheme), 1541 !, 1542 Options = Options0, 1543 Close = close(Stream), 1544 http_open(URL, Stream, Options0). 1545 1546http_scheme(http). 1547http_scheme(https). 1548 1549 1550 /******************************* 1551 * KEEP-ALIVE * 1552 *******************************/
1558consider_keep_alive(Lines, Parts, Host, StreamPair, In, Options) :- 1559 option(connection(Asked), Options), 1560 keep_alive(Asked), 1561 connection(Lines, Given), 1562 keep_alive(Given), 1563 content_length(Lines, Bytes), 1564 !, 1565 stream_pair(StreamPair, In0, _), 1566 connection_address(Host, Parts, HostPort), 1567 debug(http(connection), 1568 'Keep-alive to ~w (~D bytes)', [HostPort, Bytes]), 1569 stream_range_open(In0, In, 1570 [ size(Bytes), 1571 onclose(keep_alive(StreamPair, HostPort)) 1572 ]). 1573consider_keep_alive(_, _, _, Stream, Stream, _). 1574 1575connection_address(Host, _, Host) :- 1576 Host = _:_, 1577 !. 1578connection_address(Host, Parts, Host:Port) :- 1579 parts_port(Parts, Port). 1580 1581keep_alive(keep_alive) :- !. 1582keep_alive(Connection) :- 1583 downcase_atom(Connection, 'keep-alive'). 1584 1585:- public keep_alive/4. 1586 1587keep_alive(StreamPair, Host, _In, 0) :- 1588 !, 1589 debug(http(connection), 'Adding connection to ~p to pool', [Host]), 1590 add_to_pool(Host, StreamPair). 1591keep_alive(StreamPair, Host, In, Left) :- 1592 Left < 100, 1593 debug(http(connection), 'Reading ~D left bytes', [Left]), 1594 read_incomplete(In, Left), 1595 add_to_pool(Host, StreamPair), 1596 !. 1597keep_alive(StreamPair, _, _, _) :- 1598 debug(http(connection), 1599 'Closing connection due to excessive unprocessed input', []), 1600 ( debugging(http(connection)) 1601 -> catch(close(StreamPair), E, 1602 print_message(warning, E)) 1603 ; close(StreamPair, [force(true)]) 1604 ).
1611read_incomplete(In, Left) :- 1612 catch(setup_call_cleanup( 1613 open_null_stream(Null), 1614 copy_stream_data(In, Null, Left), 1615 close(Null)), 1616 _, 1617 fail). 1618 1619:- dynamic 1620 connection_pool/4, % Hash, Address, Stream, Time 1621 connection_gc_time/1. 1622 1623add_to_pool(Address, StreamPair) :- 1624 keep_connection(Address), 1625 get_time(Now), 1626 term_hash(Address, Hash), 1627 assertz(connection_pool(Hash, Address, StreamPair, Now)). 1628 1629get_from_pool(Address, StreamPair) :- 1630 term_hash(Address, Hash), 1631 retract(connection_pool(Hash, Address, StreamPair, _)).
1640keep_connection(Address) :- 1641 close_old_connections(2), 1642 predicate_property(connection_pool(_,_,_,_), number_of_clauses(C)), 1643 C =< 10, 1644 term_hash(Address, Hash), 1645 aggregate_all(count, connection_pool(Hash, Address, _, _), Count), 1646 Count =< 2. 1647 1648close_old_connections(Timeout) :- 1649 get_time(Now), 1650 Before is Now - Timeout, 1651 ( connection_gc_time(GC), 1652 GC > Before 1653 -> true 1654 ; ( retractall(connection_gc_time(_)), 1655 asserta(connection_gc_time(Now)), 1656 connection_pool(Hash, Address, StreamPair, Added), 1657 Added < Before, 1658 retract(connection_pool(Hash, Address, StreamPair, Added)), 1659 debug(http(connection), 1660 'Closing inactive keep-alive to ~p', [Address]), 1661 close(StreamPair, [force(true)]), 1662 fail 1663 ; true 1664 ) 1665 ).
http_close_keep_alive(_)
closes all currently known keep-alive connections.
1674http_close_keep_alive(Address) :-
1675 forall(get_from_pool(Address, StreamPair),
1676 close(StreamPair, [force(true)])).
1687keep_alive_error(error(keep_alive(closed), _), _) :- 1688 !, 1689 debug(http(connection), 'Keep-alive connection was closed', []), 1690 fail. 1691keep_alive_error(error(io_error(_,_), _), StreamPair) :- 1692 !, 1693 close(StreamPair, [force(true)]), 1694 debug(http(connection), 'IO error on Keep-alive connection', []), 1695 fail. 1696keep_alive_error(Error, StreamPair) :- 1697 close(StreamPair, [force(true)]), 1698 throw(Error). 1699 1700 1701 /******************************* 1702 * HOOK DOCUMENTATION * 1703 *******************************/
:- multifile http:open_options/2. http:open_options(Parts, Options) :- option(host(Host), Parts), Host \== localhost, Options = [proxy('proxy.local', 3128)].
This hook may return multiple solutions. The returned options are combined using merge_options/3 where earlier solutions overrule later solutions.
Cookie:
header for the current connection. Out is an
open stream to the HTTP server, Parts is the broken-down request
(see uri_components/2) and Options is the list of options passed
to http_open. The predicate is called as if using ignore/1.
Set-Cookie
field, Parts is the broken-down request (see
uri_components/2) and Options is the list of options passed to
http_open.
HTTP client library
This library defines http_open/3, which opens an URL as a Prolog stream. The functionality of the library can be extended by loading two additional modules that act as plugins:
https
is requested using a default SSL context. See the plugin for additional information regarding security.gzip
transfer encoding. This plugin is lazily loaded if a connection is opened that claims this transfer encoding.Transfer-encoding: chunked
header.Here is a simple example to fetch a web-page:
The example below fetches the modification time of a web-page. Note that
Modified
is''
(the empty atom) if the web-server does not provide a time-stamp for the resource. See also parse_time/2.Then next example uses Google search. It exploits library(uri) to manage URIs, library(sgml) to load an HTML document and library(xpath) to navigate the parsed HTML. Note that you may need to adjust the XPath queries if the data returned by Google changes (this example indeed no longer works and currently fails at the first xpath/3 call)
An example query is below:
Content-Type
header. */