View source with raw comments or as raw
    1/*  Part of INCLP(R)
    2
    3    Author:        Leslie De Koninck
    4    E-mail:        Leslie.DeKoninck@cs.kuleuven.be
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2006-2011, K.U. Leuven
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(inclpr_core,
   36	[
   37	    incremental/1,
   38	    change_incremental/1,
   39	    standard_domain/1,
   40	    change_standard_domain/1,
   41	    get_domain/2,
   42	    set_domain/2,
   43	    unify_trigger/1,
   44	    solve/0,
   45	    standard_domain/1,
   46	    {}/1
   47	]).   48
   49:- multifile prolog:message/3.   50
   51% toplevel printing
   52
   53prolog:message(query(YesNo,Bindings)) --> !,
   54    { collect_output(Bindings,[],Output) },
   55    Output,
   56    '$messages':prolog_message(query(YesNo,Bindings)).
   57
   58:- use_module(library(chr)).   59:- use_module(inclpr_interval_arithmetic,
   60	[
   61	    accepted_solution_domain/1,
   62	    accepted_solution_domain_2/1,
   63	    subdivide/3,
   64	    interval_contains/2,
   65	    interval_intersection/3
   66	]).   67:- use_module(inclpr_consistency,
   68	[
   69	    get_direct_full_evaluation/4,
   70	    check/8,
   71	    create_base_form/4,
   72	    create_partial_evaluation/5,
   73	    max_reduced/3
   74        ]).   75:- use_module(inclpr_symbolic_processing,
   76        [
   77	    to_standard_form/2,
   78	    partial_derivative/3
   79	]).   80:- use_module(inclpr_ordering,
   81        [
   82	    new/1,
   83	    get_next/2,
   84	    sv_try_remove/3,
   85	    sv_remove/3,
   86	    sv_remove_double/3,
   87	    sv_remove_number/2,
   88	    sv_merge/3,
   89	    sv_create/2
   90	]).   91:- use_module(inclpr_inversion,
   92	[
   93	    all_occurrences/1,
   94	    invert/3
   95	]).   96
   97%%%
   98
   99:- chr_type list(T) 	---> [] ; [T|list(T)].  100:- chr_type ie		---> n.  101:- chr_constraint
  102	% core
  103
  104	% collect_output(Bindings,OutputIn,OutputOut)
  105	collect_output(?any,?any,?any),
  106	% constraint(Constraint,Probe)
  107	constraint(?any,+any),
  108	% prepared_constraint(Constraint,Varlist,Probe)
  109	prepared_constraint(?any,?any,+any),
  110	% new_constraint(Constraint,Varlist,Probe)
  111	new_constraint(?any,?any,+any),
  112	% bound_lower(Var,Bound)
  113	bound_lower(-any,+float),
  114	% bound_upper(Var,Bound)
  115	bound_upper(-any,+float),
  116	
  117	% variable scheduling
  118
  119	% active_var(Phase,Var)
  120	active_var(+ie,-any),
  121	% queue(Phase,Varlist)
  122	queue(+ie,+list(any)), % !
  123	% inclusive_schedule_vars(Var)
  124	inclusive_schedule_vars(-any),
  125	% inclusive_schedule_vars(Phase,Var)
  126	inclusive_schedule_vars(+ie,-any),
  127	% exclusive_schedule_vars(Var)
  128	exclusive_schedule_vars(-any),
  129	% exclusive_schedule_vars(Phase,Var)
  130	exclusive_schedule_vars(+ie,-any),
  131	% schedule_var(Phase,Var)
  132	schedule_var(+ie,-any),
  133	% schedule_vars(Phase,Varlist)
  134	schedule_vars(+ie,+list(any)), %!
  135	% schedule_vars_excl(Phase,Varlist,Var)
  136	schedule_vars_excl(+ie,+list(any),-any), %!
  137	% schedule_constraint_vars(ID,IE)
  138	schedule_constraint_vars(+natural,+any),
  139	% schedule(Phase,Var)
  140	schedule(+ie,-any),
  141	% next_active_var(Phase)
  142	next_active_var(+ie),
  143	% get_active_var(Phase,Var)
  144	get_active_var(+ie,-any),
  145	% set_active_var(Phase,Var)
  146	set_active_var(+ie,-any),
  147		
  148	% trigger_list(Var,SortedVarlist)
  149	trigger_list(?any,?list(any)),
  150	% tl_connect_vars(Varlist,Varlist)
  151	tl_connect_vars(+list(any),?any), %!
  152	% tl_remove_doubles(Varlist,Var)
  153	tl_remove_doubles(+list(any),-any), %!
  154	% tl_remove_numbers(Varlist)
  155	tl_remove_numbers(+list(any)), %!
  156		
  157	% states
  158		
  159	% state_unify
  160	state_unify,
  161	% state_normal
  162	state_normal,
  163	% change_state(State)
  164	change_state(+any),
  165	% create_state
  166	create_state,
  167	% unify_tirgger(Var)
  168	unify_trigger(?any),
  169	% clp_core_trigger(Var)
  170	inclpr_core_trigger(?any),
  171	% unify_check_varlist_d_var(ID,IE,Var)
  172	unify_check_varlist_d_var(+natural,+ie,?any),
  173	% unify_check_varlist_d_number(ID,IE)
  174	unify_check_varlist_d_number(+natural,+ie),
  175		
  176	% phase scheduling
  177			
  178	% active_phase(Phase)
  179	active_phase(+ie),
  180	% phase_queue(Phaselist)
  181	phase_queue(+list(ie)),
  182	% get_phase(Phase)
  183	get_phase(?ie),
  184	% set_phase(Phase)
  185	set_phase(+ie),
  186	% next_phase
  187	next_phase,
  188	% schedule_phase(Phase)
  189	schedule_phase(+ie),
  190	% schedule_phases
  191	schedule_phases,
  192		
  193	% branch & prune
  194
  195	% lower_domain(Var)
  196	lower_domain(-any),
  197	% upper_domain(Var)
  198	upper_domain(-any),
  199		
  200	% varlist(ID,IE,Varlist)
  201	varlist_f(+natural,+ie,?list(any)),
  202	% varlist_d(ID,IE,Var,Varlist)
  203	varlist_d(+natural,+ie,?any,?list(any)),
  204	
  205	% constraint IDs
  206		
  207	% constraint_function(ID,Function)
  208	constraint_function(+natural,?any),
  209	% new_constraint_id(ID)
  210	new_constraint_id(+natural),
  211	% max_constraint_id(ID)
  212	max_constraint_id(+natural),
  213	% constraint_relation(ID,Relation)
  214	constraint_relation(+natural,+any),
  215	
  216		
  217	%
  218	rem_cons(+natural,+any),
  219	%
  220	chk_sol/1,
  221	%
  222	check_id(+natural,+any,?any),
  223	%
  224	in_cons/1,
  225				
  226	% natural interval extension
  227
  228	% n_i_e_create_projections(ID,Func,BaseForm,Varlist)
  229	n_i_e_create_projections(+natural,?any,?any,+list(any)), %!
  230	% n_i_e_prepare(ID,Func)
  231	n_i_e_prepare(+natural,?any),
  232	% n_i_e_p_c(ID,BaseForm,Var)
  233	n_i_e_p_c(+natural,?any,?any),
  234	% n_i_e_p_c_pd(ID,BaseForm,Var)
  235	n_i_e_p_c_pd(+natural,?any,?any),
  236		
  237	% inversion
  238		
  239	% inverted_constraint(ID,IE,BF,Var)
  240	inverted_constraint(+natural,+ie,?any,?any).  241		
  242:- chr_option(debug,off).  243:- chr_option(optimize,full).  244:- chr_option(toplevel_show_store,off).  245
  246%%%
  247
  248:- dynamic standard_domain/1.  249:- dynamic incremental/1.  250:- set_prolog_flag(float_format,'%.8f').  251
  252% States: the system is in unification state, in normal state or in no state.
  253% In unification state, the constraint store contains the state_unify/0
  254% constraint, in normal state, the constraint store contains the state_normal/0
  255% constraint. If neither are in the store, the system is in no state.
  256% change_state(State) changes the state to State, create_state sets the state
  257% to normal if the system is in no state and does nothing otherwise.
  258
  259state_1 @ state_unify \ state_unify <=> true.
  260state_2 @ state_normal \ state_normal <=> true.
  261state_3 @ state_unify \ change_state(unify) <=> true.
  262state_4 @ change_state(unify), state_normal <=> state_unify.
  263state_5 @ state_normal \ change_state(normal) <=> true.
  264state_6 @ change_state(normal), state_unify <=> state_normal.
  265state_7 @ change_state(normal) <=> state_normal.
  266state_8 @ change_state(unify) <=> state_unify.
  267state_9 @ state_normal \ create_state <=> true.
  268state_10 @ state_unify \ create_state <=> true.
  269state_11 @ create_state <=> state_normal.
  270
  271%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  272%%  _______  _____   ______ _______ %%
  273%%  |       |     | |_____/ |______ %%
  274%%  |_____  |_____| |    \_ |______ %%
  275%%                                  %%
  276%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  277
  278% Unification: when unifying, 4 modules have their attribute unification hook
  279% called: inclpr_domain, inclpr_core, inclpr_aliases and inclpr_ordering. The
  280% unification handling rules in this module (rules which require the
  281% state_unify/0 constraint) requires that all work with respect to domains,
  282% variable aliases and ordering is done before the constraints are processed.
  283% Also, the constraint store should be internally consistent as far as the
  284% CHR implementation is concerned.
  285% For each module, we add a unify_trigger/1 constraint with as argument the
  286% result of unification (a variable or a number). When 4 such unify_trigger/1
  287% constraints are available, i.e. one per module, then all necessary checks are
  288% done and we can proceed to the unification handling rules. The argument of
  289% unify_trigger/1 is used to determine whether variables have to be scheduled.
  290
  291% Unification hook for the inclpr_domain attribute:
  292% If unifying a variable with a number, it is checked whether the domain of the
  293% variable contains that number. If unifying two variables, the domains of the
  294% variables are intersected.
  295
  296inclpr_domain:attr_unify_hook(Domain,Y) :-
  297	(   number(Y)
  298	->  interval_contains(Domain,Y)
  299	;   get_attr(Y,inclpr_domain,YDomain)
  300	->  interval_intersection(Domain,YDomain,NewDomain),
  301	    put_attr(Y,inclpr_domain,NewDomain)
  302	;   put_attr(Y,inclpr_domain,Domain)
  303	),
  304	unify_trigger(Y).
  305
  306% These rules are the only ones of inclpr_core that can be activated by
  307% unification. All other require the presence of the state_unify/0 constraint.
  308% The rules cause a unify_trigger/1 constraint to be added, denoting that the
  309% CHR constraint store for this module is consistent with respect to the CHR
  310% implementation.
  311% The inclpr_core_trigger/1 constraints are used to detect unification: one
  312% such constraint is added for each new variable and the rules can only fire
  313% after unification, either with another variable, or with a number.
  314
  315unify_trigger_1 @ inclpr_core_trigger(V) \ inclpr_core_trigger(V) <=>
  316	unify_trigger(V).
  317unify_trigger_2 @ inclpr_core_trigger(N) <=>
  318	number(N) |
  319	unify_trigger(N).
  320
  321% This rule collects the 4 unify_trigger/1 constraints and puts the system in
  322% unification state. It also schedules variables for consistency checks if
  323% unification of two variables occurred.
  324
  325unify_trigger_3 @ unify_trigger(X), unify_trigger(X), unify_trigger(X),
  326    unify_trigger(X) <=>
  327	true |
  328	change_state(unify),
  329	(   var(X)
  330	->  inclusive_schedule_vars(X)
  331	;   true
  332	),
  333	state_normal.
  334
  335% get_domain(Variable,Domain)
  336%
  337% Returns in <Domain> the interval representing the current domain of variable
  338% <Variable>.
  339
  340get_domain(V,D) :- get_attr(V,inclpr_domain,D).
  341
  342% set_domain(Variable,Domain)
  343%
  344% Sets the current domain of variable <Variable> to the interval <Domain>.
  345
  346set_domain(V,D) :- put_attr(V,inclpr_domain,D).
  347
  348% Unification hook for the inclpr_aliases attribute:
  349% If unifying a variable with a number, both the center alias and the domain
  350% alias are unified with a canonical interval for that number. If unifying two
  351% variables, the aliases of both variables are unified.
  352
  353inclpr_aliases:attr_unify_hook(cd(C,D),Y) :-
  354	(   number(Y)
  355	->  C = i(Y,Y),
  356	    D = i(Y,Y)
  357	;   get_attr(Y,inclpr_aliases,cd(C,D))
  358	),
  359	unify_trigger(Y).
  360
  361% create_aliases(Variable)
  362%
  363% Creates variable aliases for the center and domain of variable <Variable>.
  364% These aliases are used so that we can differentiate between variable
  365% occurrences that have to be replaced by the domain, and occurrences that have
  366% to be replaced by the center of the domain (for center-value based interval
  367% extension). It also creates a inclpr_core_trigger/1 constraint for
  368% unification detection. Does nothing if the variable already has aliases.
  369
  370create_aliases(X) :-
  371	(   get_attr(X,inclpr_aliases,_)
  372	->  true
  373	;   put_attr(X,inclpr_aliases,cd(_,_)),
  374	    inclpr_core_trigger(X)
  375	).
  376
  377% create_domain(Variable)
  378%
  379% Gives the variable <Variable> a domain attribute, instantiated with the
  380% standard domain and creates an empty trigger_list/2 constraint for the
  381% variable. Trigger lists are used to activate variables that are connected via
  382% constraints when the domain of one of them has changed. If the variable
  383% already has a domain, nothing is done.
  384
  385create_domain(X) :-
  386	(   get_attr(X,inclpr_domain,_)
  387	->  true
  388	;   trigger_list(X,[]),
  389	    standard_domain(i(L1,U1)),
  390	    L is L1,
  391	    U is U1,
  392	    set_domain(X,i(L,U))
  393	).
  394
  395% get_aliases(Variable,Aliases)
  396%
  397% Returns in <Aliases> a term cd(C,D) with <C> the variable alias for the
  398% center of the domain of <Variable> and <D> the variable alias for the domain
  399% of <Variable>.
  400
  401get_aliases(X,Vid) :- get_attr(X,inclpr_aliases,Vid).
  402
  403% create_new_var(Variable)
  404%
  405% Prepares a new variable by adding it to the ordering, giving it aliases and
  406% giving it an initial domain.
  407
  408create_new_var(X) :-
  409	new(X),
  410	create_aliases(X),
  411	create_domain(X).
  412
  413% These rules generate a new unique identifier for a new constraint. Constraint
  414% identifiers are used to speedup matching constraints.
  415
  416constraint_id_1 @ new_constraint_id(ID), max_constraint_id(IDMax) <=>
  417	ID is IDMax + 1,
  418	max_constraint_id(ID).
  419constraint_id_2 @ new_constraint_id(ID) <=>
  420	ID = 0,
  421	max_constraint_id(0).
  422	
  423%%%%%%%%%%%%%%%%%
  424%               %
  425% Var Scheduler %
  426%               %
  427%%%%%%%%%%%%%%%%%
  428
  429% We use the concept of an active variable to denote the variable that is used
  430% in consistency checks and domain narrowing. Variables are scheduled in a
  431% queue and when an active variable has been processed, the next variable in
  432% the queue is used as the new active variable. There can be multiple queues to
  433% allow constraint processing in phases. We currently have a one-to-one
  434% relationship between phases and interval extensions.
  435
  436% inclusive_schedule_vars(Var)
  437%
  438% Schedules variable <Var> and all its connected variables for consistency
  439% checks for all interval extensions.
  440
  441inclusive_schedule_1 @ inclusive_schedule_vars(Var) <=>
  442	inclusive_schedule_vars(n,Var).
  443
  444% inclusive_schedule_vars(Phase,Var)
  445%
  446% Schedules variable <Var> and all its connected variables for consistency
  447% checks for the interval extension denoted by <Phase>.
  448
  449inclusive_schedule_2 @ inclusive_schedule_vars(Phase,Var) <=>
  450	schedule_var(Phase,Var),
  451	exclusive_schedule_vars(Phase,Var).
  452
  453% exclusive_schedule_vars(Var)
  454%
  455% Schedules the variables connected to <Var> for consistency checks for all
  456% interval extensions.
  457
  458exclusive_schedule_1 @ exclusive_schedule_vars(Var) <=>
  459	exclusive_schedule_vars(n,Var).
  460
  461% exclusive_schedule_vars(Phase,Var)
  462%
  463% Schedules the variables connected to <Var> for consistency checks for the
  464% interval extension denoted by <Phase>.
  465
  466exclusive_schedule_2 @ exclusive_schedule_vars(n,V),
  467    n_i_e_p_c(ID,_,V) #P1, varlist_f(ID,n,Varlist) #P2 ==>
  468	schedule_vars_excl(n,Varlist,V) pragma passive(P1), passive(P2).
  469exclusive_schedule_3 @ exclusive_schedule_vars(n,V),
  470    inverted_constraint(ID,n,_,V) #P1, varlist_f(ID,n,Varlist) #P2 ==>
  471	schedule_vars_excl(n,Varlist,V) pragma passive(P1), passive(P2).
  472
  473exclusive_schedule_6 @ exclusive_schedule_vars(_,_) <=> true.
  474
  475% schedule_constraint_vars(ID,IE)
  476%
  477% Schedules all the variables in the constraint with identifier <ID> for
  478% consistency checks for the interval extension denoted by <IE>.
  479
  480schedule_constraint_1 @ schedule_constraint_vars(ID,IE),
  481    varlist_f(ID,IE,Varlist) #P1 ==>
  482	schedule_vars(IE,Varlist) pragma passive(P1).
  483schedule_constraint_2 @ schedule_constraint_vars(_,_) <=> true.
  484
  485% mem_app(List,Variable,NewList)
  486%
  487% Adds <Variable> at the end of <List> if it does not appear in <List> and
  488% returns the extended list in <NewList>. If <Variable> is a member of <List>,
  489% <NewList> = <List>.
  490
  491mem_app([],X,[X]).
  492mem_app([H|T],X,[H|T2]) :-
  493	(   X == H
  494	->  T = T2
  495	;   mem_app(T,X,T2)
  496	).
  497
  498% queue/2 constraints contain a queue of variables that are scheduled for
  499% consistency checks for a given interval extension.
  500
  501% Rule representing an explicit functional dependency: one queue per interval
  502% extension.
  503
  504queue_1 @ queue(Phase,_) \ queue(Phase,_) <=> true.
  505
  506% schedule_var(IE,Variable)
  507%
  508% Schedules variable <Variable> for consistency checks for the interval
  509% extension denoted by <IE>.
  510
  511queue_2 @ schedule_var(Phase,Var), queue(Phase,Q) #P <=>
  512	true |
  513	mem_app(Q,Var,NewQ),
  514	queue(Phase,NewQ),
  515	(   \+ get_active_var(Phase,_)
  516	->  next_active_var(Phase)
  517	;   true
  518	)
  519	pragma passive(P).
  520queue_3 @ schedule_var(Phase,Var) <=>
  521	queue(Phase,[]),
  522	schedule_var(Phase,Var).
  523
  524% schedule_vars(IE,Variables)
  525%
  526% Schedules the variables in list <Variables> for consistency checks for the
  527% interval extension denoted by <IE>.
  528
  529queue_4 @ schedule_vars(Phase,[H|T]) <=>
  530	schedule_var(Phase,H),
  531	schedule_vars(Phase,T).
  532queue_5 @ schedule_vars(_,[]) <=> true.
  533
  534% schedule_vars_excl(IE,Variables,Variable)
  535%
  536% Schedules the variables in list <Variables> for consistency checks for the
  537% interval extension denoted by <IE> except for variable <Variable> which is
  538% not scheduled (even if it is in <Variables>).
  539
  540schedule_vars_excl(Phase,[H|T],V) <=>
  541	(   H \== V
  542	->  schedule_var(Phase,H)
  543	;   true
  544	),
  545	schedule_vars_excl(Phase,T,V).
  546schedule_vars_excl(_,[],_) <=> true.
  547
  548% next_active_var(IE)
  549%
  550% Sets the next variable in the queue of interval extension <IE> as the active
  551% variable for <IE>.
  552
  553queue_6 @ next_active_var(Phase), queue(Phase,[H|T]) #P <=>
  554	queue(Phase,T),
  555	set_active_var(Phase,H)
  556	pragma passive(P).
  557queue_7 @ next_active_var(Phase), active_var(Phase,_) #P <=>
  558	true pragma passive(P).
  559queue_8 @ next_active_var(_) <=> true.
  560
  561% get_active_var(IE,Variable)
  562%
  563% Returns in <Variable> the active variable for interval extension <IE>.
  564
  565active_var(Phase,AV) #P \ get_active_var(Phase,GAV) <=>
  566	AV = GAV pragma passive(P).
  567get_active_var(_,_) <=> fail.
  568
  569% set_active_var(IE,Variable)
  570%
  571% Sets <Variable> as the active variable for interval extension <IE>. This
  572% makes the current active variable passive if such exists.
  573
  574set_active_var(Phase,SAV), active_var(Phase,_) #P <=>
  575	active_var(Phase,SAV),
  576	schedule_phase(Phase) pragma passive(P).
  577set_active_var(Phase,SAV) <=>
  578	active_var(Phase,SAV),
  579	schedule_phase(Phase).
  580
  581% collect_output(Bindings,Temp,Output)
  582%
  583% Output processing for toplevel printing: <Bindings> is a list of elements
  584% <Name> = <Variable> where <Name> is a toplevel variable name and <Variable>
  585% is a variable. If <Variable> is an INCLPR variable, then it is output as
  586% `{<L> =< <Name> =< <U>}' with <L> its lower bound and <U> its upper bound.
  587% Other variables are output as `<Name> = <Variable>'. <Temp> contains the
  588% output for the bindings processed thusfar and is eventually unified with
  589% <Output>.
  590
  591collect_output([],Output,FinalOutput) <=> Output = FinalOutput.
  592collect_output([X=Y|T],Output,FinalOutput) <=>
  593	get_domain(Y,i(L,U)) |
  594	collect_output(T,['{~w =< ~w =< ~w}'-[L,X,U],nl|Output],FinalOutput).
  595collect_output([X=Y|T],Output,FinalOutput) <=>
  596	collect_output(T,['{~w = ~w}'-[X,Y],nl|Output],FinalOutput).
  597
  598%%%%%%%%%%%%%%%%%%%
  599%                 %
  600% Phase Scheduler %
  601%                 %
  602%%%%%%%%%%%%%%%%%%%
  603
  604% Phases denote different constraint processing steps. For each phase there is
  605% a queue of variables to be scheduled. The phase_queue/1 constraint contains
  606% a list of phases. For the active phase, the variable queue is processed. When
  607% this is done, the next phase in the phase queue becomes the active phase.
  608
  609% Explicit singleton declaration
  610
  611phase_queue(_) \ phase_queue(_) <=> true.
  612
  613% next_phase
  614%
  615% Sets the next phase in the phase queue as the active phase, making the
  616% current active phase passive if such exists. If the phase queue is empty, no
  617% phase is active.
  618
  619next_phase, phase_queue([H|T]) #P <=>
  620	phase_queue(T),
  621	set_phase(H) pragma passive(P).
  622next_phase, active_phase(_) #P <=>
  623	true pragma passive(P).
  624next_phase <=> true.
  625
  626% schedule_phase(Phase)
  627%
  628% Schedules <Phase> by adding it to the end of the phase queue if it is not
  629% already there and making it the active phase if no phase is currently active.
  630
  631schedule_phase(SP), phase_queue(PQ) #P <=>
  632	true |
  633	mem_app(PQ,SP,NewPQ),
  634	phase_queue(NewPQ),
  635	(   \+ get_phase(_)
  636	->  next_phase
  637	;   true
  638	)
  639	pragma passive(P).
  640schedule_phase(SP) <=>
  641	phase_queue([]),
  642	schedule_phase(SP).
  643
  644% schedule_phases
  645%
  646% Schedules all supported phases. Currently this is only the phase
  647% corresponding to using the natural interval extension.
  648
  649schedule_phases <=>
  650	schedule_phase(n).
  651
  652% get_active_phase(Phase)
  653%
  654% Returns in <Phase> the current active phase.
  655
  656active_phase(AP) #P \ get_phase(GP) <=>
  657	GP = AP pragma passive(P).
  658get_phase(_) <=> fail.
  659
  660% set_phase(Phase)
  661%
  662% Sets <Phase> as the current active phase. If another phase was active, this
  663% phase becomes passive.
  664
  665set_phase(SP), active_phase(_) #P <=>
  666	active_phase(SP) pragma passive(P).
  667set_phase(SP) <=> active_phase(SP).
  668
  669%%%%%%%%%%%%%%%%%%%%%%%%%%
  670%                        %
  671% Constraint Preparation %
  672%                        %
  673%%%%%%%%%%%%%%%%%%%%%%%%%%
  674
  675% {Constraints}
  676%
  677% Entry point for new constraints. <Constraints> is either a constraint or a
  678% conjunction of constraints.
  679
  680{C} :-
  681	nonvar(C),
  682	incremental(Inc),
  683	cns(C,Inc),
  684	(   Inc == false
  685	->  create_state
  686	;   true
  687	).
  688
  689% cns(Constraints,Incremental)
  690%
  691% Similar to {}/1 but used to differentiate between incremental constraint
  692% processing and processing in block. <Incremental> denotes the constraint
  693% processing mode and is either `true' or `false'.
  694
  695cns((Cons1,Cons2),Inc) :-
  696	!,
  697	nonvar(Cons1),
  698	cns(Cons1,Inc),
  699	nonvar(Cons2),
  700	cns(Cons2,Inc).
  701cns(Cons,Inc) :-
  702	!,
  703	constraint(Cons,p),
  704	(   Inc == true
  705	->  create_state
  706	;   true
  707	).
  708% new_constraint(Constraint,Variables,Probe)
  709%
  710% Prepares the processing of the constraint <Constraint> without changing the
  711% system to normal state. (see state_normal/0 and state_unify/0). <Probe> is
  712% currently not used. The constraint variables are listed in <Variables> and
  713% have been processed as new variables by create_new_var/1.
  714
  715new_constraint(X=Y,Vars,Prb) <=>
  716	true |
  717	(   var(X)
  718	->  (   var(Y)
  719	    ->  X = Y % rescheduling via unification checks
  720	    ;   number(Y)
  721	    ->  X is Y % rescheduling via unification checks
  722	    ;   prepared_constraint(X=Y,Vars,Prb)
  723	    )
  724	;   number(X)
  725	->  (   var(Y)
  726	    ->  Y is X % rescheduling via unification checks
  727    	    ;   number(Y)
  728	    ->  X =:= Y
  729	    ;   prepared_constraint(X=Y,Vars,Prb)
  730	    )
  731	;   prepared_constraint(X=Y,Vars,Prb)
  732	).
  733new_constraint(X>=Y,Vars,Prb) <=>
  734	true |
  735	(   var(X),
  736	    number(Y)
  737	->  bound_lower(X,Y),
  738	    inclusive_schedule_vars(X)
  739	;   number(X),
  740	    var(Y)
  741	->  bound_upper(Y,X),
  742	    inclusive_schedule_vars(Y)
  743	;   number(X),
  744	    number(Y)
  745	->  X >= Y
  746	;   prepared_constraint(X>=Y,Vars,Prb)
  747	).
  748new_constraint(X=<Y,Vars,Prb) <=>
  749	true |
  750	(   var(X),
  751	    number(Y)
  752	->  bound_upper(X,Y),
  753	    inclusive_schedule_vars(X)
  754	;   number(X),
  755	    var(Y)
  756	->  bound_lower(Y,X),
  757	    inclusive_schedule_vars(Y)
  758	;   number(X),
  759	    number(Y)
  760	->  X =< Y
  761	;   prepared_constraint(X=<Y,Vars,Prb)
  762	).
  763new_constraint(F,_,_) <=>
  764	throw(error(syntax_error('Illegal constraint relation'),
  765	    context({}/1,F))).
  766
  767% constraint(Constraint,Probe)
  768%
  769% Prepares the processing of the constraint <Constraint> without changing the
  770% system to normal state. (see state_normal/0 and state_unify/0). <Probe> is
  771% currently not used. The constraint variables are processed as new variables
  772% by create_new_var/1.
  773
  774constraint(Cons,Prb) <=>
  775	term_variables(Cons,Vars),
  776	maplist(create_new_var,Vars),
  777	new_constraint(Cons,Vars,Prb).
  778
  779% standard_domain(Domain)
  780%
  781% Dynamic predicate denoting the domain to be initially used by new variables.
  782% Can be changed by change_standard_domain/1.
  783
  784standard_domain(i(-100.0,100.0)).
  785
  786% incremental(Boolean)
  787%
  788% Dynamic predicate denoting whether constraints in one call of {}/1 are to
  789% be processed incrementally (i.e. after each constraint is read, consistency
  790% checks and narrowing is performed) or in blocks (i.e. consistency checks and
  791% narrowing are performed only after all constraints have been read). Can be
  792% changed by change_incremental/1. <Boolean> is either `true' or `false'.
  793
  794incremental(true).
  795
  796% change_incremental(Boolean)
  797%
  798% Changes the way constraints in one call of {}/1 are processed: incremental
  799% or in blocks. See incremental/1.
  800
  801change_incremental(X) :-
  802	retract(incremental(_)),
  803	assert(incremental(X)).
  804
  805% change_standard_domain(Domain)
  806%
  807% Changes the initial domain of new variables. See standard_domain/1.
  808
  809change_standard_domain(X) :-
  810	retract(standard_domain(_)),
  811	assert(standard_domain(X)).
  812
  813% prepared_constraint(Constraint,Variables,Probe)
  814%
  815% Prepares the creation of interval extensions for the constraint <Constraint>
  816% in variables <Variables>. This is only called for nontrivial constraints.
  817% <Probe> is currently not used.
  818
  819prepared_constraint(Cons,_,_) <=>
  820	true |
  821	to_standard_form(Cons,Std),
  822	(   term_variables(Std,[])
  823	->  call(Std)
  824	;   functor(Std,R,2),
  825	    arg(1,Std,F),
  826	    new_constraint_id(ID),
  827	    constraint_function(ID,F),
  828	    constraint_relation(ID,R),
  829	    n_i_e_prepare(ID,F)
  830	).
  831
  832%%%%%%%%%%%%%%%%%%%%%%
  833%                    %
  834% Unification Checks %
  835%                    %
  836%%%%%%%%%%%%%%%%%%%%%%
  837
  838% Trigger lists: the trigger_list/2 constraints relate a variable to a list of
  839% variables that is connected to it via constraints. This list is an ordered
  840% list of variables, making some operations like merging lists cheaper. The
  841% lists are used for variable scheduling.
  842
  843% Unification rules for trigger lists:
  844% Rule unify_trigger_list_1 works for the unification of two variables: the two
  845% 	related lists are merged and double occurrences of the unified
  846%	variables are removed in other lists.
  847% Rule unify_trigger_list_2 works for the unification of a variable with a
  848% 	number: the trigger list for the unified variable is removed and the
  849%	number is removed in other lists.
  850
  851unify_trigger_list_1 @ state_unify \ trigger_list(V,L1) #P1,
  852    trigger_list(V,L2) #P2 <=>
  853	sv_try_remove(L1,V,NewL1),
  854	sv_try_remove(L2,V,NewL2),
  855	sv_merge(NewL1,NewL2,L3),
  856	trigger_list(V,L3),
  857	tl_remove_doubles(L3,V)
  858	pragma passive(P1), passive(P2).
  859unify_trigger_list_2 @ state_unify \ trigger_list(N,L) #P1 <=>
  860	number(N) |
  861	tl_remove_numbers(L)
  862	pragma passive(P1).
  863
  864% using trigger lists for variable scheduling
  865
  866trigger_list(Var,List) #P1 \ schedule(Phase,Var) <=>
  867	schedule_vars(Phase,List)
  868	pragma passive(P1).
  869
  870% tl_remove_doubles(Variables,Variable)
  871%
  872% Removes double occurrences of variable <Variable> from the trigger lists of
  873% the variables in <Variables>
  874
  875tl_remove_doubles_1 @ tl_remove_doubles([],_) <=> true.
  876tl_remove_doubles_2 @ tl_remove_doubles([H|T],Var), trigger_list(H,L) #P1 <=>
  877	sv_remove_double(L,Var,NewL),
  878	trigger_list(H,NewL),
  879	tl_remove_doubles(T,Var)
  880	pragma passive(P1).
  881
  882% tl_remove_numbers(Variables)
  883%
  884% Removes a number from the trigger lists of the variables in <Variables>. Used
  885% by unification handling, so each list may contain up to one variable.
  886
  887tl_remove_numbers_1 @ tl_remove_numbers([]) <=> true.
  888tl_remove_numbers_2 @ tl_remove_numbers([H|T]), trigger_list(H,L) #P1 <=>
  889	sv_remove_number(L,NewL),
  890	trigger_list(H,NewL),
  891	tl_remove_numbers(T)
  892	pragma passive(P1).
  893
  894% tl_connect_vars(Variables)
  895%
  896% Connect the variables in <Variables> with eachother by adding all other
  897% variables to the trigger list of each variable.
  898
  899tl_connect_vars(Varlist) :-
  900	sv_create(Varlist,SortedVarlist),
  901	tl_connect_vars(SortedVarlist,SortedVarlist).
  902
  903% tl_connect_vars(List,Variables)
  904%
  905% Adds the variables in <Variables> to each variable <Variable> in <List>
  906% except for variable <Variable>. Initially, <List> and <Variables> are equal,
  907% but <List> is consumed and <Variables> remains.
  908
  909tl_connect_1 @ tl_connect_vars([],_) <=> true.
  910tl_connect_2 @ tl_connect_vars([H|T],L1), trigger_list(H,L2) #P1 <=>
  911	sv_remove(L1,H,L3),
  912	sv_merge(L3,L2,L4),
  913	trigger_list(H,L4),
  914	tl_connect_vars(T,L1)
  915	pragma passive(P1).
  916
  917% Unification handling for the natural interval extension:
  918%
  919% - Variable list of the constraint function has to be updated (duplicates or
  920%	number removed)
  921% - Variable lists of the derivatives have to be updated (duplicates of number
  922%	removed)
  923% - Unification of two variables: merging of partial derivatives
  924% - Unification with a number: removing partial derivative
  925% - Unification with a number: schedule consistency checks for involved
  926%	constraints
  927% - Inverted constraints and unification of two variables: create projection
  928%	constraints
  929
  930unify_n_i_e_var @ state_unify, n_i_e_p_c(ID,_,V) #passive \
  931    n_i_e_p_c(ID,_,V) #passive, varlist_f(ID,n,BFV) #passive <=>
  932	term_variables(BFV,NewBFV),
  933	varlist_f(ID,n,NewBFV),
  934	unify_check_varlist_d_var(ID,n,V).
  935unify_n_i_e_number @ state_unify \ n_i_e_p_c(ID,_,N) #passive,
  936    varlist_f(ID,n,BFV) #passive <=>
  937	number(N) |
  938	term_variables(BFV,NewBFV),
  939	varlist_f(ID,n,NewBFV),
  940	unify_check_varlist_d_number(ID,n),
  941	schedule_constraint_vars(ID,n).
  942
  943% Updating variable lists of the derivatives: unification of two variables
  944
  945unify_n_i_e_d_var_1 @ unify_check_varlist_d_var(ID,n,V) \
  946    varlist_d(ID,n,V,Varlist1) #passive,
  947    varlist_d(ID,n,V,Varlist2) #passive <=>
  948	term_variables(Varlist1+Varlist2,NewVarlist),
  949	varlist_d(ID,n,V,NewVarlist).
  950unify_n_i_e_d_var_2 @ unify_check_varlist_d_var(ID,n,V1) \
  951    varlist_d(ID,n,V2,Varlist) #passive <=>
  952	V1 \== V2 |
  953	term_variables(Varlist,NewVarlist),
  954	varlist_d(ID,n,V2,NewVarlist).
  955unify_n_i_e_d_var_3 @ unify_check_varlist_d_var(_,_,_) <=> true.
  956
  957% Updating variable lists of the derivatives: unification with a number
  958
  959unify_n_i_e_d_num_1 @ unify_check_varlist_d_number(ID,n) \
  960    varlist_d(ID,n,V,_) #passive <=>
  961	number(V) | true.
  962unify_n_i_e_d_num_2 @ unify_check_varlist_d_number(ID,n) \
  963    varlist_d(ID,n,V,Varlist) #passive <=>
  964	var(V) |
  965	term_variables(Varlist,NewVarlist),
  966	varlist_d(ID,n,V,NewVarlist).
  967unify_n_i_e_d_num_3 @ unify_check_varlist_d_number(_,_) <=> true.
  968
  969% Merging partial derivatives (var=var) / deleting partial derivative (number)
  970
  971unify_n_i_e_pd_var @ state_unify \ n_i_e_p_c_pd(ID,DBF1,V) #passive,
  972    n_i_e_p_c_pd(ID,DBF2,V) #passive <=>
  973	n_i_e_p_c_pd(ID,(DBF1)+(DBF2),V).
  974unify_n_i_e_pd_num @ state_unify \ n_i_e_p_c_pd(_,_,N) #passive <=>
  975	number(N) | true.
  976
  977% Inverted constraints: F = 0 -> X = Fx and Y = Fy and X = Y
  978% After unification, the number of occurrences of the unified variable has
  979% increased from 1 to 2.
  980unify_n_i_e_inv_inv @ state_unify \ inverted_constraint(ID,n,_,V) #passive,
  981    inverted_constraint(ID,n,_,V) #passive, varlist_f(ID,n,_) #passive,
  982    constraint_function(ID,F) #passive <=>
  983	create_base_form(n,F,BF,BFV),
  984	varlist_f(ID,n,BFV),
  985	n_i_e_p_c(ID,BF,V),
  986	partial_derivative(F,V,PD),
  987	create_base_form(n,PD,DBF,DBFV),
  988	varlist_d(ID,n,V,DBFV),
  989	n_i_e_p_c_pd(ID,DBF,V).
  990unify_n_i_e_inv_num @ state_unify \ inverted_constraint(ID,n,_,N) #passive,
  991    varlist_f(ID,n,Varlist) #passive <=>
  992	number(N) |
  993	term_variables(Varlist,NewVarlist),
  994	varlist_f(ID,n,NewVarlist),
  995	schedule_constraint_vars(ID,n).
  996% mixed forms
  997
  998% Projection and inversion: remove inversion and update pd
  999unify_n_i_e_inv_proj @ state_unify, n_i_e_p_c(ID,_,V) #passive \
 1000    n_i_e_p_c_pd(ID,_,V) #passive, inverted_constraint(ID,n,_,V) #passive,
 1001    varlist_f(ID,n,BFV) #passive, varlist_d(ID,n,V,_) #passive,
 1002    constraint_function(ID,F) #passive <=>
 1003	term_variables(BFV,NewBFV),
 1004	varlist_f(ID,n,NewBFV),
 1005	partial_derivative(F,V,PD),
 1006	create_base_form(n,PD,DBF,DBFV),
 1007	unify_check_varlist_d_var(ID,n,V),
 1008	varlist_d(ID,n,V,DBFV),
 1009	n_i_e_p_c_pd(ID,DBF,V).
 1010
 1011state_unify <=> true.
 1012
 1013
 1014%%%%%%%%%%%%%%%%%%%%
 1015%                  %
 1016% Variable Domains %
 1017%                  %
 1018%%%%%%%%%%%%%%%%%%%%
 1019
 1020% bound_upper(Variable,Bound)
 1021%
 1022% Reflects the effects of adding a constraint <Variable> =< <Bound> on the
 1023% inclpr_domain attribute.
 1024
 1025bound_upper(Var,Upper) <=>
 1026	true |
 1027	get_domain(Var,i(L,U)),
 1028	(   Upper >= U
 1029	->  true
 1030	;   Upper =:= L
 1031	->  Var = L
 1032	;   Upper < U,
 1033	    Upper > L
 1034	->  set_domain(Var,i(L,Upper))
 1035	).
 1036
 1037% bound_lower(Variable,Bound)
 1038%
 1039% Reflects the effects of adding a constraint <Variable> >= <Bound> on the
 1040% inclpr_domain attribute.
 1041
 1042bound_lower(Var,Lower) <=>
 1043	true |
 1044	get_domain(Var,i(L,U)),
 1045	(   Lower =< L
 1046	->  true
 1047	;   Lower =:= U
 1048	->  Var = U
 1049	;   Lower > L,
 1050	    Lower < U
 1051	->  set_domain(Var,i(Lower,U))
 1052	).
 1053
 1054%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 1055%%  _______  _____         _    _ _____ __   _  ______ %%
 1056%%  |______ |     | |       \  /    |   | \  | |  ____ %%
 1057%%  ______| |_____| |_____   \/   __|__ |  \_| |_____| %%
 1058%%                                                     %%
 1059%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 1060
 1061% solve
 1062%
 1063% Uses a branch and prune algorithm to find quasi-point solutions. These
 1064% solutions have a domain of very small (relative) width for all variables.
 1065
 1066solve :-
 1067	chk_sol(Fail),
 1068	(   var(Fail)
 1069	->  true
 1070	;   get_next(bottom,First),
 1071	    branch(First,_)
 1072	).
 1073
 1074% branch(Variable,Loop)
 1075%
 1076% If the variable <Variable> has a domain of acceptable small width, then the
 1077% next variable according to variable ordering is recursively checked.
 1078% Otherwise the domain of the variable is split in two halves and the lower
 1079% half is chosen as the new domain for <Variable>. On backtracking, the upper
 1080% half is tried. The variable <Loop> is instantiated to `false' when splitting
 1081% is done. It is used to prevent infinite looping if all domains satisfy the
 1082% precision criterion.
 1083
 1084branch(Var,Loop) :-
 1085	(   var(Var)
 1086	->  get_next(Var,Next),
 1087	    (   in_cons(Var),
 1088		get_domain(Var,Domain),
 1089		\+ accepted_solution_domain_2(Domain)
 1090	    ->  Loop = false,	
 1091		(   lower_domain(Var),
 1092		    create_state,
 1093		    chk_sol(Fail),
 1094		    (   var(Fail)
 1095		    ->	true
 1096		    ;	branch(Next,Loop)
 1097		    )
 1098		;   upper_domain(Var),
 1099		    create_state,
 1100		    chk_sol(Fail),
 1101		    (   var(Fail)
 1102		    ->	true
 1103		    ;   branch(Next,Loop)
 1104		    )
 1105		)
 1106	    ;	branch(Next,Loop)
 1107	    )
 1108	;   Var == top
 1109	->  (   var(Loop)
 1110	    ->	true
 1111	    ;	get_next(bottom,First),
 1112		branch(First,_)
 1113	    )
 1114	).
 1115
 1116% lower_domain(Variable)
 1117%
 1118% Replaces the domain of variable <Variable> by its lower half and schedules
 1119% the variable and its connected variables for consistency checks.
 1120
 1121lower_domain @ lower_domain(Var) <=>
 1122	get_domain(Var,Domain),
 1123	subdivide(lower,Domain,NewDomain) |
 1124	set_domain(Var,NewDomain),
 1125	inclusive_schedule_vars(Var),
 1126	schedule_phases.
 1127
 1128% upper_domain(Variable)
 1129%
 1130% Replaces the domain of variable <Variable> by its upper half and schedules
 1131% the variable and its connected variables for consistency checks.
 1132
 1133upper_domain @ upper_domain(Var) <=>
 1134	get_domain(Var,Domain),
 1135	subdivide(upper,Domain,NewDomain) |
 1136	set_domain(Var,NewDomain),
 1137	inclusive_schedule_vars(Var),
 1138	schedule_phases.
 1139
 1140% chk_sol(Fail)
 1141%
 1142% Checks whether we have reached a solution because the constraints cannot
 1143% cause more domain narrowing. If this is the case, <Fail> will be variable,
 1144% otherwise <Fail> will be unified with the atom `fail'. Constraints that
 1145% cannot cause more domain narrowing are removed from the constraint store.
 1146
 1147chk_sol(Fail), constraint_function(ID,_) ==>
 1148	check_id(ID,n,Fail).
 1149chk_sol(_) <=> true.
 1150
 1151% in_cons(Variable)
 1152%
 1153% Check whether the variable <Variable> belongs to a constraint. This might
 1154% change by using chk_sol/1.
 1155
 1156n_i_e_p_c(_,_,V) \ in_cons(V) <=> true.
 1157inverted_constraint(_,_,_,V) \ in_cons(V) <=> true.
 1158in_cons(_) <=> fail.
 1159
 1160% check_id(ID,IE,Fail)
 1161%
 1162% Checks whether the constraint with identifier <ID> can still cause domain
 1163% reductions with respect to interval extension <IE>. This is the case when the
 1164% range of the constraint function for the given interval extension and the
 1165% current domains of the constraint variables is of large enough relative
 1166% width. If it is the case, variable <Fail> remains a variable and the
 1167% constraint is removed from the constraint store. Otherwise, <Fail> is unified
 1168% with the atom `fail'.
 1169
 1170n_i_e_p_c(ID,BF,_), varlist_f(ID,n,BFV) \ check_id(ID,n,Fail) <=>
 1171	    true |
 1172	    (   max_reduced(n,BF,BFV)
 1173	    ->	rem_cons(ID,n)
 1174	    ;	Fail = fail
 1175	    ).
 1176inverted_constraint(ID,n,BF,_), varlist_f(ID,n,BFV) \ check_id(ID,n,Fail) <=>
 1177	    true |
 1178	    (   max_reduced(n,BF,BFV)
 1179	    ->  rem_cons(ID,n)
 1180	    ;   Fail = fail
 1181	    ).
 1182check_id(_,_,_) <=> true.
 1183	
 1184% rem_cons(ID,IE)
 1185%
 1186% Removes the CHR constraints related to the constraint with identifier <ID>
 1187% for interval extension <IE>.
 1188
 1189rem_cons(ID,n) \ n_i_e_p_c(ID,_,_) <=> true.
 1190rem_cons(ID,n) \ n_i_e_p_c_pd(ID,_,_) <=> true.
 1191rem_cons(ID,n) \ inverted_constraint(ID,n,_,_) <=> true.
 1192rem_cons(ID,n) \ varlist_f(ID,n,_) <=> true.
 1193rem_cons(ID,n) \ varlist_d(ID,n,_,_) <=> true.
 1194
 1195rem_cons(_,_) <=> true.
 1196
 1197%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 1198%% _____ __   _ _______ _______  ______ _    _ _______                         %%
 1199%%   |   | \  |    |    |______ |_____/  \  /  |_____| |                       %%
 1200%% __|__ |  \_|    |    |______ |    \_   \/   |     | |_____                  %%
 1201%%                                                                             %%
 1202%% _______ _     _ _______ _______ __   _ _______ _____  _____  __   _ _______ %%
 1203%% |______  \___/     |    |______ | \  | |______   |   |     | | \  | |______ %%
 1204%% |______ _/   \_    |    |______ |  \_| ______| __|__ |_____| |  \_| ______| %%
 1205%%                                                                             %%
 1206%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 1207
 1208%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 1209%                            %
 1210% Natural Interval Extension %
 1211%                            %
 1212%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 1213
 1214% Rules for performing consistency checks/domain narrowing:
 1215% performed with respect to an active variable and active phase, only in
 1216% normal state
 1217
 1218% inverted constraints (are equality constraints)
 1219check_inverted @ state_normal, active_phase(n), active_var(n,V),
 1220    inverted_constraint(ID,n,BF,V) #passive, varlist_f(ID,n,BFV) #passive ==>
 1221	true |
 1222	%writeln(ID:V),
 1223	get_direct_full_evaluation(n,BF,BFV,PE),
 1224	get_domain(V,Dom),
 1225	interval_intersection(Dom,PE,NewDom),
 1226	(   Dom == NewDom
 1227	->  true
 1228	;   set_domain(V,NewDom),
 1229	    schedule(n,V)
 1230	).
 1231
 1232% projection constraint: we need projection and partial derivative and
 1233% relation (=<, = or >=)
 1234check_n_i_e @ state_normal, active_phase(n), active_var(n,V),
 1235    n_i_e_p_c(ID,BF,V) #passive, varlist_f(ID,n,BFV) #passive,
 1236    n_i_e_p_c_pd(ID,DBF,V) #passive, varlist_d(ID,n,V,DBFV) #passive,
 1237    constraint_relation(ID,R) #passive ==>
 1238	true |
 1239	(   create_partial_evaluation(n,BF,BFV,PE,V),
 1240	    create_partial_evaluation(n,DBF,DBFV,DPE,V),
 1241	    get_domain(V,I1),
 1242	    check(n,PE,DPE,R,V,I1,lower,I2),
 1243	    check(n,PE,DPE,R,V,I2,upper,I3),
 1244	    (   I1 \== I3
 1245	    ->  nb_setval(inclpr_result,sd(I3))
 1246	    ;	nb_setval(inclpr_result,nothing)
 1247	    ),
 1248	    fail
 1249	;   catch(nb_getval(inclpr_result,Result),_,fail),
 1250	    nb_delete(inclpr_result),
 1251	    (   Result = sd(Domain)
 1252	    ->  set_domain(V,Domain),
 1253		schedule(n,V)
 1254	    ;   true
 1255	    )
 1256	).
 1257	
 1258% n_i_e_prepare(ID,Function)
 1259%
 1260% Prepares the projection constraints (>1 occurrence of a variable) and
 1261% inverted constraints (1 occurrence of a variable) for the natural interval
 1262% extension fo the constraint with function <Function> and identifier <ID>.
 1263
 1264prepare_n_i_e_1 @ n_i_e_prepare(ID,F) <=>
 1265	schedule_phase(n),
 1266	create_base_form(n,F,BF,BFV),
 1267	varlist_f(ID,n,BFV),
 1268	tl_connect_vars(BFV),
 1269	all_occurrences(F),
 1270	n_i_e_create_projections(ID,F,BF,BFV).
 1271
 1272% n_i_e_create_projections(ID,Function,BaseForm,Variables)
 1273%
 1274% Creates a projection constraint or inverted constraint (depending on the
 1275% number of occurrences of the variable at hand) for each variable for the
 1276% constraint with identifier <ID>, constraint function <Function> and natural
 1277% interval extension base form <BaseForm>.
 1278
 1279prepare_n_i_e_2 @ constraint_relation(ID,R) \
 1280    n_i_e_create_projections(ID,F,BF,[H|T]) <=>
 1281	true |
 1282	schedule_var(n,H),
 1283	(   R == (=),
 1284	    get_attr(H,inclpr_occurrence_count,one(_))
 1285	->  invert(F,H,Inv),
 1286	    create_base_form(n,Inv,InvBF,_),
 1287	    inverted_constraint(ID,n,InvBF,H)
 1288	;   n_i_e_p_c(ID,BF,H),
 1289	    partial_derivative(F,H,PD),
 1290	    create_base_form(n,PD,DBF,DBFV),
 1291	    varlist_d(ID,n,H,DBFV),
 1292	    n_i_e_p_c_pd(ID,DBF,H)
 1293	),
 1294	del_attr(H,inclpr_occurrence_count),
 1295	n_i_e_create_projections(ID,F,BF,T).
 1296prepare_n_i_e_3 @ n_i_e_create_projections(_,_,_,[]) <=> true.
 1297
 1298% next active var, next phase and exiting normal state.
 1299
 1300state_normal, active_phase(AP) \ active_var(AP,_) <=> next_active_var(AP).
 1301state_normal \ active_phase(_) <=> next_phase.
 1302state_normal <=> true.
 1303
 1304% explicit functional dependencies
 1305varlist_f(ID,P,_) \ varlist_f(ID,P,_) <=> true.
 1306constraint_function(ID,_) \ constraint_function(ID,_) <=> true.
 1307constraint_relation(ID,_) \ constraint_relation(ID,_) <=> true