1/*  $Id$
    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:- module(clpcd_dump,
   42	  [ dump/3,
   43	    projecting_assert/1
   44	  ]).   45
   46:- use_module(library(assoc)).   47:- use_module(library(clpcd/class)).   48:- use_module(library(clpcd/geler)).   49:- use_module(library(clpcd/itf)).   50:- use_module(library(clpcd/highlight)).   51:- use_module(library(clpcd/attributes)).   52:- use_module(library(clpcd/domain_ops)).   53:- use_module(library(clpcd/ordering)).
 dump(+Target, -NewVars, -Constraints) is det
Returns in <Constraints>, the constraints that currently hold on Target where all variables in <Target> are copied to new variables in <NewVars> and the constraints are given on these new variables. In short, you can safely manipulate <NewVars> and <Constraints> without changing the constraints on <Target>.
   63dump([],[],[]) :- !.
   64dump(Target,NewVars,Constraints) :-
   65	(   (	proper_varlist(Target)
   66	    ->  true
   67	    ;   % Target is not a list of variables
   68		throw(instantiation_error(dump(Target,NewVars,Constraints),1))
   69	    ),
   70	    ordering(Target),
   71	    related_linear_vars(Target,All),	% All contains all variables of the classes of Target variables.
   72	    nonlin_crux(All,Nonlin),
   73	    project_attributes(Target,All),
   74	    related_linear_vars(Target,Again),	% project drops/adds vars
   75	    all_attribute_goals(Again,Gs,Nonlin),
   76	    empty_assoc(D0),
   77	    mapping(Target,NewVars,D0,D1),	% late (AVL suffers from put_atts)
   78	    copy(Gs,Copy,D1,_),			% strip constraints
   79	    nb_setval(clpcd_dump,NewVars/Copy),
   80	    fail				% undo projection
   81	;   nb_current(clpcd_dump, NewVars/Constraints),
   82	    nb_delete(clpcd_dump)
   83	).
   84
   85:- meta_predicate projecting_assert(:).   86
   87projecting_assert(QClause) :-
   88	strip_module(QClause, Module, Clause),  % JW: SWI-Prolog not always qualifies the term!
   89	copy_term_clpcd(Clause,Copy,Constraints),
   90	l2c(Constraints,Conj),			% fails for []
   91        clpcd_module(Sm),
   92	!,
   93	(   Copy = (H:-B)
   94	->  % former rule
   95	    Module:assert((H:-Sm:{Conj},B))
   96	;   % former fact
   97	    Module:assert((Copy:-Sm:{Conj}))
   98	).
   99projecting_assert(Clause) :-	% not our business
  100	assert(Clause).
  101
  102copy_term_clpcd(Term,Copy,Constraints) :-
  103	(   term_variables(Term,Target),	% get all variables in Term
  104	    related_linear_vars(Target,All),	% get all variables of the classes of the variables in Term
  105	    nonlin_crux(All,Nonlin),		% get a list of all the nonlinear goals of these variables
  106	    project_attributes(Target,All),
  107	    related_linear_vars(Target,Again),	% project drops/adds vars
  108	    all_attribute_goals(Again,Gs,Nonlin),
  109	    empty_assoc(D0),
  110	    copy(Term/Gs,TmpCopy,D0,_),	  % strip constraints
  111	    nb_setval(clpcd_copy_term,TmpCopy),
  112	    fail
  113	;   nb_current(clpcd_copy_term,Copy/Constraints),
  114	    nb_delete(clpcd_copy_term)
  115	).
  116
  117% l2c(Lst,Conj)
  118%
  119% converts a list to a round list: [a,b,c] -> (a,b,c) and [a] becomes a
  120
  121l2c([X|Xs],Conj) :-
  122	(   Xs = []
  123	->  Conj = X
  124	;   Conj = (X,Xc),
  125	    l2c(Xs,Xc)
  126	).
  127
  128% proper_varlist(List)
  129%
  130% Returns whether Lst is a list of variables.
  131% First clause is to avoid unification of a variable with a list.
  132
  133proper_varlist(X) :-
  134	var(X),
  135	!,
  136	fail.
  137proper_varlist([]).
  138proper_varlist([X|Xs]) :-
  139	var(X),
  140	proper_varlist(Xs).
  141
  142% related_linear_vars(Vs,All)
  143%
  144% Generates a list of all variables that are in the classes of the variables in
  145% Vs.
  146
  147related_linear_vars(Vs,All) :-
  148	empty_assoc(S0),
  149	related_linear_sys(Vs,S0,Sys),
  150	related_linear_vars(Sys,All,[]).
  151
  152% related_linear_sys(Vars,Assoc,List)
  153%
  154% Generates in List, a list of all to classes to which variables in Vars
  155% belong.
  156% Assoc should be an empty association list and is used internally.
  157% List contains elements of the form C-C where C is a class and both C's are
  158% equal.
  159
  160related_linear_sys([],S0,L0) :- assoc_to_list(S0,L0).
  161related_linear_sys([V|Vs],S0,S2) :-
  162	(   get_attr(V,clpcd_itf,Att),
  163	    arg(6,Att,class(C))
  164	->  put_assoc(C,S0,C,S1)
  165	;   S1 = S0
  166	),
  167	related_linear_sys(Vs,S1,S2).
  168
  169% related_linear_vars(Classes,[Vars|VarsTail],VarsTail)
  170%
  171% Generates a difference list of all variables in the classes in Classes.
  172% Classes contains elements of the form C-C where C is a class and both C's are
  173% equal.
  174
  175related_linear_vars([]) --> [].
  176related_linear_vars([S-_|Ss]) -->
  177	{
  178	    class_allvars(S,Otl)
  179	},
  180	cpvars(Otl),
  181	related_linear_vars(Ss).
  182
  183% cpvars(Vars,Out,OutTail)
  184%
  185% Makes a new difference list of the difference list Vars.
  186% All nonvars are removed.
  187
  188cpvars(Xs) --> {var(Xs)}, !.
  189cpvars([X|Xs]) -->
  190	(   { var(X) }
  191	->  [X]
  192	;   []
  193	),
  194	cpvars(Xs).
  195
  196% nonlin_crux(All,Gss)
  197%
  198% Collects all pending non-linear constraints of variables in All.
  199% This marks all nonlinear goals of the variables as run and cannot
  200% be reversed manually.
  201
  202nonlin_crux(All,Gss) :-
  203	collect_nonlin(All,Gs,[]),	% collect the nonlinear goals of variables All
  204					% this marks the goals as run and cannot be reversed manually
  205	nonlin_strip(Gs,Gss).
  206
  207% nonlin_strip(Gs,Solver,Res)
  208%
  209% Removes the goals from Gs that are not from solver Solver.
  210
  211nonlin_strip([],[]).
  212nonlin_strip([_CLP:What|Gs],Res) :-
  213	(   What = {G}
  214	->  Res = [G|Gss]
  215	;   Res = [What|Gss]
  216	),
  217	nonlin_strip(Gs,Gss).
  218
  219all_attribute_goals([]) --> [].
  220all_attribute_goals([V|Vs]) -->
  221	dump_linear(V),
  222	dump_nonzero(V),
  223	all_attribute_goals(Vs).
  224
  225% mapping(L1,L2,AssocIn,AssocOut)
  226%
  227% Makes an association mapping of lists L1 and L2:
  228% L1 = [L1H|L1T] and L2 = [L2H|L2T] then the association L1H-L2H is formed
  229% and the tails are mapped similarly.
  230
  231mapping([],[],D0,D0).
  232mapping([T|Ts],[N|Ns],D0,D2) :-
  233	put_assoc(T,D0,N,D1),
  234	mapping(Ts,Ns,D1,D2).
  235
  236% copy(Term,Copy,AssocIn,AssocOut)
  237%
  238% Makes a copy of Term by changing all variables in it to new ones and
  239% building an association between original variables and the new ones.
  240% E.g. when Term = test(A,B,C), Copy = test(D,E,F) and an association between
  241% A and D, B and E and C and F is formed in AssocOut. AssocIn is input
  242% association.
  243
  244copy(Term,Copy,D0,D1) :-
  245	var(Term),
  246	(   get_assoc(Term,D0,New)
  247	->  Copy = New,
  248	    D1 = D0
  249	;   put_assoc(Term,D0,Copy,D1)
  250	).
  251copy(Term,Copy,D0,D1) :-
  252	nonvar(Term),	% Term is a functor
  253	functor(Term,N,A),
  254	functor(Copy,N,A),	% Copy is new functor with the same name and arity as Term
  255	copy(A,Term,Copy,D0,D1).
  256
  257% copy(Nb,Term,Copy,AssocIn,AssocOut)
  258%
  259% Makes a copy of the Nb arguments of Term by changing all variables in it to
  260% new ones and building an association between original variables and the new
  261% ones.
  262% See also copy/4
  263
  264copy(0,_,_,D0,D0) :- !.
  265copy(1,T,C,D0,D1) :- !,
  266	arg(1,T,At1),
  267	arg(1,C,Ac1),
  268	copy(At1,Ac1,D0,D1).
  269copy(2,T,C,D0,D2) :- !,
  270	arg(1,T,At1),
  271	arg(1,C,Ac1),
  272	copy(At1,Ac1,D0,D1),
  273	arg(2,T,At2),
  274	arg(2,C,Ac2),
  275	copy(At2,Ac2,D1,D2).
  276copy(N,T,C,D0,D2) :-
  277	arg(N,T,At),
  278	arg(N,C,Ac),
  279	copy(At,Ac,D0,D1),
  280	N1 is N-1,
  281	copy(N1,T,C,D1,D2).
 attribute_goals(@V)// is det
Translate attributes back into goals. This is used by copy_term/3, which also determines the toplevel printing of residual constraints.
  289clpcd_itf:attribute_goals(V) -->
  290	(   { term_attvars(V, Vs),
  291	      dump(Vs, NVs, List),
  292	      NVs = Vs,
  293	      del_itf(Vs),
  294	      list_to_conj(List, Conj) }
  295	->  [ {}(Conj) ]
  296	;   []
  297	).
  298
  299clpcd_class:attribute_goals(_) --> [].
  300
  301clpcd_geler:attribute_goals(V) --> clpcd_itf:attribute_goals(V).
  302
  303del_itf([]).
  304del_itf([H|T]) :-
  305	del_attr(H, clpcd_itf),
  306	del_itf(T).
  307
  308
  309list_to_conj([], true) :- !.
  310list_to_conj([X], X) :- !.
  311list_to_conj([H|T0], (H,T)) :-
  312	list_to_conj(T0, T).
  313
  314		 /*******************************
  315		 *	       SANDBOX		*
  316		 *******************************/
  317:- multifile
  318	sandbox:safe_primitive/1.  319
  320sandbox:safe_primitive(clpcd_dump:dump(_,_,_))