next up previous index
Next: General Guidelines to the Up: The Finite Domains Library Previous: Debugger Support   Index

Examples

A very simple example of using the finite domains is the send more money puzzle:
:- use_module(library(fd)).

send(List) :-
    List = [S, E, N, D, M, O, R, Y],
    List :: 0..9,
    alldifferent(List),
    1000*S+100*E+10*N+D + 1000*M+100*O+10*R+E #=
        10000*M+1000*O+100*N+10*E+Y,
    M #\= 0,
    S #\= 0,
    labeling(List).

The problem is stated very simply, one just writes down the conditions that must hold for the involved variables and then uses the default labeling procedure, i.e. the order in which the variables will be instantiated. When executing send/1, the variables S, M and O are instantiated even before the labeling procedure starts. When a consistent value for the variable E is found (5), and this value is propagated to the other variables, all variables become instantiated and thus the rest of the labeling procedure only checks groundness of the list.

A slightly more elaborate example is the eight queens puzzle. Let us show a solution for this problem generalised to N queens and also enhanced by a cost function that evaluates every solution. The cost can be for example coli - rowi for the i-th queen. We are now looking for the solution with the smallest cost, i.e. one for which the maximum of all coli - rowi `_= is minimal:

:- use_module(library(fd)).

% Find the minimal solution for the N-queens problem
cqueens(N, List) :-
    make_list(N, List),
    List :: 1..N,
    constrain_queens(List),
    make_cost(1, List, C),
    min_max(labeling(List), C).

% Set up the constraints for the queens
constrain_queens([]).
constrain_queens([X|Y]) :-
    safe(X, Y, 1),
    constrain_queens(Y).

safe(_, [], _).
safe(X, [Y|T], K) :-
    noattack(X, Y, K) ,
    K1 is K + 1 ,
    safe(X, T, K1).

% Queens in rows X and Y cannot attack each other
noattack(X, Y, K) :-
    X #\= Y,
    X + K #\= Y,
    X - K #\= Y.

% Create a list with N variables
make_list(0, []) :- !.
make_list(N, [_|Rest]) :-
    N1 is N - 1,
    make_list(N1, Rest).

% Set up the cost expression
make_cost(_, [], []).
make_cost(N, [Var|L], [N-Var|Term]) :-
    N1 is N + 1,
    make_cost(N1, L, Term).

labeling([]) :- !.
labeling(L) :-
    deleteff(Var, L, Rest),
    indomain(Var),
    labeling(Rest).

The approach is similar to the previous example: first we create the domain variables, one for each column of the board, whose values will be the rows. We state constraints which must hold between every pair of queens and finally we make the cost term in the format required for the min_max/2 predicate. The labeling predicate selects the most constrained variable for instantiation using the deleteff/3 predicate. When running the example, we get the following result:

[eclipse 19]: cqueens(8, X).
Found a solution with cost 5
Found a solution with cost 4

X = [5, 3, 1, 7, 2, 8, 6, 4] 
yes.
The time needed to find the minimal solution is about five times shorter than the time to generate all solutions. This shows the advantage of the branch and bound method. Note also that the board for this `minimal' solution looks very nice.


next up previous index
Next: General Guidelines to the Up: The Finite Domains Library Previous: Debugger Support   Index
Warwick Harvey
2004-08-07