Prolog
CLP(FD)
intro
CLP(FD)
is a library- CLP = Constraint Logic Programming
- FD = Finite Domains, namely integers
- use it to solve a set of constraints over integers
write in the interpreter:
use_module(library(clpfd)).
or write the following at the top of a file:
:- use_module(library(clpfd)).
arithmetic constraints
comparison operators
the comparison operators are almost the same but prefixed by #
X #> Y.
X #< Y.
X #>= Y.
X #=< Y.
X #= Y.
X #\= Y.
X
and Y
can be any arithmetic expression:
- an integer value
- a variable
-Expr
Expr1 @ Expr2
where@
is replaced by+
*
-
^
//
div
mod
rem
abs(Expr)
min(Expr1,Expr2)
max(Expr1,Expr2)
how are these different from the regular comparison operators?
?- X + 2 =:= Y + X.
?- X + 2 #= Y + X.
the #
-operators don’t require that any of the variables are instantiated
domains
CLP(FD)
can give a domain as a solution
?- 0 #< X, X #< 5.
in a domain sup
is for supremum and inf
is for infimum
?- 0 #< X.
?- X #< 5.
we can use the in
operator in our code
?- X in 1..5.
\/
is used for domains union
?- X in 1..5, X #\= 2.
?- X in 1\/2\/3.
labeling
indomain(X)
is used to successively bind X
to all integers of its domain
?- X in 1..3, indomain(X).
indomain
must always terminate
?- X in 0..sup, indomain(X).
label
is just like indomain
but for a list of variables
?- 0 #=< N, N #< 17, 0 #< A, 0 #< B, N * N #= A * A + B * B, label([N, A, B]).
question
implement the predicate change/2
. change(S, L)
is true iff:
S
is a positive integerL
is a sorted (descending) list made of the integers1
,5
,10
S
is the sum of the numbers in L
(assume S
is concrete)
?- change(21, [10, 5, 1, 1, 1, 1, 1, 1]).
you can use the predicate repeat/3
. repeat(N, C, L)
is true iff:
N
is a conrete non-negative integerL
is a list ofN
C
s
...
repeat(0, _, []).
repeat(N, C, [C|Xs]) :-
N #> 0,
Ns #= N - 1,
repeat(Ns, C, Xs).
build([], []).
build([[N,C]|T], L) :- repeat(N, C, Xs), build(T, Ys), append(Xs, Ys, L).
change(S, L) :-
S #= A1 + A5 * 5 + A10 * 10,
A1 #>= 0, A5 #>= 0, A10 #>= 0,
label([A1, A5, A10]),
build([[A10, 10], [A5, 5], [A1, 1]], L)
.