[ library(gfd_search) | 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, gap_sbds, gap_sbdd)
L
a collection (a la collection_to_list/2) of domain variables (Arg = 0) or a collection of terms (Arg > 0)
Arg
an integer, which is 0 if the list is a list of domain variables, or greater than 0 if the list consists of terms with arity at least Arg (the value Arg indicating the argument that contains the domain variables to be labeled)
Select
the name of a predefined selection method (input_order, first_fail, smallest, largest, occurrence, most_constrained, max_regret, anti_first_fail), or an atom or compound term specifying a user-defined selection method
Choice
the name of a predefined choice method (indomain, indomain_min, indomain_max, indomain_middle, indomain_reverse_min, indomain_reverse_max, indomain_median, indomain_split, indomain_reverse_split, indomain_random, indomain_interval), or an atom or compound term specifying a user-defined method
Method
one of the following search method specifications: 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, gap_sbds, gap_sbdd
Option
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)), integer IC finite domains, and GFD integer finite domains (if loaded via lib(gfd_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 collection of terms rather than only a collection 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 collection (treated as a list) is equal to the original list with the selected entry removed, the order of the non-selected entries does not change.

The pre-defined selection methods are the following:

Any other atom will be taken as the specification of a user-defined selection predicate. This will be invoked with 2 arguments (X,Criterion) added and is expected to compute a selection criterion (typically a number) from a variable or value X. E.g. if Select is 'my_select', a predicate definition like the following has to be provided:

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

The above selection methods use the predefined delete/5 predicate. If this is not general enough, you can replace it with your own: if Select is given as select(my_delete), then my_delete(-SelectedVar,+List,-Rest,+Arg) will be invoked for selecting a variable from List.

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, to which the variable to be labeled (or a whole element of list L, in the Arg>0 case) is passed, 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).

In addition, a fixed argument can be passed: my_choice(Param) leads to invocation of my_choice(X,Param), and my_choice(Param,FirstIn,LastOut) leads to invocation of my_choice(X,Param,In,Out).

The different search methods are

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

Modules

This predicate is sensitive to its module context (tool predicate, see @/2).

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{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{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{name:A, color:Av},L),
	member(country{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{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{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),
	get_max(X,Max),
	sbds_try(X,Max),
	sbds_indomain_max(X).


% Example showing use of the GAP-based SBDS library with a user-defined
% choice method which calls sbds_try/2.  (For the GAP-based SBDD library,
% just substitute "sbdd" for each occurrence of "sbds" below.)

top:-
	dim(M, [8]),
	M[1..8] :: 1..8,
	sbds_initialise(M,[vars],values:1..8,[symmetry(s_n,[vars])],[]),
	M =.. [_|L],	% get list of variables for search routine
	search(L,0,first_fail,gap_sbds_indomain_max,gap_sbds,[]).

gap_sbds_indomain_max(X):-
	nonvar(X).
gap_sbds_indomain_max(X):-
	var(X),
	get_max(X,Max),
	sbds_try(X,Max),
	gap_sbds_indomain_max(X).

See Also

ic : indomain / 1, ic_symbolic : indomain / 1, gfd : indomain / 1, sd : indomain / 1, fd : indomain / 1, indomain / 2, ic : labeling / 1, gfd : labeling / 1, sd : labeling / 1, fd : labeling / 1, sd : deleteff / 3, fd : deleteff / 3, fd : deleteffc / 3, ic_sbds : sbds_initialise / 4, gfd_sbds : sbds_initialise / 4, fd_sbds : sbds_initialise / 4, ic_sbds : sbds_initialise / 5, gfd_sbds : sbds_initialise / 5, fd_sbds : sbds_initialise / 5, ic_gap_sbds : sbds_initialise / 5, ic_sbds : sbds_try / 2, gfd_sbds : sbds_try / 2, fd_sbds : sbds_try / 2, ic_gap_sbds : sbds_try / 2, ic_gap_sbdd : sbdd_initialise / 5, ic_gap_sbdd : sbdd_try / 2, library(ic_sbds), library(fd_sbds), library(ic_gap_sbds), library(ic_gap_sbdd)