1/*	The MIT License (MIT)
    2 *
    3 *	Copyright (c) 2024 Rick Workman
    4 *
    5 *	Permission is hereby granted, free of charge, to any person obtaining a copy
    6 *	of this software and associated documentation files (the "Software"), to deal
    7 *	in the Software without restriction, including without limitation the rights
    8 *	to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
    9 *	copies of the Software, and to permit persons to whom the Software is
   10 *	furnished to do so, subject to the following conditions:
   11 *
   12 *	The above copyright notice and this permission notice shall be included in all
   13 *	copies or substantial portions of the Software.
   14 *
   15 *	THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
   16 *	IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
   17 *	FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
   18 *	AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
   19 *	LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
   20 *	OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
   21 *	SOFTWARE.
   22 */
   23
   24/* adapted from Eclipse source file `generic_search.ecl` under 
   25 *    Mozilla Public License Version 1.1 (https://www.eclipseclp.org/license/)
   26 *
   27 *  Unsupported:
   28 *  Tree drawing via daVinci
   29 *  Hooks for user definintions
   30 *  Selection method `max_regret`
   31 *  Search methods based on Eclipse libraries `sbds` and GAP based `sbds` and `sbdd`
   32 *  `real`s are only searched using `split` and `indomain_split` using `splitsolve/1`
   33 *     but selection criteria (from a list) may use any "choice" or "search" methods
   34 *
   35 *  Adds `indomain_solve`/`solve`
   36 *
   37 *  Dependency: Uses `add_constraint/1` from v0.12.x
   38 *
   39 */
   40
   41:- module(clpBNR_search,[   %  exports:
   42	 search/6,       % backtracking search for solutions on list of vars or like-terms
   43	 delete/5,
   44	 indomain/2
   45	]).

clpBNR_search: Support for alternative search strategies based on Eclipse family of search libraries

This module is intended to be the equivalent of Eclipse's fd_search library but extended to support real domains. (See the predicate documentation for details.) Support for drawing search trees, user defined extensions, and the SBDS library in fd_search has not been implemented in clpBNR_search. */

   51:- use_module(library(lists),[flatten/2]).          % for flattening search input lists
   52:- use_module(library(option),[option/3]).          % for option list processing
   53:- use_module(library(clpBNR)).   54
   55% sandboxing for SWISH
   56:- multifile(sandbox:safe_global_variable/1).   57:- multifile(sandbox:safe_primitive/1).   58
   59:- set_prolog_flag(optimise,true).                  % scoped to file/module
   60
   61%
   62% clpBNR access support
   63%
   64get_size(X,0) :- number(X), !.  % constants have size 0
   65get_size(X,Size) :- 
   66	domain(X,integer(Min,Max)) -> Size is Max-Min+1; delta(X,Size).
   67
   68get_lwb(X,LB) :-
   69	get_bounds(X,LB,_).
   70
   71get_upb(X,UB) :-
   72	get_bounds(X,_,UB).
   73
   74get_bounds(X,Min,Max) :-
   75	range(X,[Min,Max]).
   76
   77%
   78% Minimal support for global var equivalent of Eclipse shelf create/destroy
   79% Global vars are created on global stack so will be garbage collected on success
   80%
   81shelf_create(Shelf,Value) :-
   82	gensym('$clpBNR_shelf_handle',Shelf),                % new shelf handle
   83	(nb_linkval(Shelf,Value) ; nb_delete(Shelf), fail).  % delete on backtracking
   84%   declare safe (non-ground global names)
   85sandbox:safe_primitive(clpBNR_search:shelf_create(_Shelf,_Value)). 
 search(+Vars:list, +Arg:integer, +Select:atom, +Choice:atom, +Method:atom, Options:list) is nondet
Succeeds if a solution can be found for the list of Vars (numbers, constrained vars or terms containing such vars) given the search strategy specified by Method, Select, and Choice; fails otherwise. On backtracking, alternative solutions are generated. Method and Select apply uniformly to intervals of either type (real or integer. The semantics of Choice may depend on type (see below).

If a Vars list element cannot be reduced to an interval (see Arg below), it is just ignored. This means, given suitable values for the other arguments, search/6 will succeed unless no solution can be found. In addition, for continuous domains, this may result in solutions in which it can't be conclusively proven that they contain no solutions with narrower domains, due to narrowing or precision restrictions. (This may also apply to finite domains if the search Method is not complete.)

If Arg has a value N greater than 0, the 'N`th argument of elements in the Vars list will be subjects for the search; if 0 the element itself (must be an interval) is used.

Supported Method's include:

  139search(Vars,Arg,Select,Choice,Method,Option) :-
  140	flatten(Vars, List),  % flat list of Vars/Terms
  141	integer(Arg),
  142	callable(Select),
  143	callable(Choice),
  144	is_search_method(Method),
  145	is_list(Option),
  146	!,
  147	reset_backtrack_count(Option),
  148	% top-level block to handle the limited number of nodes
  149	catch(search1(Method,List,Arg,Select,Choice),
  150	      error(domain_error(nodes,(N,Max)),_),
  151	      fail_error_message(clpBNR(search_nodes_failed(N,Max)))
  152	     ),  %%search_nodes_failed(N,Max)),
  153	get_backtrack_count(Option).
  154search(Vars,Arg,Select,Choice,Method,Option) :-
  155	fail_error_message(clpBNR(search((Vars,Arg,Select,Choice,Method,Option)))).
  156
  157fail_error_message(Msg) :-
  158	print_message(error,Msg),
  159	fail.
  160
  161:- multifile prolog:message//1.  162
  163prolog:message(clpBNR(search(Args))) -->
  164	[ "Invalid argument: search(~w).\n"-[Args] ].
  165
  166prolog:message(clpBNR(search_nodes_failed(N,Max))) -->
  167	[ "Node count = ~w, excceeded limit of ~w\n"-[N,Max] ].
  168
  169
  170% branch one the different search methods
  171search1(complete,L,Arg,Select,Choice):-
  172	labeling(L,Arg,Select,Choice).
  173search1(bbs(Steps),L,Arg,Select,Choice):-
  174	bbs(L,Arg,Select,Choice,Steps).
  175search1(credit(Credit,Steps),L,Arg,Select,Choice):-
  176	credit(L,Arg,Select,Choice,Credit,Steps).
  177search1(lds(Disc),L,Arg,Select,Choice):-
  178	lds(L,Arg,Select,Choice,Disc).
  179search1(dbs(Level,Steps),L,Arg,Select,Choice):-
  180	dbs(Level,Steps,L,Arg,Select,Choice).
  181
  182is_search_method(complete) :- !.
  183is_search_method(bbs(N)) :- integer(N), !.
  184is_search_method(credit(N,M)) :- integer(N), integer(M), !.
  185is_search_method(credit(N,bbs(M))) :- integer(N), integer(M), !.
  186is_search_method(credit(N,lds(M))) :- integer(N), integer(M), !.
  187is_search_method(lds(N)) :- integer(N), !.
  188is_search_method(dbs(N,M)) :- integer(N), integer(M), !.
  189is_search_method(dbs(N,bbs(M))) :- integer(N), integer(M), !.
  190is_search_method(dbs(N,lds(M))) :- integer(N), integer(M), !.
  191
  192%
  193%  different search methods
  194%
  195
  196% labeling(+List:list,
  197%           ++Arg:integer,
  198%	   ++Select:atom,
  199%	   +Choice:atom)
  200%
  201labeling(Xs,Arg,Select,Choice):-
  202	(delete(X,Xs,R,Arg,Select)
  203	 -> choose(X,Arg,Choice),
  204	    inc_backtrack_count,  % for reporting in backtrack option
  205	    labeling(R,Arg,Select,Choice)
  206	 ;  true
  207	).
  208
  209
  210% bbs(+List:list,
  211%        ++Arg:integer,
  212%	++Select:atom,
  213%	+Choice:atom,
  214%	++Steps:integer)
  215% same as labeling, but stops after Steps backtracking steps
  216%
  217bbs(L,Arg,Select,Choice,Steps):-
  218	b_getval('$clpBNR_search:backtrack', CurrentBacktracks),
  219	BacktrackLimit is CurrentBacktracks+Steps,
  220	nb_setval('$clpBNR_search:backtrack_limit',BacktrackLimit),
  221	catch(bbs1(L,Arg,Select,Choice),error(domain_error(backtracks,_),_),fail).
  222
  223bbs1(Xs,Arg,Select,Choice):-
  224	(delete(X,Xs,R,Arg,Select)
  225	 -> choose(X,Arg,Choice),
  226	    inc_backtrack_count_check,
  227	    bbs1(R,Arg,Select,Choice)
  228	 ;  true
  229	).
  230
  231
  232% credit(+List:list,++Arg:integer,++Select:atom,+Choice:atom or p/2,
  233%	 ++Credit:integer,
  234%	 ++Extra:integer or bbs(integer) or lds(integer))
  235% same as labeling, but uses credit to control search
  236% always give half the credit to the first child,
  237% half of the remaining credit to the next child, etc
  238
  239credit([],_Arg,_Select,_Choice,_Credit,_Extra) :- !.
  240credit(L,Arg,Select,Choice,Credit,Extra):-  %	L = [_|_],
  241	credit1(Credit,Extra,L,Arg,Select,Choice).
  242
  243credit1(1,bbs(Extra),Xs,Arg,Select,Choice):-
  244	!,
  245	bbs(Xs,Arg,Select,Choice,Extra).
  246credit1(1,lds(Extra),Xs,Arg,Select,Choice):-
  247	!,
  248	lds(Xs,Arg,Select,Choice,Extra).
  249credit1(1,Extra,Xs,Arg,Select,Choice):-
  250	integer(Extra),
  251	!,
  252	bbs(Xs,Arg,Select,Choice,Extra).
  253credit1(Credit,Extra,Xs,Arg,Select,Choice):-
  254	Credit > 1,
  255	(delete(X,Xs,R,Arg,Select)
  256	 -> shelf_create(Shelf,Credit),  % on backtracking, shelf destroyed
  257	    credit_choice(X,Arg,Choice,Shelf,Credit_child),
  258	    credit1(Credit_child,Extra,R,Arg,Select,Choice)
  259	 ;  true
  260	).
  261
  262credit_choice(X,Arg,Choice,Shelf,Credit_child) :-
  263	    choose(X,Arg,Choice),
  264	    inc_backtrack_count,
  265	    distribute_credit(Shelf,Credit_child,Rest),
  266	    (Rest == 0 -> !  % no more credit, cut away remaining choices in choose
  267	     ; true
  268	    ).
  269
  270% the credit distribution
  271% always give (a bit more than) half the credit to the next child
  272% keep the rest of the credit for the other children
  273% do not use up credit yourself
  274% if credit remains, and there are no more children, the credit is lost
  275% if children do not use their credit, it is lost
  276distribute_credit(Shelf,Credit,Rest):-
  277	b_getval(Shelf,Old),
  278	Credit is (Old+1)//2,
  279	Rest is Old-Credit,
  280	nb_linkval(Shelf,Rest).
  281%   declare safe (non-ground global names)
  282sandbox:safe_primitive(clpBNR_search:distribute_credit(_Shelf,_Credit,_Rest)). 
  283
  284
  285% lds(+List:list,++Arg:integer,++Select:atom,++Choice:atom,++LDS:integer)
  286% same as labeling, but only allows max LDS discrepancies against heuristic
  287% solution
  288% first tries 0, then 1, then 2, up to LDS discrepancies
  289%
  290lds(L,Arg,Select,Choice,Lds):-
  291	between(0,Lds,Disc),  % between(0,Lds,1,Disc),
  292	lds1(L,Arg,Select,Choice,Disc).
  293
  294lds1(Xs,Arg,Select,Choice,Disc):-
  295	(delete(X,Xs,R,Arg,Select)
  296	 -> (Disc==0
  297		 -> once(choose(X,Arg,Choice)), % allows only shallow backtracking
  298		    update_nodes_counter, % create new node name
  299		    lds1(R,Arg,Select,Choice,0)
  300	     ;  shelf_create(Shelf,Disc),	% Disc >= 1
  301	     	lds_choice(X,Arg,Choice,Shelf,Disc1),
  302		    lds1(R,Arg,Select,Choice,Disc1)
  303	    )
  304	 ;  Disc == 0  % do not allow to use less than given discrepancies
  305	).
  306
  307lds_choice(X,Arg,Choice,Shelf,Disc) :-
  308	choose(X,Arg,Choice),
  309	inc_backtrack_count,
  310	(dec_discrepancy(Shelf,Disc) -> true
  311	 ;  !,  % cut away remaining choices in choose
  312		Disc = 0
  313	).
  314
  315dec_discrepancy(Shelf,Disc):-
  316	b_getval(Shelf,Disc),
  317	Disc > 0,	% fail if already 0
  318	Disc1 is Disc - 1,
  319	nb_linkval(Shelf,Disc1).
  320%   declare safe (non-ground global names)
  321sandbox:safe_primitive(clpBNR_search:dec_discrepancy(_Shelf,_Disc)). 
  322
  323
  324% dbs(++Level:integer,
  325%	  ++Extra:integer or bbs(integer) or lds(integer),
  326%	  +List:list,++Arg:integer,++Select:atom,+Choice:atom)
  327%	 
  328% same as labeling, but uses depth bounded search to control search
  329% explore all choice points in the first Level variables
  330dbs(0,bbs(Extra),Xs,Arg,Select,Choice):-
  331	!,
  332	bbs(Xs,Arg,Select,Choice,Extra).
  333dbs(0,lds(Extra),Xs,Arg,Select,Choice):-
  334	!,
  335	lds(Xs,Arg,Select,Choice,Extra).
  336dbs(0,Extra,Xs,Arg,Select,Choice):-
  337	integer(Extra),
  338	!,
  339	bbs(Xs,Arg,Select,Choice,Extra).
  340dbs(Level,Extra,Xs,Arg,Select,Choice):-
  341	Level >= 1,
  342	(delete(X,Xs,R,Arg,Select)
  343	 -> choose(X,Arg,Choice),
  344	    inc_backtrack_count,
  345	    Level1 is Level-1,
  346	    dbs(Level1,Extra,R,Arg,Select,Choice)
  347	 ;  true
  348	).
  349
  350
  351% choose(?X,++Arg:integer,++Choice:atom)
  352% this predicate chooses a value for the selected term
  353% this choice is non-deterministic
  354choose(X,N,Choice):-
  355	translate_indomain_atom(Choice, Method),
  356	!,  % green cut??
  357	access(X,N,Var),
  358	indomain(Var,Method).
  359
  360% Translate search/6's indomain choice atoms to those used by indomain/2
  361%% no sbds or gap_* searches supported
  362translate_indomain_atom(indomain, enum).
  363translate_indomain_atom(indomain_min, min).
  364translate_indomain_atom(indomain_max, max).
  365translate_indomain_atom(outdomain_min, reverse_min).	% Zinc
  366translate_indomain_atom(outdomain_max, reverse_max).	% Zinc
  367translate_indomain_atom(indomain_reverse_min, reverse_min).
  368translate_indomain_atom(indomain_reverse_max, reverse_max).
  369translate_indomain_atom(indomain_middle, middle).
  370translate_indomain_atom(indomain_median, median).
  371translate_indomain_atom(indomain_split, split).
  372translate_indomain_atom(indomain_solve, solve).
  373translate_indomain_atom(indomain_reverse_split, reverse_split).
  374translate_indomain_atom(indomain_interval, interval).
  375translate_indomain_atom(indomain_random, random).
  376
  377
  378% access argument N of term X, if N=0, X is returned
  379access(X,0,X) :- !.          % most common case?
  380access(X,_,X) :- var(X), !.  % var = value 
  381access(X,N,Var):-
  382	N > 0,
  383	arg(N,X,Var).
  384
  385
  386%
  387% Backtracks and Nodes support
  388%
  389sandbox:safe_global_variable('$clpBNR_search:node_limit').
  390sandbox:safe_global_variable('$clpBNR_search:nodes').
  391sandbox:safe_global_variable('$clpBNR_search:backtrack').
  392sandbox:safe_global_variable('$clpBNR_search:one_level').
  393sandbox:safe_global_variable('$clpBNR_search:backtrack_limit').
  394
  395reset_backtrack_count(Option):-
  396	option(nodes(N),Option,2000),
  397	nb_setval('$clpBNR_search:node_limit',N),
  398	nb_setval('$clpBNR_search:nodes',0),
  399	nb_setval('$clpBNR_search:backtrack',0).
  400
  401get_backtrack_count(L):-
  402	option(backtrack(N),L,_),  % unifies var in option with backtack count
  403	b_getval('$clpBNR_search:backtrack',N).
  404
  405inc_backtrack_count:-
  406	update_nodes_counter,
  407	nb_setval('$clpBNR_search:one_level',true).
  408inc_backtrack_count:-
  409	update_backtrack_count(_),
  410	fail.
  411
  412inc_backtrack_count_check :-  % only called by `bbs1`
  413	update_nodes_counter,
  414	nb_setval('$clpBNR_search:one_level',true).
  415inc_backtrack_count_check :-
  416	update_backtrack_count(N1),
  417	b_getval('$clpBNR_search:backtrack_limit',L),  % initialized by `bbs` Method
  418	N1 > L,
  419	domain_error(backtracks,N1). %exit_block(bbs)
  420
  421update_backtrack_count(N1) :-
  422	b_getval('$clpBNR_search:one_level',true),
  423	nb_setval('$clpBNR_search:one_level',false),
  424	b_getval('$clpBNR_search:backtrack',N), N1 is N+1, nb_linkval('$clpBNR_search:backtrack',N1).
  425
  426update_nodes_counter:-
  427	nb_getval('$clpBNR_search:nodes',N), N1 is N+1, nb_linkval('$clpBNR_search:nodes',N1),
  428	b_getval('$clpBNR_search:node_limit', Max),
  429	(N1 >= Max
  430	 -> domain_error(nodes,(N1,Max)) %exit_block(nodes)
  431	 ;  true
  432	).
 delete(?X:numeric, +Terms:list, ?Rest:list, +Arg:integer, +Select:atom) is semidet
Succeeds if X can be unified with an numeric element (number or interval) selected from the Terms list according to Select; the rest of the list is unified with Rest (includes any non-numeric). Fails if there are no numeric values in Terms or if an invalid Select method is specified. Terms may include numbers, clpBNR domain variables, or terms whose Arg argument is a number or domain variable. (Arg = 0 implies use of Vars element itself.)

Valid values of Select are documented in search/6.

*/

  442% delete(-X,+List:non_empty_list,-R:list,++Arg:integer,++Select:atom)
  443% choose one entry in the list based on a heuristic; this is a deterministic selection
  444% a special case for input_order to speed up the selection in that case
  445% Note clpBNR integer and real
  446delete(X,Terms,Rest,Arg,Select) :- 
  447	delete1(Select,X,Terms,Rest,Arg).       % reorder arguments
  448
  449delete1(input_order,X,List,Rest,Arg) :- !,  % select in list order
  450	List = [Term|Terms],
  451	(delete_valid(Arg,Term)
  452	 -> X = Term,
  453	    Rest = Terms
  454	 ;  delete1(input_order,X,Terms,Tail,Arg),
  455	    Rest = [Term|Tail]
  456	).
  457delete1(Select,X,List,Rest,Arg) :-          % select based on criterion
  458	(memberchk(Select,                      % rest of supported values ...
  459[first_fail, anti_first_fail, smallest, largest, occurrence, most_constrained]
  460	          )
  461	 -> NaN is nan,
  462	    (Select == most_constrained -> Crit = crit(NaN,NaN) ; Crit = NaN),
  463	    find_best_and_rest(List,Crit,_,X,Rest/Rest,Arg,Select),  % scan for best           
  464	    delete_valid(Arg,X)                 % ensure numeric
  465	 ;  fail_error_message(clpBNR(delete_method(Select)))  
  466	).                     
  467
  468prolog:message(clpBNR(delete_method(Select))) -->
  469	[ "Invalid Select method: ~w .\n"-[Select] ].
  470
  471delete_valid(0,X) :- !,
  472	(number(X) -> true ; interval(X)).
  473delete_valid(Arg,X) :- 
  474	compound(X), 
  475	Arg > 0, 
  476	arg(Arg,X,Val),
  477	delete_valid(0,Val).
  478
  479find_best_and_rest([], _CritOld, BestTerm, BestTerm, _Rest/[], _Arg, _Select) :- !.
  480find_best_and_rest([Term|Terms], CritOld, BestTerm, X, Rest/Tail, Arg, Select) :-
  481	access(Term,Arg,Var), access(BestTerm,Arg,BestVal),
  482	(number(Var)                        % pick constants and stop
  483	 -> X = Term, 
  484	    (interval(BestVal) -> Tail = [BestTerm|Terms] ; Tail = Terms)
  485	 ;  find_value(Select,Var,CritNew),
  486	    (better_item(CritNew,CritOld) 	% better than the old one ?
  487	     -> (interval(BestVal) -> Tail = [BestTerm|NxtTail] ; NxtTail = Tail),  % put interval(Best) in Rest
  488	        find_best_and_rest(Terms, CritNew, Term, X, Rest/NxtTail, Arg, Select)
  489	     ;  Tail = [Term|NxtTail],      % put Term in Rest
  490	        find_best_and_rest(Terms, CritOld, BestTerm, X, Rest/NxtTail, Arg, Select)
  491	    )
  492	).
  493
  494better_item(crit(SizeNew,NumberNew),crit(SizeOld,NumberOld)) :-  % most_constrained
  495	(better_item(SizeNew,SizeOld)
  496	 -> true
  497	 ;  better_item(NumberNew,NumberOld)
  498	).
  499better_item(CritNew,CritOld) :- number(CritNew), number(CritOld),
  500	(CritNew is nan
  501	 -> fail                                          % nan is never better
  502	 ; (CritOld is nan
  503	    -> true                                       % non-nan is better than nan
  504	    ;  CritNew < CritOld)                         % othewise less is better 
  505	).
  506
  507% find_value(++Select:atom,?X:dvarint,
  508%	     -Crit:number or crit(number,number))
  509%
  510% Find a heuristic value from a domain variable: the smaller, the better.
  511% Values will be compared using @<, so be aware of standard term ordering!
  512% If the Criterion remains uninstantiated, this indicates an optimal value,
  513% which will be picked without looking any further down the list.
  514% Note: should work for clpBNR integer and real intervals
  515find_value(first_fail,X,Size) :-
  516	get_size(X,Size), !.
  517find_value(anti_first_fail,X,Number) :- !,
  518	get_size(X,Size), !,		    % can be 1.0Inf
  519	Number is -Size.				% -1.0Inf @< -99
  520find_value(smallest,X,Min) :-
  521	get_lwb(X,Min), !.
  522find_value(largest,X,Number) :-
  523	get_upb(X,Max), !,
  524	Number is -Max.
  525find_value(occurrence,X,Number) :-
  526	interval_degree(X,Nr), !,       % constants have degree 0, cheap op for clpBNR)
  527	Number is -Nr.
  528find_value(most_constrained,X,crit(Size,Number)) :-
  529	find_value(first_fail,X,Size),
  530	find_value(occurrence,X,Number),
  531	!.
  532find_value(_Select,_X,Crit) :-
  533	Crit is nan.      % invalid X, Crit = nan
 indomain(?X:numeric, +Choice:atom) is semidet
Succeeds if X (number or interval) can be narrowed or instantiated according to the heuristic specified by Choice, subject to any constraints. On backtracking alternative values are generated. Fails if the first argument is non-numeric, the heuristic is not supported, or no values can be found subject by the heuristic subject to current constraints.

For integer domains, indomain/2 will generate integer values from the domain in an order defined by the heuristic; for real domains, sub-domains will be generated by splitting at a point defined by the heuristic. In the latter case, the predicate may succeed without splitting, e.g., some heuristics may choose not to split on a point solution (middle, solve, ..).

Supported values for Choice include:

  559% indomain(?X:dvarint,++Method:atomic)
  560% IndomainType is either one of min, max, middle or an integer
  561% these indomain versions remove the previous value on backtracking
  562% Note: only assigns values to finite domain (i.e., clpBNR integer) variables
  563indomain(X,Method):-
  564	domain_type(X,Type) -> indomain1(Method,X,Type) ; number(X).
  565
  566domain_type(X,Type)    :- 
  567	domain(X,D),          % fails if not an interval
  568	functor(D,Type,2).    % D=Type(_,_).
  569	
  570indomain1(enum,X,Type) :- !,
  571	indomain_enum(Type,X).
  572indomain1(min,X,Type) :- !,
  573	get_lwb(X,Min),
  574	indomain_min(Type,X,Min).
  575indomain1(max,X,Type):- !,
  576	get_upb(X,Max),
  577	indomain_max(Type,X,Max).
  578indomain1(reverse_min,X,Type) :- !,
  579	get_lwb(X,Min),
  580	outdomain_min(Type,X,Min).
  581indomain1(reverse_max,X,Type) :- !,
  582	get_upb(X,Max),
  583	outdomain_max(Type,X,Max).
  584indomain1(middle,X,Type) :- !,
  585	indomain_middle(Type,X).
  586indomain1(median,X,Type) :- !,
  587	indomain_median(Type,X).
  588indomain1(split,X,Type) :- !,
  589	indomain_split(Type,X).
  590indomain1(reverse_split,X,Type) :- !,
  591	indomain_reverse_split(Type,X).
  592indomain1(solve,X,_Type) :- !,
  593	solve(X).
  594indomain1(interval,X,Type) :- !,    % clpBNR intervals are compact (no gaps), so use split
  595	indomain_split(Type,X).
  596indomain1(random,X,Type) :- !,
  597	indomain_random(Type,X).
  598indomain1(Value,X,integer):- !,
  599	integer(Value),
  600	get_bounds(X,Min,Max),
  601	( Value =< Min ->
  602	    % if the starting value is too small, use indomain_min
  603	    indomain_min(integer,X,Min)
  604	; Value >= Max ->
  605	    % if the starting value is too large, use indomain_max
  606	    indomain_max(integer,X,Max)
  607	;   % enumerate from a starting value inside the domain
  608	    % From fd_search: is this enough in all cases ??
  609	    Range is 2*max(Max-Value,Value-Min)+1,
  610	    indomain_from(X,Value,1,Range)
  611	).
  612indomain1(Value,X,real):-
  613	number(Value),
  614	get_bounds(X,Min,Max),
  615	( (Min >= Value ; Value >=Max)
  616	 -> fail   % Value not in domain, cannot do anything
  617	 ;   % if Value is not a solution split the domain if not a solution
  618	    (\+(X=Value)
  619	     -> (add_constraint(X =< Value) ; add_constraint(Value =< X))
  620	     ;  true        % Value is in domain, can't split real on this value
  621	    )
  622	).
  623
  624indomain_enum(integer,X) :-
  625	enumerate(X).	
  626indomain_enum(real,_X).  % enumeration of real - succeed with no narrowing or choicepoint
  627
  628% indomain_min(?X:dvar, ++Value:integer)
  629% the choice consists in either taking the proposed value or in excluding it
  630% and choosing another one
  631indomain_min(integer,X,X).
  632indomain_min(integer,X,Min):-  % if integer, can remove current lb
  633	add_constraint(X > Min),
  634	get_lwb(X,New),
  635	indomain_min(integer,X,New).
  636indomain_min(real,_X,_Min).     % if real, can't narrow further
  637
  638outdomain_min(integer,X,Min):-
  639	add_constraint(X > Min),
  640	get_lwb(X,New),
  641	outdomain_min(integer,X,New).
  642outdomain_min(integer,X,X).
  643outdomain_min(real,_X,_Min).
  644
  645% indomain_max(?X:dvar, ++Value:integer)
  646% the choice consists in either taking the proposed value or in excluding it
  647% and choosing another one
  648indomain_max(integer,X,X).
  649indomain_max(integer,X,Max):- % if integer, can remove current ub
  650	add_constraint(X < Max),
  651	get_upb(X,New),
  652	indomain_max(integer,X,New).
  653indomain_max(real,_X,_Max).     % if real, can't narrow further
  654
  655outdomain_max(integer,X,Max):-
  656	add_constraint(X < Max),
  657	get_upb(X,New),
  658	outdomain_max(integer,X,New).
  659outdomain_max(integer,X,X).
  660outdomain_max(real,_X,_Max).
  661
  662indomain_middle(integer,X) :-
  663	get_bounds(X,Min,Max),
  664	Value is (Min+Max)//2,    % default rounds toward 0, different from split	
  665	indomain1(Value,X,integer).  % alternating around value
  666indomain_middle(real,X) :-    % same as splitsolve on single var
  667	(small(X) 
  668	 -> true                  % small, don't split further
  669	 ;  midpoint(X,Middle),   % split at midpoint
  670	    ( add_constraint(X =< Middle) ; add_constraint(Middle =< X) ),
  671	    indomain_middle(real,X)
  672	).
  673
  674indomain_median(integer,X) :- % same as middle for integers (intervals are compact)
  675	indomain_middle(integer,X).
  676indomain_median(real,X) :-
  677	(small(X) 
  678	 -> true                  % small, don't split further
  679	 ;  median(X,Median),     % split at median
  680	    (add_constraint(X =< Median) ; add_constraint(Median =< X) ),
  681	    indomain_median(real,X)
  682	).
  683
  684% split the domain until only an integer value is left or real interval sufficiently narrow
  685indomain_split(_Type,X):-
  686	number(X),
  687	!.
  688indomain_split(integer,X):-
  689	get_bounds(X,Min,Max),
  690	Middle is (Min+Max) div 2,  % Note rounds toward -inf, different definition of middle 
  691	( add_constraint(X =< Middle) ; add_constraint(Middle < X) ),
  692	indomain_split(integer,X).
  693indomain_split(real,X):- 
  694	indomain_middle(real,X).
  695
  696indomain_reverse_split(integer,X):-
  697	integer(X),
  698	!.
  699indomain_reverse_split(integer,X):-
  700	get_bounds(X,Min,Max),
  701	Middle is (Min+Max) div 2,    % Note rounds toward -inf, different definition of middle 
  702	( add_constraint(X > Middle) ; add_constraint(Middle >= X) ),
  703	indomain_reverse_split(integer,X).
  704indomain_reverse_split(real,X):-
  705	(small(X) 
  706	 -> true  % don't split further
  707	 ;  midpoint(X,Middle),
  708	    ( add_constraint(X >= Middle) ; add_constraint(Middle >= X) ),
  709	    indomain_reverse_split(real,X)
  710	).
  711
  712% choose values from the domain at random; on backtracking, the previous value
  713% is removed, so that it can be used for a complete enumeration
  714indomain_random(Type,X):-
  715	random_value(Type,X,Try),	
  716	indomain_random(Type,X,Try).
  717
  718random_value(integer,X,Try) :-
  719	get_bounds(X,Min,Max),
  720	Try is Min+random(Max-Min+1).      % random:random_between/3
  721random_value(real,X,Try) :-
  722	get_bounds(X,Min,Max),
  723	Try is Min+random_float*(Max-Min).
  724
  725indomain_random(integer,X,X).
  726indomain_random(integer,X,Try):-
  727	add_constraint(X <> Try),
  728	indomain_random(integer,X).
  729indomain_random(real,X,Try) :-
  730	split_random(10,X,Try).           % try up to 10 random values for non-solution
  731
  732split_random(0,_X,_Try) :- !.         % stop, failed to find splittable point
  733split_random(_Ct,X,_Try) :-
  734	small(X), !.                      % stop, too small to split  
  735split_random(Ct,X,Try) :-
  736	(\+(X = Try)                      % split on non-solution 
  737	 -> ( add_constraint(X =< Try) ; add_constraint(Try =< X) ),
  738	    indomain_random(real,X)       % rinse and repeat
  739	 ;  random_value(real,X,NxtTry),  % can't split on this Value, try another 
  740	 	NxtCt is Ct-1,                % decrement Ct
  741	 	split_random(NxtCt,X,NxtTry)  % rinse and repeat
  742	).
  743
  744% indomain_from(?X:dvar, ++Value:integer, ++Inc:integer, ++Range:integer)
  745% the choice consists in either taking the proposed value or in excluding it
  746% and choosing another one
  747% the next value is always the old value plus the increment
  748% the next increment is one bigger than the previous, but of opposite sign
  749% 1, -2, 3, -4, 5, -6, 7 ...
  750% if the increment becomes too large, you can stop
  751indomain_from(X,X,_,_).
  752indomain_from(X,Value,Inc,Range):-
  753	add_constraint(X