
http_open.pl -- HTTP client libraryThis 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.Here is a simple example to fetch a web-page:
?- http_open('http://www.google.com/search?q=prolog', In, []),
copy_stream_data(In, user_output),
close(In).
<!doctype html><head><title>prolog - Google Search</title><script>
...
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.
modified(URL, Stamp) :-
http_open(URL, In,
[ method(head),
header(last_modified, Modified)
]),
close(In),
Modified \== '',
parse_time(Modified, Stamp).
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.
:- use_module(library(http/http_open)).
:- use_module(library(xpath)).
:- use_module(library(sgml)).
:- use_module(library(uri)).
google(For, Title, HREF) :-
uri_encoded(query_value, For, Encoded),
atom_concat('http://www.google.com/search?q=', Encoded, URL),
http_open(URL, In, []),
call_cleanup(
load_html(In, DOM, []),
close(In)),
xpath(DOM, //h3(@class=r), Result),
xpath(Result, //a(@href=HREF0, text), Title),
uri_components(HREF0, Components),
uri_data(search, Components, Query),
uri_query_components(Query, Parts),
memberchk(q=HREF, Parts).
An example query is below:
?- google(prolog, Title, HREF). Title = 'SWI-Prolog', HREF = 'http://www.swi-prolog.org/' ; Title = 'Prolog - Wikipedia', HREF = 'https://nl.wikipedia.org/wiki/Prolog' ; Title = 'Prolog - Wikipedia, the free encyclopedia', HREF = 'https://en.wikipedia.org/wiki/Prolog' ; Title = 'Pro-Log is logistiek dienstverlener m.b.t. vervoer over water.', HREF = 'http://www.pro-log.nl/' ; Title = 'Learn Prolog Now!', HREF = 'http://www.learnprolognow.org/' ; Title = 'Free Online Version - Learn Prolog ...
http_open(+URL, -Stream, +Options) is detfalse (default true), do not try to automatically
authenticate the client if a 401 (Unauthorized) status code
is received.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.
http:disable_encoding_filter(+ContentType) is semidet[multifile]Content-encoding as Transfer-encoding
encoding for specific values of ContentType. This predicate is
multifile and can thus be extended by the user.
http_set_authorization(+URL, +Authorization) is det-, possibly defined
authorization is cleared. For example:
?- http_set_authorization('http://www.example.com/private/',
basic('John', 'Secret'))
iostream:open_hook(+Spec, +Mode, -Stream, -Close, +Options0, -Options) is semidet[multifile]http and
https URLs for Mode == read.
http_close_keep_alive(+Address) is dethttp_close_keep_alive(_)
closes all currently known keep-alive connections.