1:- module(readability_parser, [ build_agent/2
    2                              , parse/3
    3                              , parse/4
    4                              ]).    5
    6:- use_module(library(http/http_open), [http_open/3]).    7:- use_module(library(http/http_ssl_plugin)).    8:- use_module(library(http/json), [json_read_dict/2]).    9:- use_module(library(uri_qq)).
 build_agent(+Token:string, -Agent)
Construct an agent for making API requests using your Readability Parser Token. Your token is available on your account settings page.
   17build_agent(Token, Agent) :-
   18    must_be(string, Token),
   19    agent_token(Agent, Token).
   20
   21% private accessors for agent components
   22agent_token(agent(Token), Token).
 parse(+Agent, +UrlOrId:atom, -Response:dict)
Like parse/4 but without extra options.
   28parse(Agent, UrlOrId, Response) :-
   29    parse(Agent, UrlOrId, Response, _{}).
 parse(+Agent, +UrlOrId:atom, -Response:dict, +Options:dict)
Parse an article with Readability's Parser API. UrlOrId can be either an article's URL or a Readability article ID.

Response is a dict representing Readability's raw response. In most cases, you can just access this dict directly to find what you need.

   39parse(Agent, UrlOrID, Response, Options0) :-
   40    agent_token(Agent, Token),
   41    Options1 = Options0.put(token, Token),
   42
   43    identifier_type(UrlOrID, Type),
   44    Options = Options1.put(Type, UrlOrID),
   45
   46    parse(Options, Response).
   47
   48
   49% heuristic to distinguish URLs from Readability IDs
   50identifier_type(UrlOrId, Type) :-
   51    ( sub_atom(UrlOrId,0,4,_,http) -> Type = url; Type = id ).
   52
   53
   54% make request to Readability
   55parse(Args, Response) :-
   56    Url = {|uri||http://www.readability.com/api/content/v1/parser?$Args|},
   57    setup_call_cleanup( http_open(Url,Stream,[ cert_verify_hook(ssl_verify)
   58                                             , timeout(10)
   59                                             ]
   60                                 )
   61                      , ( set_stream(Stream, encoding(utf8))
   62                        , json_read_dict(Stream, Response)
   63                        )
   64                      , close(Stream)
   65                      ).
   66
   67% accept all SSL certificates
   68ssl_verify( _SSL
   69          , _ProblemCertificate
   70          , _AllCertificates
   71          , _FirstCertificate
   72          , _Error
   73          )