% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(aggregate): Aggregation operators on backtrackable predicates} \label{sec:aggregate} \begin{tags} \tag{Compatibility} Quintus, SICStus 4. The \predref{forall}{2} is a SWI-Prolog built-in and \predref{term_variables}{3} is a SWI-Prolog built-in with \textbf{different semantics}.\mtag{To be done}- Analysing the aggregation template and compiling a predicate for the list aggregation can be done at compile time. \\- \predref{aggregate_all}{3} can be rewritten to run in constant space using non-backtrackable assignment on a term. \end{tags} This library provides aggregating operators over the solutions of a predicate. The operations are a generalisation of the \predref{bagof}{3}, \predref{setof}{3} and \predref{findall}{3} built-in predicates. Aggregations that can be computed incrementally avoid \predref{findall}{3} and run in constant memory. The defined aggregation operations are counting, computing the sum, minimum, maximum, a bag of solutions and a set of solutions. We first give a simple example, computing the country with the smallest area: \begin{code} smallest_country(Name, Area) :- aggregate(min(A, N), country(N, A), min(Area, Name)). \end{code} There are four aggregation predicates (\predref{aggregate}{3}, \predref{aggregate}{4}, \predref{aggregate_all}{3} and \predref{aggregate}{4}), distinguished on two properties. \begin{description} \item[aggregate vs. aggregate_all] The aggregate predicates use \predref{setof}{3} (\predref{aggregate}{4}) or \predref{bagof}{3} (\predref{aggregate}{3}), dealing with existential qualified variables (\verb$Var^Goal$) and providing multiple solutions for the remaining free variables in \arg{Goal}. The \predref{aggregate_all}{3} predicate uses \predref{findall}{3}, implicitly qualifying all free variables and providing exactly one solution, while \predref{aggregate_all}{4} uses \predref{sort}{2} over solutions that Discriminator (see below) generated using \predref{findall}{3}. \item[The Discriminator argument] The versions with 4 arguments deduplicate redundant solutions of Goal. Solutions for which both the template variables and Discriminator are identical will be treated as one solution. For example, if we wish to compute the total population of all countries, and for some reason \verb$country(belgium, 11000000)$ may succeed twice, we can use the following to avoid counting the population of Belgium twice: \begin{code} aggregate(sum(P), Name, country(Name, P), Total) \end{code} \end{description} All aggregation predicates support the following operators below in Template. In addition, they allow for an arbitrary named compound term, where each of the arguments is a term from the list below. For example, the term \verb$r(min(X), max(X))$ computes both the minimum and maximum binding for X. \begin{description} \termitem{count}{} Count number of solutions. Same as \verb$sum(1)$. \termitem{sum}{Expr} Sum of \arg{Expr} for all solutions. \termitem{min}{Expr} Minimum of \arg{Expr} for all solutions. \termitem{min}{Expr, Witness} A term \verb$min(Min, Witness)$, where Min is the minimal version of \arg{Expr} over all solutions, and \arg{Witness} is any other template applied to solutions that produced Min. If multiple solutions provide the same minimum, \arg{Witness} corresponds to the first solution. \termitem{max}{Expr} Maximum of \arg{Expr} for all solutions. \termitem{max}{Expr, Witness} As \verb$min(Expr, Witness)$, but producing the maximum result. \termitem{set}{X} An ordered set with all solutions for \arg{X}. \termitem{bag}{X} A list of all solutions for \arg{X}. \end{description} \textbf{Acknowledgements} \textit{The development of this library was sponsored by SecuritEase, \url{http://www.securitease.com} }\vspace{0.7cm} \begin{description} \predicate[nondet]{aggregate}{3}{+Template, :Goal, -Result} Aggregate bindings in \arg{Goal} according to \arg{Template}. The \predref{aggregate}{3} version performs \predref{bagof}{3} on \arg{Goal}. \predicate[nondet]{aggregate}{4}{+Template, +Discriminator, :Goal, -Result} Aggregate bindings in \arg{Goal} according to \arg{Template}. The \predref{aggregate}{4} version performs \predref{setof}{3} on \arg{Goal}. \predicate[semidet]{aggregate_all}{3}{+Template, :Goal, -Result} Aggregate bindings in \arg{Goal} according to \arg{Template}. The \predref{aggregate_all}{3} version performs \predref{findall}{3} on \arg{Goal}. Note that this predicate fails if \arg{Template} contains one or more of \verb$min(X)$, \verb$max(X)$, \verb$min(X,Witness)$ or \verb$max(X,Witness)$ and \arg{Goal} has no solutions, i.e., the minimum and maximum of an empty set is undefined. The \arg{Template} values \const{count}, \verb$sum(X)$, \verb$max(X)$, \verb$min(X)$, \verb$max(X,W)$ and \verb$min(X,W)$ are processed incrementally rather than using \predref{findall}{3} and run in constant memory. \predicate[semidet]{aggregate_all}{4}{+Template, +Discriminator, :Goal, -Result} Aggregate bindings in \arg{Goal} according to \arg{Template}. The \predref{aggregate_all}{4} version performs \predref{findall}{3} followed by \predref{sort}{2} on \arg{Goal}. See \predref{aggregate_all}{3} to understand why this predicate can fail. \predicate{foreach}{2}{:Generator, :Goal} True when the conjunction of \textit{instances} of \arg{Goal} created from solutions for \arg{Generator} is true. Except for term copying, this could be implemented as below. \begin{code} foreach(Generator, Goal) :- findall(Goal, Generator, Goals), maplist(call, Goals). \end{code} The actual implementation uses \predref{findall}{3} on a template created from the variables \textit{shared} between \arg{Generator} and \arg{Goal}. Subsequently, it uses every instance of this template to instantiate \arg{Goal}, call \arg{Goal} and undo \textit{only} the instantiation of the template and \textit{not} other instantiations created by running \arg{Goal}. Here is an example: \begin{code} ?- foreach(between(1,4,X), dif(X,Y)), Y = 5. Y = 5. ?- foreach(between(1,4,X), dif(X,Y)), Y = 3. false. \end{code} The predicate \predref{foreach}{2} is mostly used if \arg{Goal} performs backtrackable destructive assignment on terms. Attributed variables (underlying constraints) are an example. Another example of a backtrackable data structure is in \file{library(hashtable)}. If we care only about the side effects (I/O, dynamic database, etc.) or the truth value of \arg{Goal}, \predref{forall}{2} is a faster and simpler alternative. If \arg{Goal} instantiates its arguments it is will often fail as the argument cannot be instantiated to multiple values. It is possible to incrementally \textit{grow} an argument: \begin{code} ?- foreach(between(1,4,X), member(X, L)). L = [1,2,3,4|_]. \end{code} Note that SWI-Prolog up to version 8.3.4 created copies of \arg{Goal} using \predref{copy_term}{2} for each iteration, this makes the current implementation unable to properly handle compound terms (in \arg{Goal}'s arguments) that share variables with the \arg{Generator}. As a workaround you can define a goal that does not use compound terms, like in this example: \begin{code} mem(E,L) :- % mem/2 hides the compound argument from foreach/2 member(r(E),L). ?- foreach( between(1,5,N), mem(N,L)). \end{code} \predicate[det]{free_variables}{4}{:Generator, +Template, +VarList0, -VarList} Find free variables in bagof/setof template. In order to handle variables properly, we have to find all the universally quantified variables in the \arg{Generator}. All variables as yet unbound are universally quantified, unless \begin{enumerate} \item they occur in the template \item they are bound by X\Shat{}P, \predref{setof}{3}, or \predref{bagof}{3} \end{enumerate} \verb$free_variables(Generator, Template, OldList, NewList)$ finds this set using OldList as an accumulator. \begin{tags} \mtag{author}- Richard O'Keefe \\- Jan Wielemaker (made some SWI-Prolog enhancements) \tag{license} Public domain (from DEC10 library).\mtag{To be done}- Distinguish between control-structures and data terms. \\- Exploit our built-in \predref{term_variables}{2} at some places? \end{tags} \qpredicate[semidet,multifile]{sandbox}{safe_meta}{2}{+Goal, -Called}Declare the aggregate meta-calls safe. This cannot be proven due to the manipulations of the argument \arg{Goal}. \end{description}