Did you know ... Search Documentation:
Pack modeling -- prolog/comprehension.pl
PublicShow source
author
- Francois Fages
version
- 1.1.5

Prolog metapredicates for set comprehension like setof/3 were introduced by David Warren in 1982 to collect goal instantiations by backtracking. This necessitated indeed a special mechanism to add to Prolog, which is used for bagof/3, findall/3, forall/2, foreach/2, or aggregate/3 for instance.

This approach to set comprehension is correct for the goal success semantics of Prolog, but incorrect for the answer constraint semantics, e.g. universal quantifier constraint for_all/2 defined here compared to standard forall/2 foreach/2 metapredicates:

?- L=[A, B, C], for_all(X in L, X=1). % constraint posted for all elements
L = [1, 1, 1],
A = B, B = C, C = 1.

?- L=[A, B, C], forall(member(X, L), X=1). % satisfiability test for all elements
L = [A, B, C].

?- L=[A, B, C], foreach(member(X, L), X=1). % idem
L = [A, B, C].

?- L=[A, B, C], for_all([X, Y] in L, X=Y).
L = [C, C, C],
A = B, B = C.

?- L=[A, B, C], forall((member(X, L), member(Y, L)), X=Y).
L = [A, B, C].

?- use_module(library(clpfd)).
true.

?- L=[A, B, C], forall(member(X, L), X#>1).
L = [A, B, C].

?- L=[A, B, C], for_all(X in L, X#>1).
L = [A, B, C],
clpfd:(A in 2..sup),
clpfd:(B in 2..sup),
clpfd:(C in 2..sup).

?- forall(member(X, [1, 2, 3]), Y#>X).
true.

?- for_all(X in [1, 2, 3], Y#>X).
clpfd:(Y in 4..sup).

We provide here metapredicates for comprehension by iteration, instead of backtracking, which

  • rename comprehension variables and raise an error if they are instantiated (they can be attributed and will be renamed without attributes),
  • constrain the calling context variables,
  • possibly non-deterministically, if the conditions or goal are non-deterministic.

The comprehension variables must be given with a mandatory "in" domain, and optionally a "where" condition.

The "in" domain must be either a domain of integers (i.e. union \/ of intervals ..) or a list of terms. Shorthand notations are evaluated in the domain.

?- for_all([I, J] in 1..3 where I<J, writeln(I-J)).
1-2
1-3
2-3
true.

?- for_all([I in 1..3, J in I+1..3], writeln(I-J)).
1-2
1-3
2-3
true.

list_of/3 collects the elements defined by comprehension in a list:

?- list_of([I, J] in 1..3 where I<J, I-J, List).
List = [1-2, 1-3, 2-3].

aggregate_for/6 expresses a relation on the application of a binary operator between elements defined by comprehension:

?- aggregate_for(X in 1..5, X+1, +, 0, =, Term).
Term = 1+1+(2+1+(3+1+(4+1+(5+1+0)))).

?- use_module(library(clpfd)).
true.
  
?- aggregate_for(X in 1..5, X+1, +, 0, #=, Result).
Result = 20.

The "where" condition in intensional definitions can bind or constrain context variables. In particular, if the "where" condition is a constraint, the constraint is posted and thus tested for satisfiability, not entailment. The example below illustrates the difference: X=Y is satisfiable and posted for all X, Y, whereas in the second query, the condition X==Y is just a test and succeeds on the elements where it is satisfied without changing L:

?- L=[A, B, C], for_all([X, Y] in L where X=Y, true).
L = [C, C, C],
A = B, B = C.

?- L=[A, B, C], for_all([X, Y] in L where X==Y, true).
L = [A, B, C].

The "where" condition goal can also be non-deterministic, making the comprehension metapredicate non-deterministic in this case.

 for_all(+VarDomains, +Goal)
universal quantifier for iteratively executing Goal on all instances defined in comprehension with mandatory "in" domain and optional "where" condition, both allowing shorthand/3 functional notations. An error is raised a universally quantified variable to be renamed is instantiated. The "in" domain must be either a domain of integers (i.e. union of intervals) or a list of terms.

Unlike forall/2, foreach/2, the conjunction of Goal instances constrains context variables (answer constraint semantics)

?- L=[A, B, C], for_all(X in L, X=1).
L = [1, 1, 1],
A = B, B = C, C = 1.

The "where" condition goal can be non-deterministic.

for_all/2 is similar to maplist/2 but using a Goal pattern with arguments defined by comprehension.

 list_of(+VarDomains, +Term, ?List)
List is the list of instances of Term defined in comprehension with mandatory "in" domain and optional "where" condition both allowing shorthand/3 functional notations.

list_of(VarDomains, Expr, List) is defined by aggregate_for(VarDomains, Expr, [|], [], =, List).

An error is raised if the comprehension variables to be renamed are instantiated (they can be attributed and will be renamed without attributes).

The "where" condition goal can be non-deterministic.

 aggregate_for(+VarDomains, +Expression, +Op, +E, +Relation, ?Term)
true iff Relation(Term, Aggregate) holds where Aggregate is the application of binary operation Op with starting element E, to all instances of Expression defined in comprehension by VarDomains with mandatory "in" domain and optional "where" condition. An error is raised if a comprehension variable is instantiated (if it is attributed it is renamed without attributes).

For example, list_of(VarDomains, Expression, List) is defined here by aggregate_for(VarDomains, Expression, [|], [], =, List).

The instances of Expression are not evaluated unless Expression is of the form "Variable where Goal" in which case the Goal is executed. It is an error if the first argument of where is not a variable. The variable is existentially quantified and renamed in the Goal.

The list of arguments of a term could be defined by

?- Term=f(a,g(X),Y), functor(Term, _, N),  aggregate_for([I in 1..N], Arg where arg(I, Term, Arg), '[|]', [], =, Args).
Term = f(a, g(X), Y),
N = 3,
Args = [a, g(X), Y].

aggregate_for/6 is similar to foldl/4 but more general and using Goal pattern with arguments defined in comprehension.

Used in library(clp) to define some hybrid global constraints.

 exists(+Vars, +Goal)
calls Goal with existentially quantified variables Vars. An error is raised if the existential variables to rename are instantiated (they can be attributed though and will be renamed without attributes).
 let(+Bindings, +Goal)
calls Goal with Bindings for existentially quantified variables bound to expressions allowing shorthand/3 functional notations. An error is raised if the existential variables to rename are instantiated (they can be attributed and will be renamed without attributes).