A.13 library( clp/bounds ): Integer Bounds Constraint Solver

Author: Tom Schrijvers, K.U.Leuven

The bounds solver is a rather simple integer constraint solver, implemented with attributed variables. Its syntax is a subset of the SICStus clp(FD) syntax. The library(bounds) library is not an autoload library and therefore it must be loaded explicitly before using it via:

:- use_module(library(bounds)).

A.13.1 Constraints

The following constraints are supported:
-Var in +Range
Varibale Var is restricted to be in range Range. A range is denoted by L..U where both L and U are integers.
-Vars in +Range
A list of variables Vars are restriced to be in range Range.
tuples_in(+Tuples, +Extension)
Where Tuples is a list of tuples (lists) of variables and integers, each of length N, and Extension is a list of tuples of integers, each of length N. Each tuple of Tuples is constrained to be in the relation defined by Extension. See section A.13.4 for an example.
?Expr #> ?Expr
The left-hand expression is constrained to be greater than the right-hand expressions.
?Expr #< ?Expr
The left-hand expression is constrained to be smaller than the right-hand expressions.
?Expr #>= ?Expr
The left-hand expression is constrained to be greater than or equal to the right-hand expressions.
?Expr #=< ?Expr
The left-hand expression is constrained to be smaller than or equal to the right-hand expressions.
?Expr #= ?Expr
The left-hand expression is constrained to be equal to the right-hand expressions.
?Expr #\= ?Expr
The left-hand expression is constrained to be not equal to the right-hand expressions.
sum(+Vars,+Op,?Value)
Here Vars is a list of variables and integers, Op is one of the binary constraint relation symbols above and Value is an integer or variable. It represents the constraint (ΣVars) Op Value.
lex_chain(+VarsLists)
The constraint enforces lexicographic ordering on the lists in the argument. The argument VarsLists is a list of lists of variables and integers. The current implementation was contributed by Markus Triska.
all_different(+Vars)
Constrains all variabls in the list Vars to be pairwise not equal.
indomain(+Var)
Unify variable Var with a value in its domain. Backtracks over all possible values from lowest to greatest. Contributed by Markus Triska.
label(+Vars)
Equivalent to labeling([], Vars).
labeling(+Options, +Vars)
All variables in the list Vars are assigned values from their respective domains such that no constraint on them is violated. Options is a list of options. One set of options lets you choose the variable selection strategy:
leftmost
Label the variables in the order they occur in Vars from left to right. This is the default.
ff
Label the variable whose domain contains the smallest number of elements among the remaining variables next. This is called "first-fail". The intention here is twofold: First, to detect infeasibility early by always considering the variable most likely to cause failure; second, to give priority to variables that are close to running out of domain elements.
min
Label the variable whose lower bound is the lowest among the remaining variables next.
max
Label the variable whose upper bound is the highest among the remaining variables next.

Another set of options lets you search for extrema:

min(Expr)
max(Expr)
Label the variables such that Expr assumes the smallest/highest possible value.
serialized(+Starts,+Durations)
Starts = [S_1, ... ,S_n] is a list of variables or integers, and Durations = [D_1, ... ,D_n] is a list of non-negative integers. Starts are constrained to denote the starting times of non-overlapping tasks, i.e., S_i + D_i =< S_j or S_j + D_j =< S_i for all 1 =< i < j =< n.

Here Expr can be one of

integer
Any integer.
variable
A variable.
?Expr + ?Expr
The sum of two expressions.
?Expr * ?Expr
The product of two expressions.
?Expr - ?Expr
The difference of two expressions.
max(?Expr,?Expr)
The maximum of two expressions.
min(?Expr,?Expr)
The minimum of two expressions.
?Expr mod ?Expr
The first expression modulo the second expression.
abs(?Expr)
The absolute value of an expression.

A.13.2 Constraint Implication and Reified Constraints

The following constraint implication predicates are available:
+P #=> +Q
P implies Q, where P and Q are reifyable constraints.
+Q #<= +P
P implies Q, where P and Q are reifyable constraints.
+P #<=> +Q
P and Q are equivalent, where P and Q are reifyable constraints.

In addition, instead of being a reifyable constraint, either P or Q can be a boolean variable that is the truth value of the corresponding constraint.

The following constraints are reifyable: #=/2, #\=/2, #</2, #>/2, #=</2, #>/2.

For example, to count the number of occurrences of a particular value in a list of constraint variables:

A.13.3 Example 1: Send+More=Money

The following is an implementation of the classic alphametics puzzle SEND + MORE = MONEY:
:- use_module(library(bounds)).

send([[S,E,N,D], [M,O,R,E], [M,O,N,E,Y]])  :-
              Digits   =  [S,E,N,D,M,O,R,Y],
              Carries  =  [C1,C2,C3,C4],
              Digits  in  0..9,
              Carries in  0..1,

              M                #=              C4,
              O  +  10  *  C4  #=  M  +  S  +  C3,
              N  +  10  *  C3  #=  O  +  E  +  C2,
              E  +  10  *  C2  #=  R  +  N  +  C1,
              Y  +  10  *  C1  #=  E  +  D,

              M  #>=  1,
              S  #>=  1,
              all_different(Digits),
              label(Digits).

A.13.4 Example 2: Using tuples_in for a train schedule

This example demonstrates tuples_in/2. A train schedule is represented as a list Ts of quadruples, denoting departure and arrival places and times for each train. The path/3 predicate given below constrains Ps to a feasible journey from A to D via 3 trains that are part of the given schedule.

:- use_module(library(bounds)).

schedule(Ts) :-
        Ts = [[1,2,0,1],[2,3,4,5],[2,3,0,1],[3,4,5,6],[3,4,2,3],[3,4,8,9]].

path(A, D, Ps) :-
        schedule(Ts),
        Ps = [[A,B,_T0,T1],[B,C,T2,T3],[C,D,T4,_T5]],
        tuples_in(Ps, Ts),
        T2 #> T1,
        T4 #> T3.

An example query:

?- path(1, 4, Ps), flatten(Ps, Vars), label(Vars).

Ps = [[1, 2, 0, 1], [2, 3, 4, 5], [3, 4, 8, 9]]

A.13.5 SICStus clp(FD) compatibility

Apart from the limited syntax, the bounds solver differs in the following ways from the SICStus clp(FD) solver: