1:- module(web, [
    2    get/2
    3]).    4
    5% our own libraries
    6:- use_module(library(web/response), []).    7
    8% core libraries
    9:- use_module(library(error), [must_be/2]).   10:- use_module(library(http/http_header), []). % support POST, PUT, etc. methods
   11:- use_module(library(http/http_open), [http_open/3]). % make HTTP responses
   12:- use_module(library(http/http_ssl_plugin), []). % support SSL
   13:- use_module(library(http/json), [json_read_dict/3]).  % support JSON
   14:- use_module(library(sgml), [load_structure/3]).  % support HTML parsing
   15
   16:- redefine_system_predicate(get/2).   17
   18:- dynamic cacert_file/1.   19cacert_file(File) :-
   20    absolute_file_name(library('../cacert-web.pem'), File, [access(read)]),
   21    retractall(cacert_file(_)),
   22    assert(cacert_file(File)),
   23    compile_predicates([cacert_file/1]).
   24
   25% let third parties define views on HTTP content
   26:- multifile content_view/2.   27content_view([],_).
   28content_view([View|Views],Response) :-
   29    content_view(View,Response),
   30    content_view(Views,Response).
   31content_view(codes(Codes),Response) :-
   32    response:body(Response,Body),
   33    read_stream_to_codes(Body,Codes).
   34content_view(html5(Dom),Response) :-
   35    response:body(Response,Body),
   36    load_structure(
   37        stream(Body),
   38        [Dom|_],
   39        [
   40            dialect(html5),
   41            shorttag(false),
   42            max_errors(-1),
   43            syntax_errors(quiet)
   44        ]
   45    ).
   46content_view(json(Dict),Response) :-
   47    response:content_type(Response,'application/json'),
   48    response:body(Response,Body),
   49    json_read_dict(Body,Dict,[tag('')]).
   50content_view(status_code(Code),Response) :-
   51    response:status_code(Response,Code).
 get(+Url, -Response) is det
True if an HTTP GET request to Url produces a Response. Url can be an atom, string or list of codes. If Response is an unbound variable, it's unified with a value representing the full HTTP response. See library(response) in this pack for predicates about this value.

Response may also be one of the following:

   68get(UrlText,View) :-
   69    must_be(ground,UrlText),
   70    text_atom(UrlText,Url),
   71    get_(Url,Response),
   72    ( var(View) -> View=Response; content_view(View,Response) ).
   73
   74get_(Url,Response) :-
   75    % make request
   76    cacert_file(CacertFile),
   77    Options = [
   78        method(get),
   79        header(content_type,ContentType),
   80        status_code(StatusCode),
   81        cacert_file(CacertFile)
   82    ],
   83    http_open(Url,Body,Options),
   84
   85    % describe response value
   86    response:exists(Response, [
   87        status_code-StatusCode,
   88        content_type-ContentType,
   89        body-Body
   90    ]).
 text_atom(+Text:text, -Atom:atom) is det
True if Text is represented as an Atom. Text may be a string, an atom or a code list.
   97text_atom(Text,Atom) :-
   98    atom(Text),
   99    !,
  100    Text = Atom.
  101text_atom(Text,Atom) :-
  102    string(Text),
  103    !,
  104    atom_string(Atom,Text).
  105text_atom(Text,Atom) :-
  106    is_list(Text),
  107    !,
  108    atom_codes(Atom,Text)