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:- module(clpcd_attributes,
   41	[
   42	    project_attributes/2
   43	]).   44
   45:- use_module(library(clpcd/fourmotz)).   46:- use_module(library(clpcd/geler)).   47:- use_module(library(clpcd/project)).   48:- use_module(library(clpcd/store)).   49:- use_module(library(clpcd/redund)).   50:- use_module(library(clpcd/solve)).   51:- use_module(library(clpcd/class)).   52:- use_module(library(clpcd/ordering)).   53
   54%:- public project_attributes/2. 		% xref.pl
   55
   56%
   57% interface predicate
   58%
   59% May be destructive (either acts on a copy or in a failure loop)
   60%
   61project_attributes(TargetVars,Cvas) :-
   62	sort(TargetVars,Tvs),		% duplicates ?
   63	sort(Cvas,Avs),			% duplicates ?
   64	get_clp(TargetVars,CLP),
   65	(   nonvar(CLP)
   66	->  mark_target(Tvs),
   67	    project_nonlin(Tvs,Avs,NlReachable),
   68	    (   Tvs == []
   69	    ->  drop_lin_atts(Avs)
   70	    ;   redundancy_vars(Avs,CLP),	% removes redundant bounds (redund.pl)
   71		make_target_indep(Tvs, Pivots),	% pivot partners are marked to be kept during elim.	
   72		mark_target(NlReachable),	% after make_indep to express priority
   73		drop_dep(Avs),
   74		fm_elim(CLP,Avs,Tvs,Pivots),
   75		impose_ordering(Avs)
   76	    )
   77	;   true
   78	).
   79
   80get_clp([],_).
   81get_clp([H|T],CLP) :-
   82	(   get_attr(H,clpcd_itf,Att)
   83	->  arg(1,Att,CLP)
   84	;   true
   85	),
   86	get_clp(T,CLP).
   87
   88% mark_target(Vars)
   89%
   90% Marks the variables in Vars as target variables.
   91
   92mark_target([]).
   93mark_target([V|Vs]) :-
   94	(   get_attr(V,clpcd_itf,Att)
   95	->  setarg(9,Att,target)
   96	;   true
   97	),
   98	mark_target(Vs).
   99
  100% drop_lin_atts(Vs)
  101%
  102% Removes the linear attributes of the variables in Vs.
  103% The linear attributes are type, strictness, linear equation (lin), order and class.
  104
  105drop_lin_atts([]).
  106drop_lin_atts([V|Vs]) :-
  107	get_attr(V,clpcd_itf,Att),
  108	setarg(2,Att,n),
  109	setarg(3,Att,n),
  110	setarg(4,Att,n),
  111	setarg(5,Att,n),
  112	setarg(6,Att,n),
  113	drop_lin_atts(Vs).
  114
  115impose_ordering(Cvas) :-
  116	systems(Cvas,[],Sys),
  117	impose_ordering_sys(Sys).
  118
  119impose_ordering_sys([]).
  120impose_ordering_sys([S|Ss]) :-
  121	arrangement(S,Arr),	% ordering.pl
  122	arrange(Arr,S),
  123	impose_ordering_sys(Ss).
  124
  125arrange([],_).
  126arrange(Arr,S) :-
  127	Arr = [_|_],
  128	class_allvars(S,All),
  129	order(Arr,1,N),
  130	order(All,N,_),
  131	renorm_all(All),
  132	arrange_pivot(All).
  133
  134order(Xs,N,M) :-
  135	var(Xs),
  136	!,
  137	N = M.
  138order([],N,N).
  139order([X|Xs],N,M) :-
  140	(   get_attr(X,clpcd_itf,Att),
  141	    arg(5,Att,order(O)),
  142	    var(O)
  143	->  O = N,
  144	    N1 is N+1,
  145	    order(Xs,N1,M)
  146	;   order(Xs,N,M)
  147	).
  148
  149% renorm_all(Vars)
  150%
  151% Renormalizes all linear equations of the variables in difference list Vars to reflect
  152% their new ordering.
  153
  154renorm_all(Xs) :-
  155	var(Xs),
  156	!.
  157renorm_all([X|Xs]) :-
  158	(   get_attr(X,clpcd_itf,Att),
  159	    arg(1,Att,CLP),
  160	    arg(4,Att,lin(Lin))
  161	->  renormalize(CLP,Lin,New),
  162	    setarg(4,Att,lin(New)),
  163	    renorm_all(Xs)
  164	;   renorm_all(Xs)
  165	).
  166
  167% arrange_pivot(Vars)
  168%
  169% If variable X of Vars has type t_none and has a higher order than the first element of
  170% its linear equation, then it is pivoted with that element.
  171
  172arrange_pivot(Xs) :-
  173	var(Xs),
  174	!.
  175arrange_pivot([X|Xs]) :-
  176	(   get_attr(X,clpcd_itf,AttX),
  177	    %arg(8,AttX,n), % not for nonzero
  178	    arg(1,AttX,CLP),
  179	    arg(2,AttX,type(t_none)),
  180	    arg(4,AttX,lin(Lin)),
  181	    arg(5,AttX,order(OrdX)),
  182	    Lin = [_,_,l(Y*_,_)|_],
  183	    get_attr(Y,clpcd_itf,AttY),
  184	    arg(2,AttY,type(IndAct)),
  185	    arg(5,AttY,order(OrdY)),
  186	    arg(6,AttY,class(Class)),
  187	    compare(>,OrdY,OrdX)
  188	->  pivot(CLP,X,Class,OrdY,t_none,IndAct),
  189	    arrange_pivot(Xs)
  190	;   arrange_pivot(Xs)
  191	)