1:- module(amazon_api, [ build_agent/2
    2                      , item_lookup/3
    3                      , item_lookup/4
    4                      , request/5
    5
    6                      , offer_inventory/3
    7                      , offer_low_price/3
    8                      , title/2
    9                      ]).   10
   11:- use_module(library(base64), [base64/2]).   12:- use_module(library(error), [existence_error/2]).   13:- use_module(library(func)).   14:- use_module(library(http/http_open), [http_open/3]).   15:- use_module(library(sha), [hmac_sha/4]).   16:- use_module(library(uri), [uri_encoded/3]).   17:- use_module(library(uri_qq)).   18:- use_module(library(xpath)).
 build_agent(-Agent, +Args:dict)
Build an Agent which is used for making Amazon API requests. Args should contain at least the following keys (obtained from Amazon):

It may include an optional host key which defaults to "webservices.amazon.com".

   32build_agent(Agent,Args) :-
   33    must_have(Args, associate_tag, string, Tag),
   34    must_have(Args, access_key, string, AccessKey),
   35    must_have(Args, secret_key, string, SecretKey),
   36    once( get_dict(host, Args, Host)
   37        ; Host = "webservices.amazon.com"
   38        ),
   39    Agent = agent(Host,Tag,AccessKey,SecretKey).
   40
   41must_have(Args,Key,Type,Value) :-
   42    once( get_dict(Key, Args, Value)
   43        ; existence_error(Type, Key)
   44        ).
   45
   46
   47% private accessors for agent components
   48agent_host(agent(Host,_,_,_),Host).
   49agent_tag(agent(_,Tag,_,_),Tag).
   50agent_key(agent(_,_,Key,_),Key).
   51agent_secret(agent(_,_,_,Secret),Secret).
 item_lookup(+Agent, +Asin:string, -Item, +Args:dict)
Perform an "ItemLookup" call using Amazon's Product Advertising API. Additional API arguments are passed via Args. A common use case is to specify response groups:
item_lookup(Agent,'B00004TN1Z',Item, _{'ResponseGroup':"Offers"}).
   63item_lookup(Agent, Asin, Item, Args0) :-
   64    Args = Args0.put(_{ 'ItemId' : Asin
   65                      , 'IdType' : "ASIN"
   66                      }),
   67    request(Agent, get, "ItemLookup", Item, Args).
 item_lookup(+Agent, +Asin:string, -Item)
Like item_lookup/4 with no arguments.
   72item_lookup(Agent,Asin,Item) :-
   73    item_lookup(Agent,Asin,Item,_{}).
   74
   75
   76%% request(+Agent,+Method:atom,+Operation:string,-Result,+Args:dict)
   77%
   78%  Low level predicate for performing Amazon API requests. Executes
   79%  Operation using HTTP Method.  API arguments are provided in
   80%  Args. On success, a parsed representation of the response XML
   81%  is bound to Result. See library(sgml) for the format.
   82%
   83%  library(xpath) is helpful for extracting details from Result if
   84%  there's not already a helper predicate to handle it.
   85request(Agent, Method, Operation, Result, Args0) :-
   86    agent_tag(Agent, Tag),
   87    agent_key(Agent, Key),
   88    Args1 = Args0.put([ 'Service' = "AWSECommerceService"
   89                      , 'Version' = "2011-08-01"
   90                      , 'Operation' = Operation
   91                      , 'AWSAccessKeyId' = Key
   92                      , 'AssociateTag' = Tag
   93                      ]),
   94    sign_request(Agent, Method, Args1, Args),
   95
   96    agent_host(Agent, Host),
   97    Url = {|uri||http://$Host/onca/xml?$Args|},
   98    url_dom(Url, Result).
   99
  100
  101% add timestamp and signature to Args0 giving Args
  102sign_request(Agent, Method, Args0, Args) :-
  103    % what string should we sign?
  104    Args1 = Args0.put('Timestamp', timestamp(~)),
  105    agent_host(Agent, Host),
  106    signable_string(Method, Host, Args1, SignMe),
  107
  108    % perform the signature
  109    agent_secret(Agent, Secret),
  110    hmac_sha(Secret, SignMe, HmacBytes, [algorithm(sha256)]),
  111    base64(string_codes(~,HmacBytes), Signature),
  112    Args = Args1.put('Signature', Signature).
  113
  114
  115% string to be signed to generate request signature
  116signable_string(Method, Host, Args, String) :-
  117    encode_pairs(Args, EncodedPairs),
  118    String = "~s~n~s~n~s~n~s" $ [ upcase_atom $ Method
  119                                , Host
  120                                , "/onca/xml"
  121                                , EncodedPairs
  122                                ].
  123
  124% encode request parameters into Amazon's canonical signature format
  125encode_pairs(Dict, Atom) :-
  126    dict_pairs(Dict, _, Pairs),
  127    keysort(Pairs, Sorted),
  128    maplist(encode_value, Sorted, Encoded),
  129    atomic_list_concat(Encoded, "&", Atom).
  130
  131
  132encode_value(K-V0,String) :-
  133    uri_encode(V0, V),
  134    String = "~s=~s" $ [K,V].
  135
  136
  137% encode URI values as Amazon expects.
  138% uri_encoded/3 doesn't encode comma, :, / or ? characters.
  139uri_encode(Value, Encoded) :-
  140    uri_encoded(query_value, Value, E0),
  141    atom_codes(E0, E1),
  142    once(phrase(enc, E1, E2)),
  143    atom_codes(Encoded, E2).
  144
  145enc, "%2C" --> ",", enc.
  146enc, "%2F" --> "/", enc.
  147enc, "%3A" --> ":", enc.
  148enc, "%3F" --> "?", enc.
  149enc, [C] --> [C], enc.
  150enc --> { true }.
 timestamp(-Timestamp:string) is det
Generate a timestamp compatible with Amazon's API.
  156timestamp(T) :-
  157    get_time(Now),
  158    stamp_date_time(Now, DT, 'UTC'),
  159    format_time(string(T), "%FT%T.000Z", DT).
 url_dom(+Url:atom, -Dom)
True if Dom is the parsed XML content at Url.
  165url_dom(Url, Dom) :-
  166    setup_call_cleanup( http_open(Url, In, [timeout(10)])
  167                      , url_dom_(Dom, In)
  168                      , close(In)
  169                      ).
  170
  171url_dom_(Dom, Stream) :-
  172    load_structure( Stream
  173                  , [Dom|_]
  174                  , [ dialect(xml)
  175                    , max_errors(-1)
  176                    , syntax_errors(quiet)
  177                    ]
  178                  ).
  179
  180
  181%% offer_inventory(+Item,?Condition:atom,-Inventory:integer)
  182%
  183%  Find how many offers in Condition are available. Item is a value
  184%  produced by item_lookup/3, which must include the response group
  185%  "OfferSummary" (directly or indirectly).
  186%
  187%  Condition should be one of `used`, `new` or `collectible`. Leaving
  188%  Condition unbound iterates all conditions on backtracking.
  189offer_inventory(Item, Condition, Inventory) :-
  190    inventory_node(Condition, InventoryNode),
  191    once(xpath(Item, //'OfferSummary'/InventoryNode, Total)),
  192    Total = element(_,_,[InventoryAtom]),
  193    atom_number(InventoryAtom, Inventory).
  194
  195inventory_node(used,        'TotalUsed').
  196inventory_node(new,         'TotalNew').
  197inventory_node(collectible, 'TotalCollectible').
  198
  199
  200%% offer_low_price(+Item, ?Condition, -Pennies:integer)
  201%
  202%  Find the lowest price for an offer in Condition. The price is
  203%  represented as an integer number of pennies, when using US Dollars.
  204%  An equivalent unit is used for other currencies. Item is a value
  205%  produced by item_lookup/3, which must include the response group
  206%  "OfferSummary" (directly or indirectly).
  207%
  208%  Condition should be one of `used`, `new` or `collectible`. Leaving
  209%  Condition unbound iterates all conditions on backtracking.
  210offer_low_price(Item, Condition, Pennies) :-
  211    price_node(Condition, PriceNode),
  212    once(xpath(Item, //'OfferSummary'/PriceNode/'Amount'(text), PriceAtom)),
  213    atom_number(PriceAtom, Pennies).
  214
  215price_node(used,        'LowestUsedPrice').
  216price_node(new,         'LowestNewPrice').
  217price_node(collectible, 'LowestCollectiblePrice').
  218
  219
  220%% title(+Item, -Title:atom) is det.
  221%
  222%  An item's title. Item is a value from item_lookup/3 and requires the
  223%  "ItemAttributes" response group.
  224title(Item, Title) :-
  225    once(xpath(Item, //