View source with formatted comments or as raw
    1/*
    2
    3    Part of CLP(R) (Constraint Logic Programming over Reals)
    4
    5    Author:        Leslie De Koninck
    6    E-mail:        Leslie.DeKoninck@cs.kuleuven.be
    7    WWW:           http://www.swi-prolog.org
    8		   http://www.ai.univie.ac.at/cgi-bin/tr-online?number+95-09
    9    Copyright (C): 2004, K.U. Leuven and
   10		   1992-1995, Austrian Research Institute for
   11		              Artificial Intelligence (OFAI),
   12			      Vienna, Austria
   13
   14    This software is part of Leslie De Koninck's master thesis, supervised
   15    by Bart Demoen and daily advisor Tom Schrijvers.  It is based on CLP(Q,R)
   16    by Christian Holzbaur for SICStus Prolog and distributed under the
   17    license details below with permission from all mentioned authors.
   18
   19    This program is free software; you can redistribute it and/or
   20    modify it under the terms of the GNU General Public License
   21    as published by the Free Software Foundation; either version 2
   22    of the License, or (at your option) any later version.
   23
   24    This program is distributed in the hope that it will be useful,
   25    but WITHOUT ANY WARRANTY; without even the implied warranty of
   26    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   27    GNU General Public License for more details.
   28
   29    You should have received a copy of the GNU Lesser General Public
   30    License along with this library; if not, write to the Free Software
   31    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
   32
   33    As a special exception, if you link this library with other files,
   34    compiled with a Free Software compiler, to produce an executable, this
   35    library does not by itself cause the resulting executable to be covered
   36    by the GNU General Public License. This exception does not however
   37    invalidate any other reasons why the executable file might be covered by
   38    the GNU General Public License.
   39*/
   40
   41:- module(itf_r,
   42	[
   43	    do_checks/8
   44	]).   45:- use_module(library(apply), [maplist/2]).   46:- use_module(bv_r,
   47	[
   48	    deref/2,
   49	    detach_bounds_vlv/5,
   50	    solve/1,
   51	    solve_ord_x/3
   52	]).   53:- use_module(nf_r,
   54	[
   55	    nf/2
   56	]).   57:- use_module(store_r,
   58	[
   59	    add_linear_11/3,
   60	    indep/2,
   61	    nf_coeff_of/3
   62	]).   63:- use_module('../clpqr/class',
   64	[
   65	    class_drop/2
   66	]).   67:- use_module(library(error), [type_error/2]).   68
   69do_checks(Y,Ty,St,Li,Or,Cl,No,Later) :-
   70	numbers_only(Y),
   71	verify_nonzero(No,Y),
   72	verify_type(Ty,St,Y,Later,[]),
   73	verify_lin(Or,Cl,Li,Y),
   74	maplist(call,Later).
   75
   76numbers_only(Y) :-
   77	(   var(Y)
   78	->  true
   79	;   integer(Y)
   80	->  true
   81	;   float(Y)
   82	->  true
   83	;   type_error(real, Y)
   84	).
   85
   86% verify_nonzero(Nonzero,Y)
   87%
   88% if Nonzero = nonzero, then verify that Y is not zero
   89% (if possible, otherwise set Y to be nonzero)
   90
   91verify_nonzero(nonzero,Y) :-
   92	(   var(Y)
   93	->  (   get_attr(Y,clpqr_itf,Att)
   94	    ->  setarg(8,Att,nonzero)
   95	    ;   put_attr(Y,clpqr_itf,t(clpr,n,n,n,n,n,n,nonzero,n,n,n))
   96	    )
   97	;   (   Y < -1.0e-10
   98	    ->	true
   99	    ;	Y > 1.0e-10
  100	    )
  101	).
  102verify_nonzero(n,_). % X is not nonzero
  103
  104% verify_type(type(Type),strictness(Strict),Y,[OL|OLT],OLT)
  105%
  106% if possible verifies whether Y satisfies the type and strictness of X
  107% if not possible to verify, then returns the constraints that follow from
  108% the type and strictness
  109
  110verify_type(type(Type),strictness(Strict),Y) -->
  111	verify_type2(Y,Type,Strict).
  112verify_type(n,n,_) --> [].
  113
  114verify_type2(Y,TypeX,StrictX) -->
  115	{var(Y)},
  116	!,
  117	verify_type_var(TypeX,Y,StrictX).
  118verify_type2(Y,TypeX,StrictX) -->
  119	{verify_type_nonvar(TypeX,Y,StrictX)}.
  120
  121% verify_type_nonvar(Type,Nonvar,Strictness)
  122%
  123% verifies whether the type and strictness are satisfied with the Nonvar
  124
  125verify_type_nonvar(t_none,_,_).
  126verify_type_nonvar(t_l(L),Value,S) :- ilb(S,L,Value).
  127verify_type_nonvar(t_u(U),Value,S) :- iub(S,U,Value).
  128verify_type_nonvar(t_lu(L,U),Value,S) :-
  129	ilb(S,L,Value),
  130	iub(S,U,Value).
  131verify_type_nonvar(t_L(L),Value,S) :- ilb(S,L,Value).
  132verify_type_nonvar(t_U(U),Value,S) :- iub(S,U,Value).
  133verify_type_nonvar(t_Lu(L,U),Value,S) :-
  134	ilb(S,L,Value),
  135	iub(S,U,Value).
  136verify_type_nonvar(t_lU(L,U),Value,S) :-
  137	ilb(S,L,Value),
  138	iub(S,U,Value).
  139
  140% ilb(Strict,Lower,Value) & iub(Strict,Upper,Value)
  141%
  142% check whether Value is satisfiable with the given lower/upper bound and
  143% strictness.
  144% strictness is encoded as follows:
  145% 2 = strict lower bound
  146% 1 = strict upper bound
  147% 3 = strict lower and upper bound
  148% 0 = no strict bounds
  149
  150ilb(S,L,V) :-
  151	S /\ 2 =:= 0,
  152	!,
  153	L - V < 1.0e-10. % non-strict
  154ilb(_,L,V) :- L - V < -1.0e-10. % strict
  155
  156iub(S,U,V) :-
  157	S /\ 1 =:= 0,
  158	!,
  159	V - U < 1.0e-10. % non-strict
  160iub(_,U,V) :- V - U < -1.0e-10. % strict
  161
  162%
  163% Running some goals after X=Y simplifies the coding. It should be possible
  164% to run the goals here and taking care not to put_atts/2 on X ...
  165%
  166
  167% verify_type_var(Type,Var,Strictness,[OutList|OutListTail],OutListTail)
  168%
  169% returns the inequalities following from a type and strictness satisfaction
  170% test with Var
  171
  172verify_type_var(t_none,_,_) --> [].
  173verify_type_var(t_l(L),Y,S) --> llb(S,L,Y).
  174verify_type_var(t_u(U),Y,S) --> lub(S,U,Y).
  175verify_type_var(t_lu(L,U),Y,S) -->
  176	llb(S,L,Y),
  177	lub(S,U,Y).
  178verify_type_var(t_L(L),Y,S) --> llb(S,L,Y).
  179verify_type_var(t_U(U),Y,S) --> lub(S,U,Y).
  180verify_type_var(t_Lu(L,U),Y,S) -->
  181	llb(S,L,Y),
  182	lub(S,U,Y).
  183verify_type_var(t_lU(L,U),Y,S) -->
  184	llb(S,L,Y),
  185	lub(S,U,Y).
  186
  187% llb(Strict,Lower,Value,[OL|OLT],OLT) and lub(Strict,Upper,Value,[OL|OLT],OLT)
  188%
  189% returns the inequalities following from the lower and upper bounds and the
  190% strictness see also lb and ub
  191llb(S,L,V) -->
  192	{S /\ 2 =:= 0},
  193	!,
  194	[clpr:{L =< V}].
  195llb(_,L,V) --> [clpr:{L < V}].
  196
  197lub(S,U,V) -->
  198	{S /\ 1 =:= 0},
  199	!,
  200	[clpr:{V =< U}].
  201lub(_,U,V) -->	[clpr:{V < U}].
  202
  203%
  204% We used to drop X from the class/basis to avoid trouble with subsequent
  205% put_atts/2 on X. Now we could let these dead but harmless updates happen.
  206% In R however, exported bindings might conflict, e.g. 0 \== 0.0
  207%
  208% If X is indep and we do _not_ solve for it, we are in deep shit
  209% because the ordering is violated.
  210%
  211verify_lin(order(OrdX),class(Class),lin(LinX),Y) :-
  212	!,
  213	(   indep(LinX,OrdX)
  214	->  detach_bounds_vlv(OrdX,LinX,Class,Y,NewLinX),
  215	    % if there were bounds, they are requeued already
  216	    class_drop(Class,Y),
  217	    nf(-Y,NfY),
  218	    deref(NfY,LinY),
  219	    add_linear_11(NewLinX,LinY,Lind),
  220	    (   nf_coeff_of(Lind,OrdX,_)
  221	    ->	% X is element of Lind
  222		solve_ord_x(Lind,OrdX,Class)
  223	    ;	solve(Lind)	% X is gone, can safely solve Lind
  224	    )
  225	;   class_drop(Class,Y),
  226	    nf(-Y,NfY),
  227	    deref(NfY,LinY),
  228	    add_linear_11(LinX,LinY,Lind),
  229	    solve(Lind)
  230	).
  231verify_lin(_,_,_,_)