1/*  File:    swi/paxos.pl
    2    Author:  Roy Ratcliffe
    3    WWW:     https://github.com/royratcliffe
    4    Created: Jun 12 2021
    5    Purpose: SWI Paxos
    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(swi_paxos,
   31          [ paxos_quorum_nodes/1,               % -Nodes:list(nonneg)
   32            paxos_quorum_nth1/1                 % ?Nth1
   33          ]).   34:- autoload(library(lists), [nth1/3]).   35:- autoload(library(paxos), [paxos_property/1]).   36:- use_module(library(canny/pop)).
 paxos_quorum_nodes(-Nodes:list(nonneg)) is semidet
Nodes is a list of Paxos consensus nodes who are members of the quorum. Fails if Paxos not yet initialised.
Arguments:
Nodes- is a list of node indices in low-to-high order.
   45paxos_quorum_nodes(Nodes) :-
   46    paxos_property(quorum(Quorum)),
   47    pop_lsbs(Quorum, Nodes).
 paxos_quorum_nth1(?Nth1:nonneg) is semidet
Unifies Nth1 with the order of this node within the quorum. Answers 1 if this node comes first in the known quorum of consensus nodes, for example.
   55paxos_quorum_nth1(Nth1) :-
   56    paxos_property(node(Node)),
   57    paxos_quorum_nodes(Nodes),
   58    once(nth1(Nth1, Nodes, Node))