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. Please note that the library(clp/bounds)
library is not an
autoload library and therefore this library must be loaded
explicitely before using it using:
:- use_module(library('clp/bounds')). |
Here Expr can be one of
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:
occurrences(List,Value,Count) :- occurrences(List,Value,0,Count). occurrences([],_,Count,Count). occurrences([X|Xs],Value,Acc,Count) :- X #= Value #=> NAcc #= Acc + 1, X #\= Value #=> NAcc #= Acc, occurrences(Xs,Value,NAcc,Count). |
occurrences(List,Value,Count) :- occurrences(List,Value,0,Count). occurrences([],_,Count,Count). occurrences([X|Xs],Value,Acc,Count) :- X #= Value #=> B, NAcc #= Acc + B, occurrences(Xs,Value,NAcc,Count). |
:- use_module(library('clp/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). |
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]] |