View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2015-2017, VU University Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(solution_sequences,
   36          [ distinct/1,                 % :Goal
   37            distinct/2,                 % ?Witness, :Goal
   38            reduced/1,                  % :Goal
   39            reduced/3,                  % ?Witness, :Goal, +Options
   40            limit/2,                    % +Limit, :Goal
   41            offset/2,                   % +Offset, :Goal
   42            order_by/2,                 % +Spec, :Goal
   43            group_by/4                  % +By, +Template, :Goal, -Bag
   44          ]).   45:- use_module(library(nb_set)).   46:- use_module(library(error)).   47:- use_module(library(apply)).   48:- use_module(library(lists)).   49:- use_module(library(ordsets)).   50:- use_module(library(option)).

Modify solution sequences

The meta predicates of this library modify the sequence of solutions of a goal. The modifications and the predicate names are based on the classical database operations DISTINCT, LIMIT, OFFSET, ORDER BY and GROUP BY.

These predicates were introduced in the context of the SWISH Prolog browser-based shell, which can represent the solutions to a predicate as a table. Notably wrapping a goal in distinct/1 avoids duplicates in the result table and using order_by/2 produces a nicely ordered table.

However, the predicates from this library can also be used to stay longer within the clean paradigm where non-deterministic predicates are composed from simpler non-deterministic predicates by means of conjunction and disjunction. While evaluating a conjunction, we might want to eliminate duplicates of the first part of the conjunction. Below we give both the classical solution for solving variations of (a(X), b(X)) and the ones using this library side-by-side.

Avoid duplicates of earlier steps
  setof(X, a(X), Xs),               distinct(a(X)),
  member(X, Xs),                    b(X)
  b(X).

Note that the distinct/1 based solution returns the first result of distinct(a(X)) immediately after a/1 produces a result, while the setof/3 based solution will first compute all results of a/1.

Only try b(X) only for the top-10 a(X)
  setof(X, a(X), Xs),               limit(10, order_by([desc(X)], a(X))),
  reverse(Xs, Desc),                b(X)
  first_max_n(10, Desc, Limit),
  member(X, Limit),
  b(X)

Here we see power of composing primitives from this library and staying within the paradigm of pure non-deterministic relational predicates.

See also
- all solution predicates findall/3, bagof/3 and setof/3.
- library(aggregate) */
  103:- meta_predicate
  104    distinct(0),
  105    distinct(?, 0),
  106    reduced(0),
  107    reduced(?, 0, +),
  108    limit(+, 0),
  109    offset(+, 0),
  110    order_by(+, 0),
  111    group_by(?, ?, 0, -).
 distinct(:Goal)
 distinct(?Witness, :Goal)
True if Goal is true and no previous solution of Goal bound Witness to the same value. As previous answers need to be copied, equivalence testing is based on term variance (=@=/2). The variant distinct/1 is equivalent to distinct(Goal,Goal).

If the answers are ground terms, the predicate behaves as the code below, but answers are returned as soon as they become available rather than first computing the complete answer set.

distinct(Goal) :-
    findall(Goal, Goal, List),
    list_to_set(List, Set),
    member(Goal, Set).
  132distinct(Goal) :-
  133    distinct(Goal, Goal).
  134distinct(Witness, Goal) :-
  135    term_variables(Witness, Vars),
  136    Witness1 =.. [v|Vars],
  137    empty_nb_set(Set),
  138    call(Goal),
  139    add_nb_set(Witness1, Set, true).
 reduced(:Goal)
 reduced(?Witness, :Goal, +Options)
Similar to distinct/1, but does not guarantee unique results in return for using a limited amount of memory. Both distinct/1 and reduced/1 create a table that block duplicate results. For distinct/1, this table may get arbitrary large. In contrast, reduced/1 discards the table and starts a new one of the table size exceeds a specified limit. This filter is useful for reducing the number of answers when processing large or infinite long tail distributions. Options:
size_limit(+Integer)
Max number of elements kept in the table. Default is 10,000.
  156reduced(Goal) :-
  157    reduced(Goal, Goal, []).
  158reduced(Witness, Goal, Options) :-
  159    option(size_limit(SizeLimit), Options, 10_000),
  160    term_variables(Witness, Vars),
  161    Witness1 =.. [v|Vars],
  162    empty_nb_set(Set),
  163    State = state(Set),
  164    call(Goal),
  165    reduced_(State, Witness1, SizeLimit).
  166
  167reduced_(State, Witness1, SizeLimit) :-
  168    arg(1, State, Set),
  169    add_nb_set(Witness1, Set, true),
  170    size_nb_set(Set, Size),
  171    (   Size > SizeLimit
  172    ->  empty_nb_set(New),
  173        nb_setarg(1, State, New)
  174    ;   true
  175    ).
 limit(+Count, :Goal)
Limit the number of solutions. True if Goal is true, returning at most Count solutions. Solutions are returned as soon as they become available.
  184limit(Count, Goal) :-
  185    Count > 0,
  186    State = count(0),
  187    call(Goal),
  188    arg(1, State, N0),
  189    N is N0+1,
  190    (   N =:= Count
  191    ->  !
  192    ;   nb_setarg(1, State, N)
  193    ).
 offset(+Count, :Goal)
Ignore the first Count solutions. True if Goal is true and produces more than Count solutions. This predicate computes and ignores the first Count solutions.
  201offset(Count, Goal) :-
  202    Count > 0,
  203    !,
  204    State = count(0),
  205    call(Goal),
  206    arg(1, State, N0),
  207    (   N0 >= Count
  208    ->  true
  209    ;   N is N0+1,
  210        nb_setarg(1, State, N),
  211        fail
  212    ).
  213offset(Count, Goal) :-
  214    Count =:= 0,
  215    !,
  216    call(Goal).
  217offset(Count, _) :-
  218    domain_error(not_less_than_zero, Count).
 order_by(Spec, Goal)
Order solutions according to Spec. Spec is a list of terms, where each element is one of. The ordering of solutions of Goal that only differ in variables that are not shared with Spec is not changed.
asc(Term)
Order solution according to ascending Term
desc(Term)
Order solution according to descending Term
  232order_by(Spec, Goal) :-
  233    must_be(list, Spec),
  234    non_empty_list(Spec),
  235    maplist(order_witness, Spec, Witnesses0),
  236    join_orders(Witnesses0, Witnesses),
  237    non_witness_template(Goal, Witnesses, Others),
  238    reverse(Witnesses, RevWitnesses),
  239    maplist(x_vars, RevWitnesses, WitnessVars),
  240    Template =.. [v,Others|WitnessVars],
  241    findall(Template, Goal, Results),
  242    order(RevWitnesses, 2, Results, OrderedResults),
  243    member(Template, OrderedResults).
  244
  245order([], _, Results, Results).
  246order([H|T], N, Results0, Results) :-
  247    order1(H, N, Results0, Results1),
  248    N2 is N + 1,
  249    order(T, N2, Results1, Results).
  250
  251order1(asc(_), N, Results0, Results) :-
  252    sort(N, @=<, Results0, Results).
  253order1(desc(_), N, Results0, Results) :-
  254    sort(N, @>=, Results0, Results).
  255
  256non_empty_list([]) :-
  257    !,
  258    domain_error(non_empty_list, []).
  259non_empty_list(_).
  260
  261order_witness(Var, _) :-
  262    var(Var),
  263    !,
  264    instantiation_error(Var).
  265order_witness(asc(Term), asc(Witness)) :-
  266    !,
  267    witness(Term, Witness).
  268order_witness(desc(Term), desc(Witness)) :-
  269    !,
  270    witness(Term, Witness).
  271order_witness(Term, _) :-
  272    domain_error(order_specifier, Term).
  273
  274x_vars(asc(Vars), Vars).
  275x_vars(desc(Vars), Vars).
  276
  277witness(Term, Witness) :-
  278    term_variables(Term, Vars),
  279    Witness =.. [v|Vars].
 join_orders(+SpecIn, -SpecOut) is det
Merge subsequent asc and desc sequences. For example, [asc(v(A)), asc(v(B))] becomes [asc(v(A,B))].
  286join_orders([], []).
  287join_orders([asc(O1)|T0], [asc(O)|T]) :-
  288    !,
  289    ascs(T0, OL, T1),
  290    join_witnesses(O1, OL, O),
  291    join_orders(T1, T).
  292join_orders([desc(O1)|T0], [desc(O)|T]) :-
  293    !,
  294    descs(T0, OL, T1),
  295    join_witnesses(O1, OL, O),
  296    join_orders(T1, T).
  297
  298ascs([asc(A)|T0], [A|AL], T) :-
  299    !,
  300    ascs(T0, AL, T).
  301ascs(L, [], L).
  302
  303descs([desc(A)|T0], [A|AL], T) :-
  304    !,
  305    descs(T0, AL, T).
  306descs(L, [], L).
  307
  308join_witnesses(O, [], O) :- !.
  309join_witnesses(O, OL, R) :-
  310    term_variables([O|OL], VL),
  311    R =.. [v|VL].
 non_witness_template(+Goal, +Witness, -Template) is det
Create a template for the bindings that are not part of the witness variables.
  318non_witness_template(Goal, Witness, Template) :-
  319    ordered_term_variables(Goal, AllVars),
  320    ordered_term_variables(Witness, WitnessVars),
  321    ord_subtract(AllVars, WitnessVars, TemplateVars),
  322    Template =.. [t|TemplateVars].
  323
  324ordered_term_variables(Term, Vars) :-
  325    term_variables(Term, Vars0),
  326    sort(Vars0, Vars).
 group_by(+By, +Template, :Goal, -Bag) is nondet
Group bindings of Template that have the same value for By. This predicate is almost the same as bagof/3, but instead of specifying the existential variables we specify the free variables. It is provided for consistency and complete coverage of the common database vocabulary.
  336group_by(By, Template, Goal, Bag) :-
  337    ordered_term_variables(Goal, GVars),
  338    ordered_term_variables(By+Template, UVars),
  339    ord_subtract(GVars, UVars, ExVars),
  340    bagof(Template, ExVars^Goal, Bag)