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:
- library(http/http_ssl_plugin)
- Loading this library causes http_open/3 to handle HTTPS connections.
Relevant options for SSL certificate handling are handed to
ssl_context/3. This plugin is loaded automatically if the scheme
https
is requested using a default SSL context. See the plugin for
additional information regarding security.
- library(zlib)
- Loading this library supports the
gzip
transfer encoding. This
plugin is lazily loaded if a connection is opened that claims this
transfer encoding.
- library(http/http_cookie)
- Loading this library adds tracking cookies to http_open/3. Returned
cookies are collected in the Prolog database and supplied for
subsequent requests.
- library(http/http_stream)
- This library adds support for chunked encoding and makes the
http_open/3 advertise itself as HTTP/1.1 instead of HTTP/1.0.
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
...
- See also
- - load_html/3 and xpath/3 can be used to parse and navigate HTML
documents.
- - http_get/3 and http_post/4 provide an alternative interface that
convert the reply depending on the
Content-Type
header.
- http_open(+URL, -Stream, +Options) is det
- Open the data at the HTTP server as a Prolog stream. URL is
either an atom specifying a URL or a list representing a
broken-down URL as specified below. After this predicate
succeeds the data can be read from Stream. After completion this
stream must be closed using the built-in Prolog predicate
close/1. Options provides additional options:
- authenticate(+Boolean)
- If
false
(default true
), do not try to automatically
authenticate the client if a 401 (Unauthorized) status code
is received.
- authorization(+Term)
- Send authorization. See also http_set_authorization/2. Supported
schemes:
- basic(+User, +Password)
- HTTP Basic authentication.
- bearer(+Token)
- HTTP Bearer authentication.
- digest(+User, +Password)
- HTTP Digest authentication. This option is only provided
if the plugin library(http/http_digest) is also loaded.
- unix_socket(+Path)
- Connect to the given Unix domain socket. In this scenario
the host name and port or ignored. If the server replies
with a redirect message and the host differs from the
original host as normal TCP connection is used to handle
the redirect. This option is inspired by
curl(1)
's option
`--unix-socket`.
- connection(+Connection)
- Specify the
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.
- final_url(-FinalURL)
- Unify FinalURL with the final destination. This differs from
the original URL if the returned head of the original
indicates an HTTP redirect (codes 301, 302 or 303). Without a
redirect, FinalURL is the same as URL if URL is an atom, or a
URL constructed from the parts.
- header(Name, -AtomValue)
- If provided, AtomValue is unified with the value of the
indicated field in the reply header. Name is matched
case-insensitive and the underscore (_) matches the hyphen
(-). Multiple of these options may be provided to extract
multiple header fields. If the header is not available
AtomValue is unified to the empty atom ('').
- headers(-List)
- If provided, List is unified with a list of Name(Value) pairs
corresponding to fields in the reply header. Name and Value
follow the same conventions used by the
header(Name,Value)
option.
- method(+Method)
- One of
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
.
- size(-Size)
- Size is unified with the integer value of
Content-Length
in the reply header.
- version(-Version)
- Version is a pair
Major-Minor
, where Major and Minor
are integers representing the HTTP version in the reply header.
- range(+Range)
- Ask for partial content. Range is a term Unit(From,To),
where From is an integer and To is either an integer or
the atom
end
. HTTP 1.1 only supports Unit = bytes
. E.g.,
to ask for bytes 1000-1999, use the option
range(bytes(1000,1999))
- redirect(+Boolean)
- If
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.
- status_code(-Code)
- If this option is present and Code unifies with the HTTP
status code, do not translate errors (4xx, 5xx) into an
exception. Instead, http_open/3 behaves as if 2xx (success) is
returned, providing the application to read the error document
from the returned stream.
- output(-Out)
- Unify the output stream with Out and do not close it. This can
be used to upgrade a connection.
- timeout(+Timeout)
- If provided, set a timeout on the stream using set_stream/2.
With this option if no new data arrives within Timeout seconds
the stream raises an exception. Default is to wait forever
(
infinite
).
- post(+Data)
- Issue a
POST
request on the HTTP server. Data is
handed to http_post_data/3.
- proxy(+Host:Port)
- Use an HTTP proxy to connect to the outside world. See also
socket:proxy_for_url/3. This option overrules the proxy
specification defined by socket:proxy_for_url/3.
- proxy(+Host, +Port)
- Synonym for
proxy(+Host:Port)
. Deprecated.
- proxy_authorization(+Authorization)
- Send authorization to the proxy. Otherwise the same as the
authorization
option.
- bypass_proxy(+Boolean)
- If
true
, bypass proxy hooks. Default is false
.
- request_header(Name=Value)
- Additional name-value parts are added in the order of
appearance to the HTTP request header. No interpretation is
done.
- max_redirect(+Max)
- Sets the maximum length of a redirection chain. This is needed
for some IRIs that redirect indefinitely to other IRIs without
looping (e.g., redirecting to IRIs with a random element in them).
Max must be either a non-negative integer or the atom
infinite
.
The default value is 10
.
- user_agent(+Agent)
- Defines the value of the
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.
- Arguments:
-
URL | - is either an atom or string (url) or a list of parts.
When provided, this list may contain the fields
scheme , user , password , host , port , path
and either query_string (whose argument is an atom)
or search (whose argument is a list of
Name(Value) or Name=Value compound terms).
Only host is mandatory. The example below opens the
URL http://www.example.com/my/path?q=Hello%20World&lang=en .
Note that values must not be quoted because the
library inserts the required quotes.
http_open([ host('www.example.com'),
path('/my/path'),
search([ q='Hello world',
lang=en
])
])
|
- throws
- -
error(existence_error(url, Id),Context)
is raised if the
HTTP result code is not in the range 200..299. Context has the
shape context(Message, status(Code, TextCode))
, where Code is the
numeric HTTP code and TextCode is the textual description thereof
provided by the server. Message may provide additional details or
may be unbound.
- See also
- - ssl_context/3 for SSL related options if
library(http/http_ssl_plugin) is loaded.
- map_method(+MethodID, -Method)[multifile]
- Support additional
METHOD
keywords. Default are the official
HTTP methods as defined by the various RFCs.
- http:disable_encoding_filter(+ContentType) is semidet[multifile]
- Do not use the
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
- Set user/password to supply with URLs that have URL as prefix.
If Authorization is the atom
-
, possibly defined
authorization is cleared. For example:
?- http_set_authorization('http://www.example.com/private/',
basic('John', 'Secret'))
- To be done
- - Move to a separate module, so http_get/3, etc. can use this
too.
- iostream:open_hook(+Spec, +Mode, -Stream, -Close, +Options0, -Options) is semidet[multifile]
- Hook implementation that makes open_any/5 support
http
and
https
URLs for Mode == read
.
- http_close_keep_alive(+Address) is det
- Close all keep-alive connections matching Address. Address is of
the form Host:Port. In particular,
http_close_keep_alive(_)
closes all currently known keep-alive connections.