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

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.

See also
- all solution predicates findall/3, bagof/3 and setof/3.
- library(aggregate) */
  106:- meta_predicate
  107    distinct(0),
  108    distinct(?, 0),
  109    reduced(0),
  110    reduced(?, 0, +),
  111    limit(+, 0),
  112    offset(+, 0),
  113    call_nth(0, ?),
  114    order_by(+, 0),
  115    group_by(?, ?, 0, -).  116
  117:- noprofile((
  118       distinct/1,
  119       distinct/2,
  120       reduced/1,
  121       reduced/2,
  122       limit/2,
  123       offset/2,
  124       call_nth/2,
  125       order_by/2,
  126       group_by/3)).
 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).
  148distinct(Goal) :-
  149    distinct(Goal, Goal).
  150distinct(Witness, Goal) :-
  151    term_variables(Witness, Vars),
  152    Witness1 =.. [v|Vars],
  153    setup_call_cleanup(
  154        trie_new(Trie),
  155        distinct_gen(Trie, Goal, Witness1),
  156        trie_destroy(Trie)).
  157
  158distinct_gen(Trie, Goal, Witness) :-
  159    call(Goal),
  160    trieable(Witness, ForTrie),
  161    trie_insert(Trie, ForTrie).
  162
  163trieable(Term, ForTrie) :-
  164    acyclic_term(Term),
  165    term_attvars(Term, []),
  166    !,
  167    ForTrie = t(Term).
  168trieable(Term, ForTrie) :-
  169    copy_term(Term, Term2),
  170    term_attvars(Term2, AttVars),
  171    maplist(attrs, AttVars, AttVals),
  172    ForTrie0 = a(Term2, AttVals),
  173    (   acyclic_term(ForTrie0)
  174    ->  ForTrie = ForTrie0
  175    ;   term_factorized(ForTrie0, Plain, Assign),
  176        ForTrie = c(Plain, Assign)
  177    ).
  178
  179attrs(Var, Atts) :-
  180    get_attrs(Var, Atts),
  181    del_attrs(Var).
 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.
  199reduced(Goal) :-
  200    reduced(Goal, Goal, []).
  201reduced(Witness, Goal, Options) :-
  202    option(size_limit(SizeLimit), Options, 10_000),
  203    term_variables(Witness, Vars),
  204    Witness1 =.. [v|Vars],
  205    setup_call_cleanup(
  206        reduced_init(State),
  207        reduced_next(State, Goal, Witness1, SizeLimit),
  208        reduced_exit(State)).
  209
  210reduced_init(State) :-
  211    trie_new(Set),
  212    State = state(Set).
  213
  214reduced_exit(state(Trie)) :-
  215    trie_destroy(Trie).
  216
  217reduced_next(State, Goal, Witness, SizeLimit) :-
  218    call(Goal),
  219    arg(1, State, Set),
  220    trieable(Witness, ForTrie),
  221    trie_insert(Set, ForTrie),
  222    trie_property(Set, node_count(Size)),
  223    (   Size > SizeLimit
  224    ->  trie_destroy(Set),
  225        trie_new(New),
  226        nb_setarg(1, State, New)
  227    ;   true
  228    ).
 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.
Arguments:
Count- is either infinite, making this predicate equivalent to call/1 or an integer. If Count < 1 this predicate fails immediately.
  241limit(Count, Goal) :-
  242    Count == infinite,
  243    !,
  244    call(Goal).
  245limit(Count, Goal) :-
  246    Count > 0,
  247    State = count(0),
  248    call(Goal),
  249    arg(1, State, N0),
  250    N is N0+1,
  251    (   N =:= Count
  252    ->  !
  253    ;   nb_setarg(1, State, N)
  254    ).
 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.
  262offset(Count, Goal) :-
  263    Count > 0,
  264    !,
  265    State = count(0),
  266    call(Goal),
  267    arg(1, State, N0),
  268    (   N0 >= Count
  269    ->  true
  270    ;   N is N0+1,
  271        nb_setarg(1, State, N),
  272        fail
  273    ).
  274offset(Count, Goal) :-
  275    Count =:= 0,
  276    !,
  277    call(Goal).
  278offset(Count, _) :-
  279    domain_error(not_less_than_zero, Count).
 call_nth(:Goal, ?Nth)
True when Goal succeeded for the Nth time. If Nth is bound on entry, the predicate succeeds deterministically if there are at least Nth solutions for Goal.
  287call_nth(Goal, Nth) :-
  288    integer(Nth),
  289    !,
  290    (   Nth > 0
  291    ->  (   call_nth(Goal, Sofar),
  292            Sofar =:= Nth
  293        ->  true
  294        )
  295    ;   domain_error(not_less_than_one, Nth)
  296    ).
  297call_nth(Goal, Nth) :-
  298    var(Nth),
  299    !,
  300    State = count(0),
  301    call(Goal),
  302    arg(1, State, N0),
  303    Nth is N0+1,
  304    nb_setarg(1, State, Nth).
  305call_nth(_Goal, Bad) :-
  306    must_be(integer, Bad).
 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

This predicate is based on findall/3 and (thus) variables in answers are copied.

  322order_by(Spec, Goal) :-
  323    must_be(list, Spec),
  324    non_empty_list(Spec),
  325    maplist(order_witness, Spec, Witnesses0),
  326    join_orders(Witnesses0, Witnesses),
  327    non_witness_template(Goal, Witnesses, Others),
  328    reverse(Witnesses, RevWitnesses),
  329    maplist(x_vars, RevWitnesses, WitnessVars),
  330    Template =.. [v,Others|WitnessVars],
  331    findall(Template, Goal, Results),
  332    order(RevWitnesses, 2, Results, OrderedResults),
  333    member(Template, OrderedResults).
  334
  335order([], _, Results, Results).
  336order([H|T], N, Results0, Results) :-
  337    order1(H, N, Results0, Results1),
  338    N2 is N + 1,
  339    order(T, N2, Results1, Results).
  340
  341order1(asc(_), N, Results0, Results) :-
  342    sort(N, @=<, Results0, Results).
  343order1(desc(_), N, Results0, Results) :-
  344    sort(N, @>=, Results0, Results).
  345
  346non_empty_list([]) :-
  347    !,
  348    domain_error(non_empty_list, []).
  349non_empty_list(_).
  350
  351order_witness(Var, _) :-
  352    var(Var),
  353    !,
  354    instantiation_error(Var).
  355order_witness(asc(Term), asc(Witness)) :-
  356    !,
  357    witness(Term, Witness).
  358order_witness(desc(Term), desc(Witness)) :-
  359    !,
  360    witness(Term, Witness).
  361order_witness(Term, _) :-
  362    domain_error(order_specifier, Term).
  363
  364x_vars(asc(Vars), Vars).
  365x_vars(desc(Vars), Vars).
  366
  367witness(Term, Witness) :-
  368    term_variables(Term, Vars),
  369    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))].
  376join_orders([], []).
  377join_orders([asc(O1)|T0], [asc(O)|T]) :-
  378    !,
  379    ascs(T0, OL, T1),
  380    join_witnesses(O1, OL, O),
  381    join_orders(T1, T).
  382join_orders([desc(O1)|T0], [desc(O)|T]) :-
  383    !,
  384    descs(T0, OL, T1),
  385    join_witnesses(O1, OL, O),
  386    join_orders(T1, T).
  387
  388ascs([asc(A)|T0], [A|AL], T) :-
  389    !,
  390    ascs(T0, AL, T).
  391ascs(L, [], L).
  392
  393descs([desc(A)|T0], [A|AL], T) :-
  394    !,
  395    descs(T0, AL, T).
  396descs(L, [], L).
  397
  398join_witnesses(O, [], O) :- !.
  399join_witnesses(O, OL, R) :-
  400    term_variables([O|OL], VL),
  401    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.
  408non_witness_template(Goal, Witness, Template) :-
  409    ordered_term_variables(Goal, AllVars),
  410    ordered_term_variables(Witness, WitnessVars),
  411    ord_subtract(AllVars, WitnessVars, TemplateVars),
  412    Template =.. [t|TemplateVars].
  413
  414ordered_term_variables(Term, Vars) :-
  415    term_variables(Term, Vars0),
  416    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.
  426group_by(By, Template, Goal, Bag) :-
  427    ordered_term_variables(Goal, GVars),
  428    ordered_term_variables(By+Template, UVars),
  429    ord_subtract(GVars, UVars, ExVars),
  430    bagof(Template, ExVars^Goal, Bag)