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 CWI, Amsterdam 9 All rights reserved. 10 11 Redistribution and use in source and binary forms, with or without 12 modification, are permitted provided that the following conditions 13 are met: 14 15 1. Redistributions of source code must retain the above copyright 16 notice, this list of conditions and the following disclaimer. 17 18 2. Redistributions in binary form must reproduce the above copyright 19 notice, this list of conditions and the following disclaimer in 20 the documentation and/or other materials provided with the 21 distribution. 22 23 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 24 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 25 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 26 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 27 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 28 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 29 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 30 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 31 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 32 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 33 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 34 POSSIBILITY OF SUCH DAMAGE. 35*/ 36 37:- module(http_open, 38 [ http_open/3, % +URL, -Stream, +Options 39 http_set_authorization/2, % +URL, +Authorization 40 http_close_keep_alive/1 % +Address 41 ]). 42:- autoload(library(aggregate),[aggregate_all/3]). 43:- autoload(library(apply),[foldl/4,include/3]). 44:- autoload(library(base64),[base64/3]). 45:- autoload(library(debug),[debug/3,debugging/1]). 46:- autoload(library(error), 47 [ domain_error/2, must_be/2, existence_error/2, instantiation_error/1 48 ]). 49:- autoload(library(lists),[last/2,member/2]). 50:- autoload(library(option), 51 [ meta_options/3, option/2, select_option/4, merge_options/3, 52 option/3, select_option/3 53 ]). 54:- autoload(library(readutil),[read_line_to_codes/2]). 55:- autoload(library(uri), 56 [ uri_resolve/3, uri_components/2, uri_data/3, 57 uri_authority_components/2, uri_authority_data/3, 58 uri_encoded/3, uri_query_components/2, uri_is_global/1 59 ]). 60:- autoload(library(http/http_header), 61 [ http_parse_header/2, http_post_data/3 ]). 62:- autoload(library(http/http_stream),[stream_range_open/3]). 63:- if(exists_source(library(ssl))). 64:- autoload(library(ssl), [ssl_upgrade_legacy_options/2]). 65:- endif. 66:- use_module(library(socket)).
172:- multifile 173 http:encoding_filter/3, % +Encoding, +In0, -In 174 http:current_transfer_encoding/1, % ?Encoding 175 http:disable_encoding_filter/1, % +ContentType 176 http:http_protocol_hook/5, % +Protocol, +Parts, +StreamPair, 177 % -NewStreamPair, +Options 178 http:open_options/2, % +Parts, -Options 179 http:write_cookies/3, % +Out, +Parts, +Options 180 http:update_cookies/3, % +CookieLine, +Parts, +Options 181 http:authenticate_client/2, % +URL, +Action 182 http:http_connection_over_proxy/6. 183 184:- meta_predicate 185 http_open( , , ). 186 187:- predicate_options(http_open/3, 3, 188 [ authorization(compound), 189 final_url(-atom), 190 header(+atom, -atom), 191 headers(-list), 192 connection(+atom), 193 method(oneof([delete,get,put,head,post,patch,options])), 194 size(-integer), 195 status_code(-integer), 196 output(-stream), 197 timeout(number), 198 unix_socket(+atom), 199 proxy(atom, integer), 200 proxy_authorization(compound), 201 bypass_proxy(boolean), 202 request_header(any), 203 user_agent(atom), 204 version(-compound), 205 % The option below applies if library(http/http_header) is loaded 206 post(any), 207 % The options below apply if library(http/http_ssl_plugin)) is loaded 208 pem_password_hook(callable), 209 cacert_file(atom), 210 cert_verify_hook(callable) 211 ]).
User-Agent
, can be overruled using the
option user_agent(Agent)
of http_open/3.
218user_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.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))
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.
408:- multifile 409 socket:proxy_for_url/3. % +URL, +Host, -ProxyList 410 411http_open(URL, Stream, QOptions) :- 412 meta_options(is_meta, QOptions, Options0), 413 ( atomic(URL) 414 -> parse_url_ex(URL, Parts) 415 ; Parts = URL 416 ), 417 autoload_https(Parts), 418 upgrade_ssl_options(Parts, Options0, Options), 419 add_authorization(Parts, Options, Options1), 420 findall(HostOptions, hooked_options(Parts, HostOptions), AllHostOptions), 421 foldl(merge_options_rev, AllHostOptions, Options1, Options2), 422 ( option(bypass_proxy(true), Options) 423 -> try_http_proxy(direct, Parts, Stream, Options2) 424 ; term_variables(Options2, Vars2), 425 findall(Result-Vars2, 426 try_a_proxy(Parts, Result, Options2), 427 ResultList), 428 last(ResultList, Status-Vars2) 429 -> ( Status = true(_Proxy, Stream) 430 -> true 431 ; throw(error(proxy_error(tried(ResultList)), _)) 432 ) 433 ; try_http_proxy(direct, Parts, Stream, Options2) 434 ). 435 436try_a_proxy(Parts, Result, Options) :- 437 parts_uri(Parts, AtomicURL), 438 option(host(Host), Parts), 439 ( option(unix_socket(Path), Options) 440 -> Proxy = unix_socket(Path) 441 ; ( option(proxy(ProxyHost:ProxyPort), Options) 442 ; is_list(Options), 443 memberchk(proxy(ProxyHost,ProxyPort), Options) 444 ) 445 -> Proxy = proxy(ProxyHost, ProxyPort) 446 ; socket:proxy_for_url(AtomicURL, Host, Proxy) 447 ), 448 debug(http(proxy), 449 'http_open: Connecting via ~w to ~w', [Proxy, AtomicURL]), 450 ( catch(try_http_proxy(Proxy, Parts, Stream, Options), E, true) 451 -> ( var(E) 452 -> !, Result = true(Proxy, Stream) 453 ; Result = error(Proxy, E) 454 ) 455 ; Result = false(Proxy) 456 ), 457 debug(http(proxy), 'http_open: ~w: ~p', [Proxy, Result]). 458 459try_http_proxy(Method, Parts, Stream, Options0) :- 460 option(host(Host), Parts), 461 proxy_request_uri(Method, Parts, RequestURI), 462 select_option(visited(Visited0), Options0, OptionsV, []), 463 Options = [visited([Parts|Visited0])|OptionsV], 464 parts_scheme(Parts, Scheme), 465 default_port(Scheme, DefPort), 466 url_part(port(Port), Parts, DefPort), 467 host_and_port(Host, DefPort, Port, HostPort), 468 ( option(connection(Connection), Options0), 469 keep_alive(Connection), 470 get_from_pool(Host:Port, StreamPair), 471 debug(http(connection), 'Trying Keep-alive to ~p using ~p', 472 [ Host:Port, StreamPair ]), 473 catch(send_rec_header(StreamPair, Stream, HostPort, 474 RequestURI, Parts, Options), 475 error(E,_), 476 keep_alive_error(E)) 477 -> true 478 ; http:http_connection_over_proxy(Method, Parts, Host:Port, 479 SocketStreamPair, Options, Options1), 480 ( catch(http:http_protocol_hook(Scheme, Parts, 481 SocketStreamPair, 482 StreamPair, Options), 483 Error, 484 ( close(SocketStreamPair, [force(true)]), 485 throw(Error))) 486 -> true 487 ; StreamPair = SocketStreamPair 488 ), 489 send_rec_header(StreamPair, Stream, HostPort, 490 RequestURI, Parts, Options1) 491 ), 492 return_final_url(Options). 493 494proxy_request_uri(direct, Parts, RequestURI) :- 495 !, 496 parts_request_uri(Parts, RequestURI). 497proxy_request_uri(unix_socket(_), Parts, RequestURI) :- 498 !, 499 parts_request_uri(Parts, RequestURI). 500proxy_request_uri(_, Parts, RequestURI) :- 501 parts_uri(Parts, RequestURI). 502 503httphttp_connection_over_proxy(unix_socket(Path), _, _, 504 StreamPair, Options, Options) :- 505 !, 506 unix_domain_socket(Socket), 507 tcp_connect(Socket, Path), 508 tcp_open_socket(Socket, In, Out), 509 stream_pair(StreamPair, In, Out). 510httphttp_connection_over_proxy(direct, _, Host:Port, 511 StreamPair, Options, Options) :- 512 !, 513 open_socket(Host:Port, StreamPair, Options). 514httphttp_connection_over_proxy(proxy(ProxyHost, ProxyPort), Parts, _, 515 StreamPair, Options, Options) :- 516 \+ ( memberchk(scheme(Scheme), Parts), 517 secure_scheme(Scheme) 518 ), 519 !, 520 % We do not want any /more/ proxy after this 521 open_socket(ProxyHost:ProxyPort, StreamPair, 522 [bypass_proxy(true)|Options]). 523httphttp_connection_over_proxy(socks(SocksHost, SocksPort), _Parts, Host:Port, 524 StreamPair, Options, Options) :- 525 !, 526 tcp_connect(SocksHost:SocksPort, StreamPair, [bypass_proxy(true)]), 527 catch(negotiate_socks_connection(Host:Port, StreamPair), 528 Error, 529 ( close(StreamPair, [force(true)]), 530 throw(Error) 531 )).
cacerts_file(File)
option to a cacerts(List)
option to ensure proper
merging of options.539hooked_options(Parts, Options) :- 540 http:open_options(Parts, Options0), 541 upgrade_ssl_options(Parts, Options0, Options). 542 543:- if(current_predicate(ssl_upgrade_legacy_options/2)). 544upgrade_ssl_options(Parts, Options0, Options) :- 545 requires_ssl(Parts), 546 !, 547 ssl_upgrade_legacy_options(Options0, Options). 548:- endif. 549upgrade_ssl_options(_, Options, Options). 550 551merge_options_rev(Old, New, Merged) :- 552 merge_options(New, Old, Merged). 553 554is_meta(pem_password_hook). % SSL plugin callbacks 555is_meta(cert_verify_hook). 556 557 558httphttp_protocol_hook(http, _, StreamPair, StreamPair, _). 559 560default_port(https, 443) :- !. 561default_port(wss, 443) :- !. 562default_port(_, 80). 563 564host_and_port(Host, DefPort, DefPort, Host) :- !. 565host_and_port(Host, _, Port, Host:Port).
571autoload_https(Parts) :- 572 requires_ssl(Parts), 573 memberchk(scheme(S), Parts), 574 \+ clause(http:http_protocol_hook(S, _, StreamPair, StreamPair, _),_), 575 exists_source(library(http/http_ssl_plugin)), 576 !, 577 use_module(library(http/http_ssl_plugin)). 578autoload_https(_). 579 580requires_ssl(Parts) :- 581 memberchk(scheme(S), Parts), 582 secure_scheme(S). 583 584secure_scheme(https). 585secure_scheme(wss).
593send_rec_header(StreamPair, Stream, Host, RequestURI, Parts, Options) :- 594 ( catch(guarded_send_rec_header(StreamPair, Stream, 595 Host, RequestURI, Parts, Options), 596 E, true) 597 -> ( var(E) 598 -> ( option(output(StreamPair), Options) 599 -> true 600 ; true 601 ) 602 ; close(StreamPair, [force(true)]), 603 throw(E) 604 ) 605 ; close(StreamPair, [force(true)]), 606 fail 607 ). 608 609guarded_send_rec_header(StreamPair, Stream, Host, RequestURI, Parts, Options) :- 610 user_agent(Agent, Options), 611 method(Options, MNAME), 612 http_version(Version), 613 option(connection(Connection), Options, close), 614 debug(http(send_request), "> ~w ~w HTTP/~w", [MNAME, RequestURI, Version]), 615 debug(http(send_request), "> Host: ~w", [Host]), 616 debug(http(send_request), "> User-Agent: ~w", [Agent]), 617 debug(http(send_request), "> Connection: ~w", [Connection]), 618 format(StreamPair, 619 '~w ~w HTTP/~w\r\n\c 620 Host: ~w\r\n\c 621 User-Agent: ~w\r\n\c 622 Connection: ~w\r\n', 623 [MNAME, RequestURI, Version, Host, Agent, Connection]), 624 parts_uri(Parts, URI), 625 x_headers(Options, URI, StreamPair), 626 write_cookies(StreamPair, Parts, Options), 627 ( option(post(PostData), Options) 628 -> http_post_data(PostData, StreamPair, []) 629 ; format(StreamPair, '\r\n', []) 630 ), 631 flush_output(StreamPair), 632 % read the reply header 633 read_header(StreamPair, Parts, ReplyVersion, Code, Comment, Lines), 634 update_cookies(Lines, Parts, Options), 635 do_open(ReplyVersion, Code, Comment, Lines, Options, Parts, Host, 636 StreamPair, Stream).
644http_version('1.1') :- 645 http:current_transfer_encoding(chunked), 646 !. 647http_version('1.0'). 648 649method(Options, MNAME) :- 650 option(post(_), Options), 651 !, 652 option(method(M), Options, post), 653 ( map_method(M, MNAME0) 654 -> MNAME = MNAME0 655 ; domain_error(method, M) 656 ). 657method(Options, MNAME) :- 658 option(method(M), Options, get), 659 ( map_method(M, MNAME0) 660 -> MNAME = MNAME0 661 ; map_method(_, M) 662 -> MNAME = M 663 ; domain_error(method, M) 664 ).
METHOD
keywords. Default are the official
HTTP methods as defined by the various RFCs.671:- multifile 672 map_method/2. 673 674map_method(delete, 'DELETE'). 675map_method(get, 'GET'). 676map_method(head, 'HEAD'). 677map_method(post, 'POST'). 678map_method(put, 'PUT'). 679map_method(patch, 'PATCH'). 680map_method(options, 'OPTIONS').
request_header(Name=Value)
options in
Options.
689x_headers(Options, URI, Out) :- 690 x_headers_(Options, [url(URI)|Options], Out). 691 692x_headers_([], _, _). 693x_headers_([H|T], Options, Out) :- 694 x_header(H, Options, Out), 695 x_headers_(T, Options, Out). 696 697x_header(request_header(Name=Value), _, Out) :- 698 !, 699 debug(http(send_request), "> ~w: ~w", [Name, Value]), 700 format(Out, '~w: ~w\r\n', [Name, Value]). 701x_header(proxy_authorization(ProxyAuthorization), Options, Out) :- 702 !, 703 auth_header(ProxyAuthorization, Options, 'Proxy-Authorization', Out). 704x_header(authorization(Authorization), Options, Out) :- 705 !, 706 auth_header(Authorization, Options, 'Authorization', Out). 707x_header(range(Spec), _, Out) :- 708 !, 709 Spec =.. [Unit, From, To], 710 ( To == end 711 -> ToT = '' 712 ; must_be(integer, To), 713 ToT = To 714 ), 715 debug(http(send_request), "> Range: ~w=~d-~w", [Unit, From, ToT]), 716 format(Out, 'Range: ~w=~d-~w\r\n', [Unit, From, ToT]). 717x_header(_, _, _).
721auth_header(basic(User, Password), _, Header, Out) :- 722 !, 723 format(codes(Codes), '~w:~w', [User, Password]), 724 phrase(base64(Codes), Base64Codes), 725 debug(http(send_request), "> ~w: Basic ~s", [Header, Base64Codes]), 726 format(Out, '~w: Basic ~s\r\n', [Header, Base64Codes]). 727auth_header(bearer(Token), _, Header, Out) :- 728 !, 729 debug(http(send_request), "> ~w: Bearer ~w", [Header,Token]), 730 format(Out, '~w: Bearer ~w\r\n', [Header, Token]). 731auth_header(Auth, Options, _, Out) :- 732 option(url(URL), Options), 733 add_method(Options, Options1), 734 http:authenticate_client(URL, send_auth_header(Auth, Out, Options1)), 735 !. 736auth_header(Auth, _, _, _) :- 737 domain_error(authorization, Auth). 738 739user_agent(Agent, Options) :- 740 ( option(user_agent(Agent), Options) 741 -> true 742 ; user_agent(Agent) 743 ). 744 745add_method(Options0, Options) :- 746 option(method(_), Options0), 747 !, 748 Options = Options0. 749add_method(Options0, Options) :- 750 option(post(_), Options0), 751 !, 752 Options = [method(post)|Options0]. 753add_method(Options0, [method(get)|Options0]).
764 % Redirections 765do_open(_, Code, _, Lines, Options0, Parts, _, In, Stream) :- 766 redirect_code(Code), 767 option(redirect(true), Options0, true), 768 location(Lines, RequestURI), 769 !, 770 debug(http(redirect), 'http_open: redirecting to ~w', [RequestURI]), 771 close(In), 772 parts_uri(Parts, Base), 773 uri_resolve(RequestURI, Base, Redirected), 774 parse_url_ex(Redirected, RedirectedParts), 775 ( redirect_limit_exceeded(Options0, Max) 776 -> format(atom(Comment), 'max_redirect (~w) limit exceeded', [Max]), 777 throw(error(permission_error(redirect, http, Redirected), 778 context(_, Comment))) 779 ; redirect_loop(RedirectedParts, Options0) 780 -> throw(error(permission_error(redirect, http, Redirected), 781 context(_, 'Redirection loop'))) 782 ; true 783 ), 784 redirect_options(Parts, RedirectedParts, Options0, Options), 785 http_open(RedirectedParts, Stream, Options). 786 % Need authentication 787do_open(_Version, Code, _Comment, Lines, Options0, Parts, _Host, In0, Stream) :- 788 authenticate_code(Code), 789 option(authenticate(true), Options0, true), 790 parts_uri(Parts, URI), 791 parse_headers(Lines, Headers), 792 http:authenticate_client( 793 URI, 794 auth_reponse(Headers, Options0, Options)), 795 !, 796 close(In0), 797 http_open(Parts, Stream, Options). 798 % Accepted codes 799do_open(Version, Code, _, Lines, Options, Parts, Host, In0, In) :- 800 ( option(status_code(Code), Options), 801 Lines \== [] 802 -> true 803 ; successful_code(Code) 804 ), 805 !, 806 parts_uri(Parts, URI), 807 parse_headers(Lines, Headers), 808 return_version(Options, Version), 809 return_size(Options, Headers), 810 return_fields(Options, Headers), 811 return_headers(Options, Headers), 812 consider_keep_alive(Lines, Parts, Host, In0, In1, Options), 813 transfer_encoding_filter(Lines, In1, In), 814 % properly re-initialise the stream 815 set_stream(In, file_name(URI)), 816 set_stream(In, record_position(true)). 817do_open(_, _, _, [], Options, _, _, _, _) :- 818 option(connection(Connection), Options), 819 keep_alive(Connection), 820 !, 821 throw(error(keep_alive(closed),_)). 822 % report anything else as error 823do_open(_Version, Code, Comment, _, _, Parts, _, _, _) :- 824 parts_uri(Parts, URI), 825 ( map_error_code(Code, Error) 826 -> Formal =.. [Error, url, URI] 827 ; Formal = existence_error(url, URI) 828 ), 829 throw(error(Formal, context(_, status(Code, Comment)))). 830 831 832successful_code(Code) :- 833 between(200, 299, Code).
839redirect_limit_exceeded(Options, Max) :-
840 option(visited(Visited), Options, []),
841 length(Visited, N),
842 option(max_redirect(Max), Options, 10),
843 (Max == infinite -> fail ; N > Max).
853redirect_loop(Parts, Options) :-
854 option(visited(Visited), Options, []),
855 include(==(Parts), Visited, Same),
856 length(Same, Count),
857 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.
869redirect_options(Parts, RedirectedParts, Options0, Options) :- 870 select_option(unix_socket(_), Options0, Options1), 871 memberchk(host(Host), Parts), 872 memberchk(host(RHost), RedirectedParts), 873 debug(http(redirect), 'http_open: redirecting AF_UNIX ~w to ~w', 874 [Host, RHost]), 875 Host \== RHost, 876 !, 877 redirect_options(Options1, Options). 878redirect_options(_, _, Options0, Options) :- 879 redirect_options(Options0, Options). 880 881redirect_options(Options0, Options) :- 882 ( select_option(post(_), Options0, Options1) 883 -> true 884 ; Options1 = Options0 885 ), 886 ( select_option(method(Method), Options1, Options), 887 \+ redirect_method(Method) 888 -> true 889 ; Options = Options1 890 ). 891 892redirect_method(delete). 893redirect_method(get). 894redirect_method(head).
904map_error_code(401, permission_error). 905map_error_code(403, permission_error). 906map_error_code(404, existence_error). 907map_error_code(405, permission_error). 908map_error_code(407, permission_error). 909map_error_code(410, existence_error). 910 911redirect_code(301). % Moved Permanently 912redirect_code(302). % Found (previously "Moved Temporary") 913redirect_code(303). % See Other 914redirect_code(307). % Temporary Redirect 915 916authenticate_code(401).
929open_socket(Address, StreamPair, Options) :- 930 debug(http(open), 'http_open: Connecting to ~p ...', [Address]), 931 tcp_connect(Address, StreamPair, Options), 932 stream_pair(StreamPair, In, Out), 933 debug(http(open), '\tok ~p ---> ~p', [In, Out]), 934 set_stream(In, record_position(false)), 935 ( option(timeout(Timeout), Options) 936 -> set_stream(In, timeout(Timeout)) 937 ; true 938 ). 939 940 941return_version(Options, Major-Minor) :- 942 option(version(Major-Minor), Options, _). 943 944return_size(Options, Headers) :- 945 ( memberchk(content_length(Size), Headers) 946 -> option(size(Size), Options, _) 947 ; true 948 ). 949 950return_fields([], _). 951return_fields([header(Name, Value)|T], Headers) :- 952 !, 953 ( Term =.. [Name,Value], 954 memberchk(Term, Headers) 955 -> true 956 ; Value = '' 957 ), 958 return_fields(T, Headers). 959return_fields([_|T], Lines) :- 960 return_fields(T, Lines). 961 962return_headers(Options, Headers) :- 963 option(headers(Headers), Options, _).
headers(-List)
option. Invalid
header lines are skipped, printing a warning using
pring_message/2.971parse_headers([], []) :- !. 972parse_headers([Line|Lines], Headers) :- 973 catch(http_parse_header(Line, [Header]), Error, true), 974 ( var(Error) 975 -> Headers = [Header|More] 976 ; print_message(warning, Error), 977 Headers = More 978 ), 979 parse_headers(Lines, More).
final_url(URL)
, unify URL with the final
URL after redirections.987return_final_url(Options) :- 988 option(final_url(URL), Options), 989 var(URL), 990 !, 991 option(visited([Parts|_]), Options), 992 parts_uri(Parts, URL). 993return_final_url(_).
1005transfer_encoding_filter(Lines, In0, In) :- 1006 transfer_encoding(Lines, Encoding), 1007 !, 1008 transfer_encoding_filter_(Encoding, In0, In). 1009transfer_encoding_filter(Lines, In0, In) :- 1010 content_encoding(Lines, Encoding), 1011 content_type(Lines, Type), 1012 \+ http:disable_encoding_filter(Type), 1013 !, 1014 transfer_encoding_filter_(Encoding, In0, In). 1015transfer_encoding_filter(_, In, In). 1016 1017transfer_encoding_filter_(Encoding, In0, In) :- 1018 stream_pair(In0, In1, Out), 1019 ( nonvar(Out) 1020 -> close(Out) 1021 ; true 1022 ), 1023 ( http:encoding_filter(Encoding, In1, In) 1024 -> true 1025 ; autoload_encoding(Encoding), 1026 http:encoding_filter(Encoding, In1, In) 1027 -> true 1028 ; domain_error(http_encoding, Encoding) 1029 ). 1030 1031:- multifile 1032 autoload_encoding/1. 1033 1034:- if(exists_source(library(zlib))). 1035autoload_encoding(gzip) :- 1036 use_module(library(zlib)). 1037:- endif. 1038 1039content_type(Lines, Type) :- 1040 member(Line, Lines), 1041 phrase(field('content-type'), Line, Rest), 1042 !, 1043 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.1051httpdisable_encoding_filter('application/x-gzip'). 1052httpdisable_encoding_filter('application/x-tar'). 1053httpdisable_encoding_filter('x-world/x-vrml'). 1054httpdisable_encoding_filter('application/zip'). 1055httpdisable_encoding_filter('application/x-gzip'). 1056httpdisable_encoding_filter('application/x-zip-compressed'). 1057httpdisable_encoding_filter('application/x-compress'). 1058httpdisable_encoding_filter('application/x-compressed'). 1059httpdisable_encoding_filter('application/x-spoon').
Transfer-encoding
header.1066transfer_encoding(Lines, Encoding) :- 1067 what_encoding(transfer_encoding, Lines, Encoding). 1068 1069what_encoding(What, Lines, Encoding) :- 1070 member(Line, Lines), 1071 phrase(encoding_(What, Debug), Line, Rest), 1072 !, 1073 atom_codes(Encoding, Rest), 1074 debug(http(What), '~w: ~p', [Debug, Rest]). 1075 1076encoding_(content_encoding, 'Content-encoding') --> 1077 field('content-encoding'). 1078encoding_(transfer_encoding, 'Transfer-encoding') --> 1079 field('transfer-encoding').
Content-encoding
header.
1086content_encoding(Lines, Encoding) :-
1087 what_encoding(content_encoding, Lines, Encoding).
Invalid reply header
.
1106read_header(In, Parts, Major-Minor, Code, Comment, Lines) :- 1107 read_line_to_codes(In, Line), 1108 ( Line == end_of_file 1109 -> parts_uri(Parts, Uri), 1110 existence_error(http_reply,Uri) 1111 ; true 1112 ), 1113 Line \== end_of_file, 1114 phrase(first_line(Major-Minor, Code, Comment), Line), 1115 debug(http(open), 'HTTP/~d.~d ~w ~w', [Major, Minor, Code, Comment]), 1116 read_line_to_codes(In, Line2), 1117 rest_header(Line2, In, Lines), 1118 !, 1119 ( debugging(http(open)) 1120 -> forall(member(HL, Lines), 1121 debug(http(open), '~s', [HL])) 1122 ; true 1123 ). 1124read_header(_, _, 1-1, 500, 'Invalid reply header', []). 1125 1126rest_header([], _, []) :- !. % blank line: end of header 1127rest_header(L0, In, [L0|L]) :- 1128 read_line_to_codes(In, L1), 1129 rest_header(L1, In, L).
1135content_length(Lines, Length) :- 1136 member(Line, Lines), 1137 phrase(content_length(Length0), Line), 1138 !, 1139 Length = Length0. 1140 1141location(Lines, RequestURI) :- 1142 member(Line, Lines), 1143 phrase(atom_field(location, RequestURI), Line), 1144 !. 1145 1146connection(Lines, Connection) :- 1147 member(Line, Lines), 1148 phrase(atom_field(connection, Connection0), Line), 1149 !, 1150 Connection = Connection0. 1151 1152first_line(Major-Minor, Code, Comment) --> 1153 "HTTP/", integer(Major), ".", integer(Minor), 1154 skip_blanks, 1155 integer(Code), 1156 skip_blanks, 1157 rest(Comment). 1158 1159atom_field(Name, Value) --> 1160 field(Name), 1161 rest(Value). 1162 1163content_length(Len) --> 1164 field('content-length'), 1165 integer(Len). 1166 1167field(Name) --> 1168 { atom_codes(Name, Codes) }, 1169 field_codes(Codes). 1170 1171field_codes([]) --> 1172 ":", 1173 skip_blanks. 1174field_codes([H|T]) --> 1175 [C], 1176 { match_header_char(H, C) 1177 }, 1178 field_codes(T). 1179 1180match_header_char(C, C) :- !. 1181match_header_char(C, U) :- 1182 code_type(C, to_lower(U)), 1183 !. 1184match_header_char(0'_, 0'-). 1185 1186 1187skip_blanks --> 1188 [C], 1189 { code_type(C, white) 1190 }, 1191 !, 1192 skip_blanks. 1193skip_blanks --> 1194 [].
1200integer(Code) --> 1201 digit(D0), 1202 digits(D), 1203 { number_codes(Code, [D0|D]) 1204 }. 1205 1206digit(C) --> 1207 [C], 1208 { code_type(C, digit) 1209 }. 1210 1211digits([D0|D]) --> 1212 digit(D0), 1213 !, 1214 digits(D). 1215digits([]) --> 1216 [].
1222rest(Atom) --> call(rest_(Atom)). 1223 1224rest_(Atom, L, []) :- 1225 atom_codes(Atom, L). 1226 1227 1228 /******************************* 1229 * AUTHORIZATION MANAGEMENT * 1230 *******************************/
-
, possibly defined
authorization is cleared. For example:
?- http_set_authorization('http://www.example.com/private/', basic('John', 'Secret'))
1246:- dynamic 1247 stored_authorization/2, 1248 cached_authorization/2. 1249 1250http_set_authorization(URL, Authorization) :- 1251 must_be(atom, URL), 1252 retractall(stored_authorization(URL, _)), 1253 ( Authorization = (-) 1254 -> true 1255 ; check_authorization(Authorization), 1256 assert(stored_authorization(URL, Authorization)) 1257 ), 1258 retractall(cached_authorization(_,_)). 1259 Var) (:- 1261 var(Var), 1262 !, 1263 instantiation_error(Var). 1264check_authorization(basic(User, Password)) :- 1265 must_be(atom, User), 1266 must_be(text, Password). 1267check_authorization(digest(User, Password)) :- 1268 must_be(atom, User), 1269 must_be(text, Password).
1277authorization(_, _) :- 1278 \+ stored_authorization(_, _), 1279 !, 1280 fail. 1281authorization(URL, Authorization) :- 1282 cached_authorization(URL, Authorization), 1283 !, 1284 Authorization \== (-). 1285authorization(URL, Authorization) :- 1286 ( stored_authorization(Prefix, Authorization), 1287 sub_atom(URL, 0, _, _, Prefix) 1288 -> assert(cached_authorization(URL, Authorization)) 1289 ; assert(cached_authorization(URL, -)), 1290 fail 1291 ). 1292 _, Options, Options) (:- 1294 option(authorization(_), Options), 1295 !. 1296add_authorization(Parts, Options0, Options) :- 1297 url_part(user(User), Parts), 1298 url_part(password(Passwd), Parts), 1299 !, 1300 Options = [authorization(basic(User,Passwd))|Options0]. 1301add_authorization(Parts, Options0, Options) :- 1302 stored_authorization(_, _) -> % quick test to avoid work 1303 parts_uri(Parts, URL), 1304 authorization(URL, Auth), 1305 !, 1306 Options = [authorization(Auth)|Options0]. 1307add_authorization(_, Options, Options).
1315parse_url_ex(URL, [uri(URL)|Parts]) :- 1316 uri_components(URL, Components), 1317 phrase(components(Components), Parts), 1318 ( option(host(_), Parts) 1319 -> true 1320 ; domain_error(url, URL) 1321 ). 1322 1323components(Components) --> 1324 uri_scheme(Components), 1325 uri_path(Components), 1326 uri_authority(Components), 1327 uri_request_uri(Components). 1328 1329uri_scheme(Components) --> 1330 { uri_data(scheme, Components, Scheme), nonvar(Scheme) }, 1331 !, 1332 [ scheme(Scheme) 1333 ]. 1334uri_scheme(_) --> []. 1335 1336uri_path(Components) --> 1337 { uri_data(path, Components, Path0), nonvar(Path0), 1338 ( Path0 == '' 1339 -> Path = (/) 1340 ; Path = Path0 1341 ) 1342 }, 1343 !, 1344 [ path(Path) 1345 ]. 1346uri_path(_) --> []. 1347 Components) (--> 1349 { uri_data(authority, Components, Auth), nonvar(Auth), 1350 !, 1351 uri_authority_components(Auth, Data) 1352 }, 1353 [ authority(Auth) ], 1354 auth_field(user, Data), 1355 auth_field(password, Data), 1356 auth_field(host, Data), 1357 auth_field(port, Data). 1358uri_authority(_) --> []. 1359 1360auth_field(Field, Data) --> 1361 { uri_authority_data(Field, Data, EncValue), nonvar(EncValue), 1362 !, 1363 ( atom(EncValue) 1364 -> uri_encoded(query_value, Value, EncValue) 1365 ; Value = EncValue 1366 ), 1367 Part =.. [Field,Value] 1368 }, 1369 [ Part ]. 1370auth_field(_, _) --> []. 1371 1372uri_request_uri(Components) --> 1373 { uri_data(path, Components, Path0), 1374 uri_data(search, Components, Search), 1375 ( Path0 == '' 1376 -> Path = (/) 1377 ; Path = Path0 1378 ), 1379 uri_data(path, Components2, Path), 1380 uri_data(search, Components2, Search), 1381 uri_components(RequestURI, Components2) 1382 }, 1383 [ request_uri(RequestURI) 1384 ].
1392parts_scheme(Parts, Scheme) :- 1393 url_part(scheme(Scheme), Parts), 1394 !. 1395parts_scheme(Parts, Scheme) :- % compatibility with library(url) 1396 url_part(protocol(Scheme), Parts), 1397 !. 1398parts_scheme(_, http). 1399 1400parts_authority(Parts, Auth) :- 1401 url_part(authority(Auth), Parts), 1402 !. 1403parts_authority(Parts, Auth) :- 1404 url_part(host(Host), Parts, _), 1405 url_part(port(Port), Parts, _), 1406 url_part(user(User), Parts, _), 1407 url_part(password(Password), Parts, _), 1408 uri_authority_components(Auth, 1409 uri_authority(User, Password, Host, Port)). 1410 1411parts_request_uri(Parts, RequestURI) :- 1412 option(request_uri(RequestURI), Parts), 1413 !. 1414parts_request_uri(Parts, RequestURI) :- 1415 url_part(path(Path), Parts, /), 1416 ignore(parts_search(Parts, Search)), 1417 uri_data(path, Data, Path), 1418 uri_data(search, Data, Search), 1419 uri_components(RequestURI, Data). 1420 1421parts_search(Parts, Search) :- 1422 option(query_string(Search), Parts), 1423 !. 1424parts_search(Parts, Search) :- 1425 option(search(Fields), Parts), 1426 !, 1427 uri_query_components(Search, Fields). 1428 1429 1430parts_uri(Parts, URI) :- 1431 option(uri(URI), Parts), 1432 !. 1433parts_uri(Parts, URI) :- 1434 parts_scheme(Parts, Scheme), 1435 ignore(parts_authority(Parts, Auth)), 1436 parts_request_uri(Parts, RequestURI), 1437 uri_components(RequestURI, Data), 1438 uri_data(scheme, Data, Scheme), 1439 uri_data(authority, Data, Auth), 1440 uri_components(URI, Data). 1441 1442parts_port(Parts, Port) :- 1443 parts_scheme(Parts, Scheme), 1444 default_port(Scheme, DefPort), 1445 url_part(port(Port), Parts, DefPort). 1446 1447url_part(Part, Parts) :- 1448 Part =.. [Name,Value], 1449 Gen =.. [Name,RawValue], 1450 option(Gen, Parts), 1451 !, 1452 Value = RawValue. 1453 1454url_part(Part, Parts, Default) :- 1455 Part =.. [Name,Value], 1456 Gen =.. [Name,RawValue], 1457 ( option(Gen, Parts) 1458 -> Value = RawValue 1459 ; Value = Default 1460 ). 1461 1462 1463 /******************************* 1464 * COOKIES * 1465 *******************************/ 1466 Out, Parts, Options) (:- 1468 http:write_cookies(Out, Parts, Options), 1469 !. 1470write_cookies(_, _, _). 1471 _, _, _) (:- 1473 predicate_property(http:update_cookies(_,_,_), number_of_clauses(0)), 1474 !. 1475update_cookies(Lines, Parts, Options) :- 1476 ( member(Line, Lines), 1477 phrase(atom_field('set_cookie', CookieData), Line), 1478 http:update_cookies(CookieData, Parts, Options), 1479 fail 1480 ; true 1481 ). 1482 1483 1484 /******************************* 1485 * OPEN ANY * 1486 *******************************/ 1487 1488:- multifile iostream:open_hook/6.
http
and
https
URLs for Mode == read
.1496iostreamopen_hook(URL, read, Stream, Close, Options0, Options) :- 1497 (atom(URL) -> true ; string(URL)), 1498 uri_is_global(URL), 1499 uri_components(URL, Components), 1500 uri_data(scheme, Components, Scheme), 1501 http_scheme(Scheme), 1502 !, 1503 Options = Options0, 1504 Close = close(Stream), 1505 http_open(URL, Stream, Options0). 1506 1507http_scheme(http). 1508http_scheme(https). 1509 1510 1511 /******************************* 1512 * KEEP-ALIVE * 1513 *******************************/
1519consider_keep_alive(Lines, Parts, Host, StreamPair, In, Options) :- 1520 option(connection(Asked), Options), 1521 keep_alive(Asked), 1522 connection(Lines, Given), 1523 keep_alive(Given), 1524 content_length(Lines, Bytes), 1525 !, 1526 stream_pair(StreamPair, In0, _), 1527 connection_address(Host, Parts, HostPort), 1528 debug(http(connection), 1529 'Keep-alive to ~w (~D bytes)', [HostPort, Bytes]), 1530 stream_range_open(In0, In, 1531 [ size(Bytes), 1532 onclose(keep_alive(StreamPair, HostPort)) 1533 ]). 1534consider_keep_alive(_, _, _, Stream, Stream, _). 1535 1536connection_address(Host, _, Host) :- 1537 Host = _:_, 1538 !. 1539connection_address(Host, Parts, Host:Port) :- 1540 parts_port(Parts, Port). 1541 1542keep_alive(keep_alive) :- !. 1543keep_alive(Connection) :- 1544 downcase_atom(Connection, 'keep-alive'). 1545 1546:- public keep_alive/4. 1547 1548keep_alive(StreamPair, Host, _In, 0) :- 1549 !, 1550 debug(http(connection), 'Adding connection to ~p to pool', [Host]), 1551 add_to_pool(Host, StreamPair). 1552keep_alive(StreamPair, Host, In, Left) :- 1553 Left < 100, 1554 debug(http(connection), 'Reading ~D left bytes', [Left]), 1555 read_incomplete(In, Left), 1556 add_to_pool(Host, StreamPair), 1557 !. 1558keep_alive(StreamPair, _, _, _) :- 1559 debug(http(connection), 1560 'Closing connection due to excessive unprocessed input', []), 1561 ( debugging(http(connection)) 1562 -> catch(close(StreamPair), E, 1563 print_message(warning, E)) 1564 ; close(StreamPair, [force(true)]) 1565 ).
1572read_incomplete(In, Left) :- 1573 catch(setup_call_cleanup( 1574 open_null_stream(Null), 1575 copy_stream_data(In, Null, Left), 1576 close(Null)), 1577 _, 1578 fail). 1579 1580:- dynamic 1581 connection_pool/4, % Hash, Address, Stream, Time 1582 connection_gc_time/1. 1583 1584add_to_pool(Address, StreamPair) :- 1585 keep_connection(Address), 1586 get_time(Now), 1587 term_hash(Address, Hash), 1588 assertz(connection_pool(Hash, Address, StreamPair, Now)). 1589 1590get_from_pool(Address, StreamPair) :- 1591 term_hash(Address, Hash), 1592 retract(connection_pool(Hash, Address, StreamPair, _)).
1601keep_connection(Address) :- 1602 close_old_connections(2), 1603 predicate_property(connection_pool(_,_,_,_), number_of_clauses(C)), 1604 C =< 10, 1605 term_hash(Address, Hash), 1606 aggregate_all(count, connection_pool(Hash, Address, _, _), Count), 1607 Count =< 2. 1608 1609close_old_connections(Timeout) :- 1610 get_time(Now), 1611 Before is Now - Timeout, 1612 ( connection_gc_time(GC), 1613 GC > Before 1614 -> true 1615 ; ( retractall(connection_gc_time(_)), 1616 asserta(connection_gc_time(Now)), 1617 connection_pool(Hash, Address, StreamPair, Added), 1618 Added < Before, 1619 retract(connection_pool(Hash, Address, StreamPair, Added)), 1620 debug(http(connection), 1621 'Closing inactive keep-alive to ~p', [Address]), 1622 close(StreamPair, [force(true)]), 1623 fail 1624 ; true 1625 ) 1626 ).
http_close_keep_alive(_)
closes all currently known keep-alive connections.
1635http_close_keep_alive(Address) :-
1636 forall(get_from_pool(Address, StreamPair),
1637 close(StreamPair, [force(true)])).
1646keep_alive_error(keep_alive(closed)) :- 1647 !, 1648 debug(http(connection), 'Keep-alive connection was closed', []), 1649 fail. 1650keep_alive_error(io_error(_,_)) :- 1651 !, 1652 debug(http(connection), 'IO error on Keep-alive connection', []), 1653 fail. 1654keep_alive_error(Error) :- 1655 throw(Error). 1656 1657 1658 /******************************* 1659 * HOOK DOCUMENTATION * 1660 *******************************/
:- 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 a 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.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.
An example query is below:
Content-Type
header. */