1/*
    2
    3    Part of CLP(Q,R) (Constraint Logic Programming over Rationals and 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): 2006, K.U. Leuven and
   10		   1992-1995, Austrian Research Institute for
   11		              Artificial Intelligence (OFAI),
   12			      Vienna, Austria
   13
   14    This software is based on CLP(Q,R) by Christian Holzbaur for SICStus
   15    Prolog and distributed under the license details below with permission from
   16    all mentioned authors.
   17
   18    This program is free software; you can redistribute it and/or
   19    modify it under the terms of the GNU General Public License
   20    as published by the Free Software Foundation; either version 2
   21    of the License, or (at your option) any later version.
   22
   23    This program is distributed in the hope that it will be useful,
   24    but WITHOUT ANY WARRANTY; without even the implied warranty of
   25    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   26    GNU General Public License for more details.
   27
   28    You should have received a copy of the GNU Lesser General Public
   29    License along with this library; if not, write to the Free Software
   30    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
   31
   32    As a special exception, if you link this library with other files,
   33    compiled with a Free Software compiler, to produce an executable, this
   34    library does not by itself cause the resulting executable to be covered
   35    by the GNU General Public License. This exception does not however
   36    invalidate any other reasons why the executable file might be covered by
   37    the GNU General Public License.
   38*/
   39
   40%
   41% Answer constraint projection
   42%
   43
   44:- module(clpcd_project,
   45	[
   46	    drop_dep/1,
   47	    drop_dep_one/1,
   48	    make_target_indep/2
   49	]).   50
   51:- use_module(library(clpcd/indep)).   52:- use_module(library(clpcd/solve)).   53
   54%
   55% Collect the pivots in reverse order
   56% We have to protect the target variables pivot partners
   57% from redundancy eliminations triggered by fm_elim,
   58% in order to allow for reverse pivoting.
   59%
   60make_target_indep(Ts,Ps) :- make_target_indep(Ts,[],Ps).
   61
   62% make_target_indep(Targets,Pivots,PivotsTail)
   63%
   64% Tries to make as many targetvariables independent by pivoting them with a non-target
   65% variable. The pivots are stored as T:NT where T is a target variable and NT a non-target
   66% variable. The non-target variables are marked to be kept during redundancy eliminations.
   67
   68make_target_indep([],Ps,Ps).
   69make_target_indep([T|Ts],Ps0,Pst) :-
   70	(   get_attr(T,clpcd_itf,AttT),
   71	    arg(1,AttT,CLP),
   72	    arg(2,AttT,type(Type)),
   73	    arg(4,AttT,lin([_,_|H])),
   74	    nontarget(H,Nt)
   75	->  Ps1 = [T:Nt|Ps0],
   76	    get_attr(Nt,clpcd_itf,AttN),
   77	    arg(2,AttN,type(IndAct)),
   78	    arg(5,AttN,order(Ord)),
   79	    arg(6,AttN,class(Class)),
   80	    setarg(11,AttN,keep),
   81	    pivot(CLP,T,Class,Ord,Type,IndAct)
   82	;   Ps1 = Ps0
   83	),
   84	make_target_indep(Ts,Ps1,Pst).
   85
   86% nontarget(Hom,Nt)
   87%
   88% Finds a nontarget variable in homogene part Hom.
   89% Hom contains elements of the form l(V*K,OrdV).
   90% A nontarget variable has no target attribute and no keep_indep attribute.
   91
   92nontarget([l(V*_,_)|Vs],Nt) :-
   93	(   get_attr(V,clpcd_itf,Att),
   94	    arg(9,Att,n),
   95	    arg(10,Att,n)
   96	->  Nt = V
   97	;   nontarget(Vs,Nt)
   98	).
   99
  100% drop_dep(Vars)
  101%
  102% Does drop_dep_one/1 on each variable in Vars.
  103
  104drop_dep(Vs) :-
  105	var(Vs),
  106	!.
  107drop_dep([]).
  108drop_dep([V|Vs]) :-
  109	drop_dep_one(V),
  110	drop_dep(Vs).
  111
  112% drop_dep_one(V)
  113%
  114% If V is an unbounded dependent variable that isn't a target variable, shouldn't be kept
  115% and is not nonzero, drops all linear attributes of V.
  116% The linear attributes are: type, strictness, linear equation (lin), class and order.
  117
  118drop_dep_one(V) :-
  119	get_attr(V,clpcd_itf,Att),
  120	Att = t(CLP,type(t_none),_,lin(Lin),order(OrdV),_,_,n,n,_,n),
  121	\+ indep(CLP,Lin,OrdV),
  122	!,
  123	setarg(2,Att,n),
  124	setarg(3,Att,n),
  125	setarg(4,Att,n),
  126	setarg(5,Att,n),
  127	setarg(6,Att,n).
  128drop_dep_one(_)