1:- module(
    2  nb_ext,
    3  [
    4    nb_increment/2, % +State, +Index
    5    nb_increment/3, % +State, +Index, -Value
    6    nb_plus/3,      % +State, +Index, +Increment
    7    nb_plus/4       % +State, +Index, +Increment, -Value
    8  ]
    9).

Non-backtracking support

Extended support for non-backtracking behavior.

*/

   17:- use_module(library(clpfd)).
 nb_increment(+State:compound, +Index:positive_integer) is det
   23nb_increment(State, Index) :-
   24  nb_increment(State, Index, _).
 nb_increment(+State:compound, +Index:positive_integer, -Value:nonneg) is det
   29nb_increment(State, Index, Value) :-
   30  nb_plus(State, Index, 1, Value).
 nb_plus(+State:compound, +Index:positive_integer, +Increment:number) is det
   36nb_plus(State, Index, Increment) :-
   37  nb_plus(State, Index, Increment, _).
   38
   39
   40%! nb_plus(+State:compound,
   41%!         +Index:positive_integer,
   42%!         +Increment:number,
   43%!         -Value:nonneg) is det.
   44
   45nb_plus(State, Index, Increment, Value1) :-
   46  arg(Index, State, Value1),
   47  Value2