1/*  File:    paxos/http_handlers.pl
    2    Author:  Roy Ratcliffe
    3    WWW:     https://github.com/royratcliffe
    4    Created: Jun 12 2021
    5    Purpose: Paxos HTTP Handlers
    6
    7Copyright (c) 2021, Roy Ratcliffe, United Kingdom
    8
    9Permission is hereby granted, free of charge,  to any person obtaining a
   10copy  of  this  software  and    associated   documentation  files  (the
   11"Software"), to deal in  the   Software  without  restriction, including
   12without limitation the rights to  use,   copy,  modify,  merge, publish,
   13distribute, sublicense, and/or sell  copies  of   the  Software,  and to
   14permit persons to whom the Software is   furnished  to do so, subject to
   15the following conditions:
   16
   17    The above copyright notice and this permission notice shall be
   18    included in all copies or substantial portions of the Software.
   19
   20THE SOFTWARE IS PROVIDED "AS IS", WITHOUT  WARRANTY OF ANY KIND, EXPRESS
   21OR  IMPLIED,  INCLUDING  BUT  NOT   LIMITED    TO   THE   WARRANTIES  OF
   22MERCHANTABILITY, FITNESS FOR A PARTICULAR   PURPOSE AND NONINFRINGEMENT.
   23IN NO EVENT SHALL THE AUTHORS  OR   COPYRIGHT  HOLDERS BE LIABLE FOR ANY
   24CLAIM, DAMAGES OR OTHER LIABILITY,  WHETHER   IN  AN ACTION OF CONTRACT,
   25TORT OR OTHERWISE, ARISING FROM,  OUT  OF   OR  IN  CONNECTION  WITH THE
   26SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
   27
   28*/
   29
   30:- module(paxos_http_handlers, []).   31:- autoload(library(paxos),
   32            [ paxos_property/1,
   33              paxos_get/3,
   34              paxos_set/3
   35            ]).   36:- autoload(library(http/http_dispatch), [http_handler/3]).   37:- autoload(library(http/http_json),
   38            [ reply_json/1,
   39              reply_json/2,
   40              http_read_json/2
   41            ]).   42:- autoload(library(http/http_parameters), [http_parameters/2]).   43:- autoload(library(lists), [nth1/3]).   44:- use_module(library(swi/paxos)).

Paxos HTTP Handlers

These handlers spool up a JSON-based HTTP interface to the Paxos predicates, namely

Take the example below. Uses http_server/1 to start a HTTP server on some given port.

?- [library(http/http_server), library(http/http_client)].
true.

?- http_server([port(8080)]).
% Started server at http://localhost:8080/
true.

?- http_get('http://localhost:8080/paxos/properties', A, []).
A = json([node=0, quorum=1, failed=0]).

Getting and setting using JSON encoding works as follows.

?- http_get('http://localhost:8080/paxos/hello', A, [status_code(B)]).
A = '',
B = 204.

?- http_post('http://localhost:8080/paxos/hello', json(world), A, []).
A = @true.

?- http_get('http://localhost:8080/paxos/hello', A, [status_code(B)]).
A = world,
B = 200.

Note that the initial GET fails. It replies with the empty atom since no content exists. Predicate paxos_get/2 is semi-deterministic; it can fail. Empty atom is not valid Prolog-encoding for JSON. Status code of 204 indicates no content. The Paxos ledger does not contain data for that key.

Thereafter, POST writes a string value for the key and a repeated GET attempt now answers the new consensus data. Status code 200 indicates a successful ledger concensus.

Serialisation

Serialises unknowns. Paxos ledgers may contain non-JSON compatible data. Anything that does not correctly serialise as JSON becomes an atomicly rendered Prolog term. Take a consensus value of term a(1) for example; GET requests see "a(1)" as a rendered Prolog string. The ledger comprises Prolog terms, fundamentally, rather than JSON-encoded strings.

Setting a Paxos value reads JSON from the POST request body. It can be any valid JSON value including atomic values as well as objects and arrays.

*/

  109:- http_handler(root(paxos/properties), properties, []).  110:- http_handler(root(paxos/Key), key(Method, Key),
  111                [ method(Method),
  112                  methods([get, post])
  113                ]).  114:- http_handler(root(paxos/quorum), quorum, []).
 properties(+Request) is semidet
Paxos properties request. The paxos_property/1 predicate answers terms non-deterministically. Finds all the terms and relies on the JSON serialiser to convert the node, quorum and failed terms to correct JSON object key-value pairs. The JSON serialiser accepts one-arity functors as pairs.
  124properties(_) :-
  125    findall(Property, paxos_property(Property), Properties),
  126    reply_json(json(Properties)).
 key(+Method, +Key, +Request) is semidet
By design, the GET method reply represents failure as a no-content status-204 response. This serves to disambiguate between a fail response and a successful false response. JSON of false is a valid quorum ledger data value, as in this example.
?- http_post('http://localhost:8080/paxos/hello',
             json(@false), A, [status_code(B)]).
A = @true,
B = 200.

The POST method simply replies true or false in JSON when paxos_set/2 succeeds or fails respectively.

Also note that Paxos gets and sets are not instantaneous. Getting a key's value involves communication with the quorum since the enquiring node does not necessarily carry the key at first.

  149key(get, Key, Request) :-
  150    request_options(Request, Options),
  151    (   paxos_get(Key, Data, Options)
  152    ->  reply_json(Data, [serialize_unknown(true)])
  153    ;   throw(http_reply(no_content))
  154    ).
  155key(post, Key, Request) :-
  156    http_read_json(Request, Data),
  157    request_options(Request, Options),
  158    (   paxos_set(Key, Data, Options)
  159    ->  Reply = true
  160    ;   Reply = false
  161    ),
  162    reply_json(@(Reply)).
 request_options(+Request, -Options) is det
Finds HTTP Request parameters:

Seconds must be in-between one millisecond and 10 seconds. These arbitrary limits intend to strike a reasonable balance between resource usages.

  175request_options(Request, Options) :-
  176    findall(Option, request_option(Request, Option), Options).
  177
  178request_option(Request, retry(Retries)) :-
  179    http_parameters(Request,
  180                    [retry(Retries, [nonneg, optional(true)])]),
  181    nonvar(Retries).
  182request_option(Request, timeout(Seconds)) :-
  183    http_parameters(Request,
  184                    [ timeout(Seconds,
  185                              [ between(0.001, 10),
  186                                optional(true)
  187                              ])
  188                    ]),
  189    nonvar(Seconds).
  190
  191quorum(_) :-
  192    paxos_property(node(Node)),
  193    paxos_quorum_nodes(Nodes),
  194    once(nth1(Nth1, Nodes, Node)),
  195    reply_json(json([nodes=Nodes, nth1=Nth1]))