Go to the first, previous, next, last section, table of contents.


Constraint programming over finite domains

Author(s): J.M. Gomez, M. Carro.

This package allows to write and evaluate constraint programming expressions over finite domains in a Ciao program.

(Other examples can be found in the source and library directories.)

:- use_package(fd).
:- use_module(library(prolog_sys), [statistics/2]).
:- use_module(library(format)).

smm(SMM) :-
        statistics(runtime,_),
        do_smm(SMM),
        statistics(runtime,[_, Time]),
        format("Used ~d milliseconds~n", Time).

do_smm(X) :-
        X = [S,E,N,D,M,O,R,Y],
        X in 0 .. 9,
        all_different(X),
        M .>. 0,
        S .>. 0,
        1000*S + 100*E + 10*N + D + 1000*M + 100*O + 10*R + E .=. 10000*M + 1000*O + 100*N + 10*E + Y,
       labeling(X).

:- use_package(fd).
:- use_module(library(prolog_sys), [statistics/2]).
:- use_module(library(format)).
:- use_module(library(aggregates)).
:- use_module(library(lists),[length/2]).

queens(N, Qs) :-
        statistics(runtime,_),
        do_queens(N, Qs),
        statistics(runtime,[_, Time]),
        format("Used ~d milliseconds~n", Time).

do_queens(N, Qs):- 
        constrain_values(N, N, Qs),
        all_different(Qs),!,
        labeling(Qs).

constrain_values(0, _N, []).
constrain_values(N, Range, [X|Xs]):-
        N > 0, 
        X in 1 .. Range,
        N1 is N - 1,
        constrain_values(N1, Range, Xs),
        no_attack(Xs, X, 1).

no_attack([], _Queen, _Nb).
no_attack([Y|Ys], Queen, Nb):-
        Nb1 is Nb + 1,
        no_attack(Ys, Queen, Nb1),
        Queen .<>. Y + Nb,
        Queen .<>. Y - Nb.        

Usage and interface (fd)

Documentation on exports (fd)

REGTYPE: fd_item/1:

Usage: fd_item(FD_item)

REGTYPE: fd_range/1:

Usage: fd_range(FD_range)

REGTYPE: fd_subrange/1:

Usage:

REGTYPE: fd_store/1:

Usage: fd_store(FD_store)

REGTYPE: fd_store_entity/1:

Usage:

PREDICATE: labeling/1:

Usage: labeling(Vars)

PREDICATE: pitm/2:

Usage: pitm(V, MiddlePoint)

PREDICATE: choose_var/3:

Usage: choose_var(ListOfVars, Var, RestOfVars)

PREDICATE: choose_free_var/2:

Usage: choose_free_var(ListOfVars, Var)

PREDICATE: choose_var_nd/2:

Usage: choose_var_nd(ListOfVars, Var)

PREDICATE: choose_value/2:

Usage: choose_value(Var, Value)

PREDICATE: retrieve_range/2:

Usage: retrieve_range(Var, Range)

PREDICATE: retrieve_store/2:

Usage: retrieve_store(Var, Store)

PREDICATE: glb/2:

Usage: glb(Var, LowerBound)

PREDICATE: lub/2:

Usage: lub(Var, UpperBound)

PREDICATE: bounds/3:

Usage: bounds(Var, LowerBound, UpperBound)

PREDICATE: retrieve_list_of_values/2:

Usage: retrieve_list_of_values(Var, ListOfValues)


Go to the first, previous, next, last section, table of contents.