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.
fd)fd)
Usage: fd_item(FD_item)
FD_item is a finite domain entity, i.e. either a finite domains variable or an integer.
Usage: fd_range(FD_range)
FD_range is the range of a finite domain entity.
Usage:
Usage: fd_store(FD_store)
FD_store is a representation of the constraint store of a finite domain entity.
Usage:
Usage: labeling(Vars)
Vars. On exit all variables are instantiated to a consistent value. On backtracking, the predicate returns all possible assignments. No labeling heuristics implemented so far, i.e. variables are instantiated in their order of appearance.
Vars is a list of fd_items.
(basic_props:list/2)
Usage: pitm(V, MiddlePoint)
MiddlePoint the intermediate value of the range of V. In case V is a ground integer value the returned value is V itself.
V is currently a term which is not a free variable.
(term_typing:nonvar/1)
MiddlePoint is a free variable.
(term_typing:var/1)
V is a finite domain entity, i.e. either a finite domains variable or an integer.
(user(... /fd_doc):fd_item/1)
MiddlePoint is an integer.
(basic_props:int/1)
Usage: choose_var(ListOfVars, Var, RestOfVars)
Var from a list of fd items ListOfVars and the rest of the list RestOfVarsin a deterministic way. Currently it always returns the first item of the list.
ListOfVars is currently a term which is not a free variable.
(term_typing:nonvar/1)
Var is a free variable.
(term_typing:var/1)
RestOfVars is a free variable.
(term_typing:var/1)
ListOfVars is a list of fd_items.
(basic_props:list/2)
Var is a finite domain entity, i.e. either a finite domains variable or an integer.
(user(... /fd_doc):fd_item/1)
RestOfVars is a list of fd_items.
(basic_props:list/2)
Usage: choose_free_var(ListOfVars, Var)
Var from a list of fd items ListOfVars. Currently it always returns the first free variable of the list.
ListOfVars is currently a term which is not a free variable.
(term_typing:nonvar/1)
Var is a free variable.
(term_typing:var/1)
ListOfVars is a list of fd_items.
(basic_props:list/2)
Var is a free variable.
(term_typing:var/1)
Usage: choose_var_nd(ListOfVars, Var)
Var from a list of fd items ListOfVars .
ListOfVars is currently a term which is not a free variable.
(term_typing:nonvar/1)
Var is a free variable.
(term_typing:var/1)
ListOfVars is a list of fd_items.
(basic_props:list/2)
Var is a finite domain entity, i.e. either a finite domains variable or an integer.
(user(... /fd_doc):fd_item/1)
Usage: choose_value(Var, Value)
Value from the domain of Var. On backtracking returns all possible values for Var.
Var is currently a term which is not a free variable.
(term_typing:nonvar/1)
Value is a free variable.
(term_typing:var/1)
Var is a finite domain entity, i.e. either a finite domains variable or an integer.
(user(... /fd_doc):fd_item/1)
Value is an integer.
(basic_props:int/1)
Usage: retrieve_range(Var, Range)
Range the range of an fd item Var.
Var is currently a term which is not a free variable.
(term_typing:nonvar/1)
Range is a free variable.
(term_typing:var/1)
Var is a free variable.
(term_typing:var/1)
Range is the range of a finite domain entity.
(user(... /fd_doc):fd_range/1)
Usage: retrieve_store(Var, Store)
Store a representation of the constraint store of an fd item Var.
Var is currently a term which is not a free variable.
(term_typing:nonvar/1)
Store is a free variable.
(term_typing:var/1)
Var is a free variable.
(term_typing:var/1)
Store is a representation of the constraint store of a finite domain entity.
(user(... /fd_doc):fd_store/1)
Usage: glb(Var, LowerBound)
LowerBound the lower bound of the range of Var.
Var is currently a term which is not a free variable.
(term_typing:nonvar/1)
LowerBound is a free variable.
(term_typing:var/1)
Var is a finite domain entity, i.e. either a finite domains variable or an integer.
(user(... /fd_doc):fd_item/1)
LowerBound is an integer.
(basic_props:int/1)
Usage: lub(Var, UpperBound)
UpperBound the upper bound of the range of Var.
Var is currently a term which is not a free variable.
(term_typing:nonvar/1)
UpperBound is a free variable.
(term_typing:var/1)
Var is a finite domain entity, i.e. either a finite domains variable or an integer.
(user(... /fd_doc):fd_item/1)
UpperBound is an integer.
(basic_props:int/1)
Usage: bounds(Var, LowerBound, UpperBound)
LowerBound and UpperBound the lower and upper bounds of the range of Var.
Var is currently a term which is not a free variable.
(term_typing:nonvar/1)
LowerBound is a free variable.
(term_typing:var/1)
UpperBound is a free variable.
(term_typing:var/1)
Var is a finite domain entity, i.e. either a finite domains variable or an integer.
(user(... /fd_doc):fd_item/1)
LowerBound is an integer.
(basic_props:int/1)
UpperBound is an integer.
(basic_props:int/1)
Usage: retrieve_list_of_values(Var, ListOfValues)
ListOfValues an enumeration of al the values in the range of Var
Var is currently a term which is not a free variable.
(term_typing:nonvar/1)
ListOfValues is a free variable.
(term_typing:var/1)
Var is a finite domain entity, i.e. either a finite domains variable or an integer.
(user(... /fd_doc):fd_item/1)
ListOfValues is a list of ints.
(basic_props:list/2)
Go to the first, previous, next, last section, table of contents.