[ library(ic) | The ECLiPSe Libraries | Reference Manual | Alphabetic Index ]

search(+L, ++Arg, ++Select, +Choice, ++Method, +Option)

A generic search routine for finite domains or IC which implements different partial search methods (complete, credit, lds, bbs, dbs, sbds)
L
is a list of domain variables (Arg = 0) or a list of terms (Arg > 0)
Arg
is an integer, which is 0 if the list is a list of dvarints or greater 0 if the list consists of terms of arity greater than Arg, the value Arg indicates the selected argument of the term
Select
is a predefined selection method or the name of a predicate of arity 2. Predefined methods are input_order, first_fail, smallest, largest, occurrence, most_constrained, max_regret, anti_first_fail
Choice
is the name of a predicate of arity 1 or a term with two arguments with the same functor as a predicate of arity 3. Some names are already predefined as special cases and are handled without a meta-call: indomain, indomain_min, indomain_max, indomain_middle, indomain_median, indomain_split, indomain_random, indomain_interval
Method
is one of the following: complete, bbs(Steps:integer), lds(Disc:integer), credit(Credit:integer, Extra:integer or bbs(Steps:integer) or lds(Disc:integer)), dbs(Level:integer, Extra:integer or bbs(Steps:integer) or lds(Disc:integer)), sbds
Option
is a list of option terms. Currently recognized are backtrack(-N), node(++Call), nodes(++N)

Description

Search/6 provides a generic interface to a set of different search methods. It can currently be used with either the finite domains (if loaded via lib(fd_search)), or integer IC domains (if loaded via lib(ic_search)). By changing the Method argument, different partial search algorithms (and their parameters) can be selected and controlled. The search predicate also provides a number of pre-defined variable selection methods (to choose which variable will be assigned next) and some pre-defined value assignment methods (to try out the possible values for the selected variable in some heuristic order), but user-defined methods can be used in their place as well. In order to allow more structure in the application program, it is possible to pass a list of terms rather than only a list of domain variables. In this way all information about some entity can be easily grouped together. It also allows more complex labeling methods which combine the assignment of multiple variables (like a preference value and a decision variable).

All search methods use a stable selection method. If several entries have the same heuristic value, then the first one is selected. The rest of the list is equal to the original list with the selected entry removed, the order of the non-selected entries does not change.

Integer values are not treated differently from the domain variables, they are selected only if their heuristic value is better than those of the other entries.

The pre-defined selection methods use the following criteria:

Any other name is taken as the name of a user-defined predicate of arity 2 which is expected to compute a selection criterion (typically a number), e.g.

my_select(X,Criterion) :-
	...	% compute Criterion from variable X
The variable-selection will then select the variable with the lowest value of Criterion. If several variables have the same value, the first one is selected.

The pre-defined choice methods have the following meaning:

Any other name is taken as the name of a user-defined predicate of arity 1, e.g.

my_choice(X) :-
	...	% make a choice on variable X
Alternatively, a term with 2 arguments can be given as the choice-method, e.g. my_choice(FirstIn,LastOut). this will lead to the invocation of a choice predicate with arity 3, e.g.
my_choice(X,In,Out) :-
	...	% make a choice on variable X, using In-Out
This allows user-defined state to be transferred between the subsequent invocations of the choice-predicate (the Out argument of a call to my_choice/3 for one variable is unified with the In argument of the call to my_choice/3 for the next variable, and so on).

The different search methods are

The option list is used to pass additional parameters to and from the procedure. The currently recognized options are:

Fail Conditions

Fails if the search tree generated does not contain any solution. For partial search methods, this does not mean that the problem does not have a solution, but only that the part of the tree generated did not contain one.

Resatisfiable

yes

Examples

top:-
	length(L,8),
	L :: 1..8,
	search(L,0,input_order,indomain,complete,[]).

top:-
	length(L,8),
	L :: 1..8,
	search(L,0,input_order,indomain,bbs(15),[]).

top:-
	length(L,8),
	L :: 1..8,
	search(L,0,input_order,indomain,lds(2),[]).

top:-
	length(L,8),
	L :: 1..8,
	search(L,0,input_order,indomain,credit(64,bbs(5)),[]).

top:-
	length(L,8),
	L :: 1..8,
	search(L,0,input_order,indomain,dbs(2,lds(1)),[]).

% a more complex example with different methods and heuristics
% the list to be assigned is a list of terms queen/2

:- local struct(queen(place,var)).

top:-
	member(Method,[complete,lds(2),credit(64,5),bbs(1000),dbs(5,10)]),
	member(Select,[first_fail,most_constrained,input_order]),
	member(Choice,[indomain,
	               indomain_min,
		       indomain_max,
		       indomain_middle,
		       indomain_median,
		       indomain_split,
		       indomain_random]),
	writeln(queen(Method,Select,Choice)),
	once(queen_credit(64,Select,Choice,Method,L,Back)),
	writeln(L),
	writeln(backtrack(Back)),
	fail.
top:-
	nl.

queen_credit(N,Select,Choice,Method,L,Back):-
	create_queens(1,N,Queens,L),
	setup(L),
	rearrange(Queens,Queens,[],[],Queens1),
	search(Queens1, var of queen, Select, Choice, Method, [backtrack(Back)]).

rearrange([],Last,Last,Res,Res).
rearrange([_],[Mid|Last],Last,Res,[Mid|Res]).
rearrange([_,_|S],[H|T],A1,In,Res):-
	rearrange(S,T,[A|A1],[H,A|In],Res).

create_queens(N,M,[],[]):-
	N > M,
	!.
create_queens(N,M,[queen with [place:N,var:X]|T],[X|L]):-
	X :: 1..M,
	N1 is N+1,
	create_queens(N1,M,T,L).

setup([]).
setup([H|T]):-
	setup1(H,T,1),
	setup(T).

setup1(_,[],_).
setup1(X,[Y|R],N):-
	X #\= Y,
	X #\= Y + N,
	Y #\= X + N,
	N1 is N+1,
	setup1(X,R,N1).


% this example shows how to pass information from one assignment step 
% to the next
% this uses a term of two arguments as the choice argument
% The example also shows the use of the option argument:
% the search tree generated is drawn with the daVinci graph drawing tool
% and the search is limited to 1000 nodes.
% The number of backtracking steps is returned in the variables Back.
:-local struct(country(name,color)).

top:-
	countries(C),
	create_countries(C,Countries,Vars),
	findall(n(A,B),n(A,B),L),
	setup(L,Countries),
	search(Countries,
	       color of country, % select based on this variable
	       most_constrained,
	       assign([1,2,3,4],Out), % this calls assign/3
	       complete,
	       [backtrack(Back),node(daVinci),nodes(1000)]),
	writeln(Vars),
	writeln(Back),
	writeln(Out).

create_countries([],[],[]).
create_countries([C|C1],[country with [name:C, color:V]|R1],[V|V1]):-
	V :: 1..4,
	create_countries(C1,R1,V1).

setup([],_L).
setup([n(A,B)|N1],L):-
	member(country with [name:A, color:Av],L),
	member(country with [name:B, color:Bv],L),
	Av #\= Bv,
	setup(N1,L).

% this is the choice predicate
% the first argument is the complete selected term
% the second is the input argument
% the third is the output argument
% here we pass a list of values and rotate this list from one step to the next
assign(country with color:X,L,L1):-
	rotate(L,L1),
	member(X,L).

rotate([A,B,C,D],[B,C,D,A]).

% another example of argument passing 
% here each entry gets the same information
% it is passed unchanged from one level to the next

top:-
	...
	length(L,N),
	L :: 1..10,
	...
        search(L,
	       0,
	       most_constrained,
	       % pass two lists as the In argument of assign
	       % try the odd numbers before the even numbers
	       assign([1,3,5,7,9]-[2,4,6,8,10],_), 
	       complete,[]),
	...

% this is the assignment routine
% the first argument is a 
% Pass the In argument as the Out argument
% try values from list L1 before values from list L2
assign(X,L1-L2,L1-L2):-
	member(X,L1);member(X,L2).

% and another example from square placement
% alternatively try minimal and maximal values first

:-local struct(square(x,y,size)).

top:-
	data(L),
	create_squares(L,Squares),
	...
        search(Squares,
	       0, % this value does not matter if input_order is chosen
	       input_order,
	       assign(min,_),
	       complete,
	       []),
	...

% the assignment routine
% alternate between min and max for consecutive levels in the search
assign(square with [x:X,y:Y],Type,Type1):-
	swap(Type,Type1),
	indomain(X,Type),
	indomain(Y,Type).

swap(max,min).
swap(min,max).

% this example shows that the choice routine may consist of several clauses
% the idea comes from a graph coloring heuristic

top:-
	length(L,N),
	L :: 1..100,
	...
        search(L,
	       0,
	       most_constrained,
	       assign(0,K), The In argument is the highest color used so far
	       complete,[]),
	...


% assign variable X either to one of the colors 1..K 
% which have already been used, or to the new color K+1
% we do not need to try other values K+2 etc, as this is a symmetry that
% we can avoid
assign(X,K,K):-
	X #=< K,
	indomain(X).
assign(K1,K,K1):-
	K1 is K+1.


% example showing use of the SBDS library with a user-defined choice method
% which calls sbds_try/2.

top:-
	dim(M, [8]),
	M[1..8] :: 1..8,
	...
	sbds_initialise(M,SymPreds,#=,[]),
	M =.. [_|L],	% get list of variables for search routine
	search(L,0,first_fail,sbds_indomain_max,sbds,[]).

sbds_indomain_max(X):-
	nonvar(X).
sbds_indomain_max(X):-
	var(X),
	maxdomain(X,Max),
	sbds_try(X,Max),
	sbds_indomain_max(X).

See Also

indomain / 1, indomain / 2, labeling / 1, fd : deleteff / 3, fd : deleteffc / 3, fd_sbds : sbds_initialise / 4, ic_sbds : sbds_initialise / 4, fd_sbds : sbds_initialise / 5, ic_sbds : sbds_initialise / 5, fd_sbds : sbds_try / 2, ic_sbds : sbds_try / 2