PIPS
sc_build_sc_nredund.c File Reference
#include <stdio.h>
#include <stdlib.h>
#include "linear_assert.h"
#include "boolean.h"
#include "arithmetique.h"
#include "vecteur.h"
#include "contrainte.h"
#include "sc.h"
+ Include dependency graph for sc_build_sc_nredund.c:

Go to the source code of this file.

Functions

bool ineq_redund_with_sc_p (Psysteme sc, Pcontrainte ineq)
 This function returns true if the inequation ineq is redundant for the system ps and false otherwise. More...
 
bool eq_redund_with_sc_p (Psysteme sc, Pcontrainte eq)
 bool eq_redund_with_sc_p(sc, eq) Psysteme sc; Pcontrainte eq; More...
 
Psysteme extract_nredund_subsystem (Psysteme s1, Psysteme s2)
 Psysteme extract_nredund_subsystem(s1, s2) Psysteme s1, s2;. More...
 
void build_sc_nredund_1pass_ofl_ctrl (Psysteme volatile *psc, int ofl_ctrl)
 Psysteme build_sc_nredund_1pass_ofl_ctrl(Psysteme ps, int ofl_ctrl) input : a system in which redundancies must be eliminated, and an integer indicating how overflow errors must be handled. More...
 
void sc_safe_build_sc_nredund_1pass (Psysteme volatile *ps)
 
void build_sc_nredund_1pass (Psysteme volatile *ps)
 Computation of a new system sc from the system ps, where each constraint of the system ps is added to the new system sc, if the constraint is not redundant with the system sc previously computed. More...
 
void build_sc_nredund_2pass_ofl_ctrl (Psysteme volatile *psc, int ofl_ctrl)
 
void sc_safe_build_sc_nredund_2pass (Psysteme volatile *ps)
 
void build_sc_nredund_2pass (Psysteme volatile *psc)
 void build_sc_nredund_2pass Psysteme *psc; More...
 
static bool sc_elim_triang_integer_redund_constraint_p (Pcontrainte pc2, Pbase index_base, Pcontrainte ineq, Variable var_hr, tab_info, int *rank_max)
 This function returns true if the constraint ineq can be eliminated from the system sc and false oterwise. More...
 
Psysteme build_integer_sc_nredund (volatile Psysteme ps, Pbase index_base, int tab_info[][4], int loop_level, int dim_h __attribute__((unused)), int n __attribute__((unused)))
 Computation of a new system sc from the system ps, where each constraint of the system ps is added to the new system sc, if the constraint is not redundant with the system sc previously computed. More...
 
bool bound_redund_with_sc_p (Psysteme sc, Pcontrainte ineq1, Pcontrainte ineq2, Variable var)
 This function returns true if the constraint C (resulting of the combination of the two constraints ineq1 and ineq2) is redundant for the system sc, and false otherwise. More...
 

Function Documentation

◆ bound_redund_with_sc_p()

bool bound_redund_with_sc_p ( Psysteme  sc,
Pcontrainte  ineq1,
Pcontrainte  ineq2,
Variable  var 
)

This function returns true if the constraint C (resulting of the combination of the two constraints ineq1 and ineq2) is redundant for the system sc, and false otherwise.

Assume that ineq1 = coeff1 (positive) * var + E1 <=0 ineq2 = coeff2 (negative) * var +E2 <=0 C = coeff1 * E2 - coeff2 * E1 - coeff1*coeff2-coeff1 <=0

Definition at line 535 of file sc_build_sc_nredund.c.

539 {
540 
541  volatile Pcontrainte posit, negat;
543  bool result = false;
544 
545  if (!CONTRAINTE_UNDEFINED_P(ineq1) && !CONTRAINTE_UNDEFINED_P(ineq2)) {
546 
547  if (value_pos_p(vect_coeff(var,ineq1->vecteur))) {
548  posit = contrainte_copy(ineq1);
549  negat = contrainte_copy(ineq2);
550  }
551  else {
552  posit = contrainte_copy(ineq2);
553  negat = contrainte_copy(ineq1);
554  }
555 
557  result = false;
558  TRY {
559  ineg = sc_integer_inequalities_combination_ofl_ctrl
560  (sc, posit, negat, var, &result, FWD_OFL_CTRL);
561  contrainte_rm(ineg);
563  }
564 
565  contrainte_rm(posit);
566  contrainte_rm(negat);
567  }
568  return result;
569 }
#define CATCH(what)
@ overflow_error
#define UNCATCH(what)
#define TRY
#define value_pos_p(val)
#define CONTRAINTE_UNDEFINED_P(c)
#define CONTRAINTE_UNDEFINED
#define contrainte_rm(c)
the standard xxx_rm does not return a value
Pcontrainte contrainte_copy(Pcontrainte c_in)
Have a look at contrainte_dup and contraintes_dup which reverse the order of the list This copy versi...
Definition: alloc.c:254
Pvecteur vecteur
#define FWD_OFL_CTRL
Value vect_coeff(Variable var, Pvecteur vect)
Variable vect_coeff(Variable var, Pvecteur vect): coefficient de coordonnee var du vecteur vect —> So...
Definition: unaires.c:228

References CATCH, contrainte_copy(), contrainte_rm, CONTRAINTE_UNDEFINED, CONTRAINTE_UNDEFINED_P, FWD_OFL_CTRL, overflow_error, TRY, UNCATCH, value_pos_p, vect_coeff(), and Scontrainte::vecteur.

Referenced by constraint_distribution().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ build_integer_sc_nredund()

Psysteme build_integer_sc_nredund ( volatile Psysteme  ps,
Pbase  index_base,
int  tab_info[][4],
int  loop_level,
int dim_h   __attribute__(unused),
int n   __attribute__(unused) 
)

Computation of a new system sc from the system ps, where each constraint of the system ps is added to the new system sc, if the constraint is not redundant with the system sc previously computed.

The difference with the function build_sc_nredund is that at least 2 constraints are kept for each variable: one for the upper bound and the other for the lower bound.

The rational set defined by ps may be enlarged by this procedure because an integer constraint negation is used.

Modifs:

  • change _dup to _copy.
  • the parameters of contrainte_dup, _copy, _reverse are not changed like base_dup, so it's ok.

this condition is true if the constraint can be eliminated from the system, that means if this is not the last constraint on the variable or if all the constraints on this variable can be eliminated (the rank of variable is greater the number of loops)

Definition at line 432 of file sc_build_sc_nredund.c.

439 {
440 
441  volatile Psysteme sc = sc_new();
442  Pcontrainte eq;
443  // Automatic variables read in a CATCH block need to be declared volatile as
444  // specified by the documentation
445  volatile Pcontrainte ineq, pred;
446  int rank_hr,rank_max = 0;
447  Variable var_hr;
448  Value coeff;
449  volatile int sign;
450 
451  if (SC_UNDEFINED_P(ps) || SC_EMPTY_P(ps) || sc_empty_p(ps) )
452  return ps;
453  sc->base = base_copy(ps->base);
454  sc->dimension = ps->dimension;
455 
456  for (eq = ps->egalites;
459  sc_add_eg(sc,pc);
460  }
461 
462  if (!CONTRAINTE_UNDEFINED_P(ps->inegalites)) {
463 
464  sc->inegalites = contrainte_copy(ps->inegalites);
465  sc->nb_ineq +=1;
466  for (pred = ps->inegalites,ineq = (ps->inegalites)->succ;
467  !CONTRAINTE_UNDEFINED_P(ineq); ineq=ineq->succ) {
468 
469  Pcontrainte volatile ineg = contrainte_copy(ineq);
470  sc_add_inegalite(sc,ineg);
471 
472  // search the characteristics of the variable of higher rank in
473  // the constraint ineq
474  if (( rank_hr= search_higher_rank(ineq->vecteur,index_base)) >0) {
475  var_hr=variable_of_rank(index_base,rank_hr);
476  coeff=vect_coeff(var_hr,ineq->vecteur);
477  sign = value_sign(coeff);
478 
480  (ps->inegalites,index_base,ineq, var_hr,tab_info, &rank_max)
481  && (rank_max >= loop_level)) {
482 
483  /* this condition is true if the constraint can be
484  eliminated from the system, that means if this is
485  not the last constraint on the variable or if all
486  the constraints on this variable can be
487  eliminated (the rank of variable is greater the
488  number of loops) */
489 
490  contrainte_reverse(ineg);
492  pred = pred->succ;
493  contrainte_reverse(ineg);
494  }
495  TRY {
496  // test de sc_faisabilite avec la nouvelle inegalite
498 
499  // si le systeme est non faisable ==>
500  // inegalite redondante ==> elimination de cette inegalite
501  sc->inegalites = sc->inegalites->succ;
502  ineg->succ = NULL;
503  contrainte_rm(ineg);
504  sc->nb_ineq -=1;
505  pred->succ = ineq->succ;
506 
507  // mise a jour du nombre de contraintes restantes
508  // contraingnant la variable de rang rank_hr
509  if (sign >0) tab_info[rank_hr][2] --;
510  else if (sign <0) tab_info[rank_hr][3]--;
511  }
512  else {
513  pred = pred->succ;
514  contrainte_reverse(ineg);
515  }
517  }
518  }
519  }
520  }
521  }
522  return sc;
523 }
#define value_sign(v)
trian operators on values
int Value
int search_higher_rank(Pvecteur vect, Pbase base)
int search_higher_rank(): this fonction returns the rank of the variable of higher rank in the vecteu...
Definition: base.c:541
void contrainte_reverse(Pcontrainte)
void contrainte_reverse(Pcontrainte eq): changement de signe d'une contrainte, i.e.
Definition: unaires.c:67
Psysteme sc_new(void)
Psysteme sc_new(): alloue un systeme vide, initialise tous les champs avec des valeurs nulles,...
Definition: sc_alloc.c:55
bool sc_empty_p(Psysteme sc)
bool sc_empty_p(Psysteme sc): check if the set associated to sc is the constant sc_empty or not.
Definition: sc_alloc.c:350
void sc_add_inegalite(Psysteme p, Pcontrainte i)
void sc_add_inegalite(Psysteme p, Pcontrainte i): macro ajoutant une inegalite i a un systeme p; la b...
Definition: sc_alloc.c:406
static bool sc_elim_triang_integer_redund_constraint_p(Pcontrainte pc2, Pbase index_base, Pcontrainte ineq, Variable var_hr, tab_info, int *rank_max)
This function returns true if the constraint ineq can be eliminated from the system sc and false oter...
bool sc_rational_feasibility_ofl_ctrl(Psysteme sc, int ofl_ctrl, bool ofl_res)
Pcontrainte eq
element du vecteur colonne du systeme donne par l'analyse
Definition: sc_gram.c:108
Variable variable_of_rank()
struct Scontrainte * succ
Pcontrainte inegalites
Definition: sc-local.h:71
Pbase base
Definition: sc-local.h:75
int dimension
Definition: sc-local.h:74
int nb_ineq
Definition: sc-local.h:73
void * Variable
arithmetique is a requirement for vecteur, but I do not want to inforce it in all pips files....
Definition: vecteur-local.h:60
#define OFL_CTRL
I do thing that overflows are managed in a very poor manner.
Pbase base_copy(Pbase b)
Direct duplication.
Definition: alloc.c:300

References Ssysteme::base, base_copy(), CATCH, contrainte_copy(), contrainte_reverse(), contrainte_rm, CONTRAINTE_UNDEFINED_P, Ssysteme::dimension, Ssysteme::egalites, eq, Ssysteme::inegalites, Ssysteme::nb_ineq, OFL_CTRL, overflow_error, sc_add_inegalite(), sc_elim_triang_integer_redund_constraint_p(), sc_empty_p(), sc_new(), sc_rational_feasibility_ofl_ctrl(), search_higher_rank(), Scontrainte::succ, TRY, UNCATCH, value_sign, variable_of_rank(), vect_coeff(), and Scontrainte::vecteur.

Referenced by movement_computation(), and parallel_tiling().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ build_sc_nredund_1pass()

void build_sc_nredund_1pass ( Psysteme volatile *  ps)

Computation of a new system sc from the system ps, where each constraint of the system ps is added to the new system sc, if the constraint is not redundant with the system sc previously computed.

The set of equalities is copied as such and ignored by redundancy checks.

Definition at line 269 of file sc_build_sc_nredund.c.

271 {
273 }
void build_sc_nredund_1pass_ofl_ctrl(Psysteme volatile *psc, int ofl_ctrl)
Psysteme build_sc_nredund_1pass_ofl_ctrl(Psysteme ps, int ofl_ctrl) input : a system in which redunda...

References build_sc_nredund_1pass_ofl_ctrl(), and OFL_CTRL.

Referenced by movement_computation(), sc_projection_concat_proj_on_variables(), and sc_safe_build_sc_nredund_1pass().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ build_sc_nredund_1pass_ofl_ctrl()

void build_sc_nredund_1pass_ofl_ctrl ( Psysteme volatile *  psc,
int  ofl_ctrl 
)

Psysteme build_sc_nredund_1pass_ofl_ctrl(Psysteme ps, int ofl_ctrl) input : a system in which redundancies must be eliminated, and an integer indicating how overflow errors must be handled.

output : Computes a new system sc from the system ps, where each constraint of the system ps is added to the new system sc, if the constraint is not redundant with the system sc previously computed. modifies : comment : The set of equalities is copied as such and ignored by redundancy checks.

if ofl_ctrl == 0 overflow errors are trapped in the routine which checks if the system is feasible. if ofl_ctrl == 2 overflow errors are trapped in the sc_rational_feasibility_ofl_ctrl routine that keeps the constraint in the system whatever its redundancy characteristic if ofl_ctrl == 1 overflow errors are forwarded to the calling routine.

the redundancy elimination assumes integer points. The rational set defined by sc may be enlarged.

if more than 6 exceptions are thrown from within the loop, the loop is stopped.

Definition at line 190 of file sc_build_sc_nredund.c.

193 {
194 
195  Psysteme sc;
196  Psysteme ps = *psc;
197  Pcontrainte ineq, ineg;
198  int init_exception_thrown = linear_number_of_exception_thrown;
199 
200  if (SC_UNDEFINED_P(ps) || sc_rn_p(ps) || sc_empty_p(ps))
201  return;
202 
203  sc = sc_init_with_sc(ps);
205  sc=sc_empty(base_dup(ps->base));
206  sc_rm(ps);
207  *psc =sc;
208  return;
209  }
210 
212  sc->nb_eq = ps->nb_eq;
213  for (ineq = ps->inegalites;
214  !CONTRAINTE_UNDEFINED_P(ineq) &&
215  /* if more than 6 exceptions are thrown from within the loop,
216  the loop is stopped. */
217  linear_number_of_exception_thrown-init_exception_thrown<7;
218  ineq=ineq->succ)
219  {
220  ineg = contrainte_copy(ineq);
221  contrainte_reverse(ineg);
222 
223  sc_add_inegalite(sc,ineg);
224 
225  if (sc_rational_feasibility_ofl_ctrl(sc,ofl_ctrl,true))
226  contrainte_reverse(ineg);
227  else {
228  sc->inegalites = sc->inegalites->succ;
229  ineg->succ = NULL;
230  contrainte_rm(ineg);
231  sc->nb_ineq--;
232  }
233  }
234 
235  if (linear_number_of_exception_thrown-init_exception_thrown>=7)
236  fprintf(stderr, "[build_sc_nredund_1pass_ofl_ctrl] "
237  "too many exceptions in redundancy elimination... function stopped.\n");
238 
239  sc_rm(ps);
240  *psc = sc;
241 }
int linear_number_of_exception_thrown
Pcontrainte contraintes_copy(Pcontrainte c_in)
Pcontrainte contraintes_copy(Pcontrainte c_in) a list of constraints is copied with the same order In...
Definition: alloc.c:270
bool sc_rn_p(Psysteme sc)
bool sc_rn_p(Psysteme sc): check if the set associated to sc is the whole space, rn
Definition: sc_alloc.c:369
Psysteme sc_empty(Pbase b)
Psysteme sc_empty(Pbase b): build a Psysteme with one unfeasible constraint to define the empty subsp...
Definition: sc_alloc.c:319
void sc_rm(Psysteme ps)
void sc_rm(Psysteme ps): liberation de l'espace memoire occupe par le systeme de contraintes ps;
Definition: sc_alloc.c:277
Psysteme sc_init_with_sc(Psysteme sc)
This function returns a new empty system which has been initialized with the same dimension and base ...
Definition: sc_alloc.c:303
int fprintf()
test sc_min : ce test s'appelle par : programme fichier1.data fichier2.data ...
Pcontrainte egalites
Definition: sc-local.h:70
int nb_eq
Definition: sc-local.h:72
Pbase base_dup(Pbase b)
Pbase base_dup(Pbase b) Note: this function changes the value of the pointer.
Definition: alloc.c:268

References Ssysteme::base, base_dup(), contrainte_copy(), contrainte_reverse(), contrainte_rm, CONTRAINTE_UNDEFINED_P, contraintes_copy(), Ssysteme::egalites, fprintf(), Ssysteme::inegalites, linear_number_of_exception_thrown, Ssysteme::nb_eq, Ssysteme::nb_ineq, OFL_CTRL, sc_add_inegalite(), sc_empty(), sc_empty_p(), sc_init_with_sc(), sc_rational_feasibility_ofl_ctrl(), sc_rm(), sc_rn_p(), and Scontrainte::succ.

Referenced by build_sc_nredund_1pass(), and build_sc_nredund_2pass_ofl_ctrl().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ build_sc_nredund_2pass()

void build_sc_nredund_2pass ( Psysteme volatile *  psc)

void build_sc_nredund_2pass Psysteme *psc;

Definition at line 331 of file sc_build_sc_nredund.c.

332 {
333  if (SC_UNDEFINED_P(*psc))
334  return;
335  else
337 }
void build_sc_nredund_2pass_ofl_ctrl(Psysteme volatile *psc, int ofl_ctrl)

References build_sc_nredund_2pass_ofl_ctrl(), and OFL_CTRL.

Referenced by clean_shared_io_system(), clean_the_system(), generate_distributed_io_system(), put_variables_in_ordered_lists(), and sc_safe_build_sc_nredund_2pass().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ build_sc_nredund_2pass_ofl_ctrl()

void build_sc_nredund_2pass_ofl_ctrl ( Psysteme volatile *  psc,
int  ofl_ctrl 
)

Definition at line 275 of file sc_build_sc_nredund.c.

278 {
279  Psysteme ps = *psc;
280  static int francois_check = 0;
281  Pvecteur ip;
282  if(francois_check && !SC_UNDEFINED_P(ps))
283  ip = vect_make_dense(ps->base, 1LL, 0LL, 0LL, 100LL, 0LL);
284 
285  if (SC_UNDEFINED_P(ps) || sc_rn_p(ps) || sc_empty_p(ps))
286  return;
287 
288  *psc = sc_normalize(ps);
289  if(francois_check)
290  assert(sc_belongs_p(*psc, ip));
291 ifscdebug(5) {
292  fprintf(stderr, "after normalize: \n");
293  sc_default_dump(*psc);
294  }
295  assert(!SC_UNDEFINED_P(*psc));
296  build_sc_nredund_1pass_ofl_ctrl(psc, ofl_ctrl);
297  if(francois_check)
298  assert(sc_belongs_p(*psc, ip));
299 ifscdebug(5) {
300  fprintf(stderr, "after first nredund: \n");
301  sc_default_dump(*psc);
302  }
303  build_sc_nredund_1pass_ofl_ctrl(psc, ofl_ctrl);
304  if(francois_check)
305  assert(sc_belongs_p(*psc, ip));
306 }
#define assert(ex)
Definition: newgen_assert.h:41
bool sc_belongs_p(Psysteme ps, Pvecteur v)
package sc
Definition: sc_belong.c:51
void sc_default_dump(Psysteme sc)
void sc_default_dump(Psysteme sc): dump to stderr
Definition: sc_io.c:170
Psysteme sc_normalize(Psysteme ps)
Psysteme sc_normalize(Psysteme ps): normalisation d'un systeme d'equation et d'inequations lineaires ...
le type des coefficients dans les vecteurs: Value est defini dans le package arithmetique
Definition: vecteur-local.h:89
Pvecteur vect_make_dense(Pbase b, Value val,...)
Allocate a new vector v whose coefficient are given by the list of values ad whose dimension is given...
Definition: alloc.c:198

References assert, Ssysteme::base, build_sc_nredund_1pass_ofl_ctrl(), fprintf(), sc_belongs_p(), sc_default_dump(), sc_empty_p(), sc_normalize(), sc_rn_p(), and vect_make_dense().

Referenced by build_sc_nredund_2pass(), and sc_projection_optim_along_vecteur_ofl().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ eq_redund_with_sc_p()

bool eq_redund_with_sc_p ( Psysteme  sc,
Pcontrainte  eq 
)

bool eq_redund_with_sc_p(sc, eq) Psysteme sc; Pcontrainte eq;

IN: sc, eq

OUT: returned boolean

true if eq is redundant with sc (c) FC 16/05/94

eq considered as an inequality

Definition at line 99 of file sc_build_sc_nredund.c.

102 {
103  if (!ineq_redund_with_sc_p(sc, eq)) /* eq considered as an inequality */
104  return(false);
105  else
106  {
108  c = contrainte_copy(eq);
109  bool
110  res = ineq_redund_with_sc_p(sc, (contrainte_chg_sgn(c), c));
111  contrainte_free(c);
112  return(res);
113  }
114 }
Pcontrainte contrainte_free(Pcontrainte c)
Pcontrainte contrainte_free(Pcontrainte c): liberation de l'espace memoire alloue a la contrainte c a...
Definition: alloc.c:184
void contrainte_chg_sgn(Pcontrainte)
void contrainte_chg_sgn(Pcontrainte eq): changement de signe d'une contrainte, i.e.
Definition: unaires.c:56
bool ineq_redund_with_sc_p(Psysteme sc, Pcontrainte ineq)
This function returns true if the inequation ineq is redundant for the system ps and false otherwise.

References contrainte_chg_sgn(), contrainte_copy(), contrainte_free(), eq, and ineq_redund_with_sc_p().

Referenced by extract_nredund_subsystem(), and show_nredund().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ extract_nredund_subsystem()

Psysteme extract_nredund_subsystem ( Psysteme  s1,
Psysteme  s2 
)

Psysteme extract_nredund_subsystem(s1, s2) Psysteme s1, s2;.

  IN: s1, s2
 OUT: returned Psysteme

returns the constraints of s1 that are not redundant with s2

(c) FC 16/05/94

temporary

inequalities

could be inlined to avoid costly sc_copy inside ineq_redund_with_sc_p

equalities

Definition at line 127 of file sc_build_sc_nredund.c.

129 {
130  Psysteme
131  new = SC_UNDEFINED;
136  cnew = CONTRAINTE_UNDEFINED; /* temporary */
137 
138  /* inequalities
139  */
140  for(c=sc_inegalites(s1);
142  c=c->succ)
143  /* could be inlined to avoid costly sc_copy inside ineq_redund_with_sc_p
144  */
145  if (!ineq_redund_with_sc_p(s2, c))
146  cnew = contrainte_copy(c),
147  cnew->succ = in,
148  in = cnew;
149 
150  /* equalities
151  */
152  for(c=sc_egalites(s1);
154  c=c->succ)
155  if (!eq_redund_with_sc_p(s2, c))
156  cnew = contrainte_copy(c),
157  cnew->succ = eq,
158  eq = cnew;
159 
160  new = sc_make(eq, in);
161  return(sc_nredund(&new), new);
162 }
Psysteme sc_make(Pcontrainte leg, Pcontrainte lineg)
Psysteme sc_make(Pcontrainte leg, Pcontrainte lineg): allocation et initialisation d'un systeme d'equ...
Definition: sc.c:78
bool eq_redund_with_sc_p(Psysteme sc, Pcontrainte eq)
bool eq_redund_with_sc_p(sc, eq) Psysteme sc; Pcontrainte eq;
s1
Definition: set.c:247

References contrainte_copy(), CONTRAINTE_UNDEFINED, eq, eq_redund_with_sc_p(), ineq_redund_with_sc_p(), s1, sc_make(), and Scontrainte::succ.

Referenced by create_step_regions(), GENERATION(), hpfc_simplify_condition(), and processor_loop().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ ineq_redund_with_sc_p()

bool ineq_redund_with_sc_p ( Psysteme  sc,
Pcontrainte  ineq 
)

This function returns true if the inequation ineq is redundant for the system ps and false otherwise.

sc and ineq are not modified by the function.

Inequality ineq may not be redundant wrt ps for rational numbers and nevertheless true is returned if it is redundant wrt integer points.

A bug found here: if we have input sc==NULL with ineq=NULL, then we'll have to test the satisfiability of a sc that has a base null and an ineq (core dump): because in sc_add_inegalite, we test only if the pointers (sc,ineg) are null. The encountered case is that the pointer not null but his all elements are null or except only one element. This means the constraint is not valid.

DN 2/1/2003 The same with eq_redund_with_sc_p Modifs:

  • change _dup to _copy
  • correct the bug

othing to test: 0==0 is intrinsically redundant

test de sc_faisabilite avec la nouvelle inegalite

Definition at line 59 of file sc_build_sc_nredund.c.

62 {
63  Psysteme ps;
64  Pcontrainte ineg;
65  bool result = false;
66 
67  if (CONTRAINTE_NULLE_P(ineq)) {
68  /*nothing to test: 0==0 is intrinsically redundant */
69  return true;
70  }
71 
72  ps = sc_copy(sc);
73  ineg = contrainte_copy(ineq);
74  contrainte_reverse(ineg);
75  sc_add_inegalite(ps,ineg);
76 
77  base_rm(sc_base(ps));
78  sc_base(ps) = BASE_NULLE;
79  sc_creer_base(ps);
80 
81  /* test de sc_faisabilite avec la nouvelle inegalite */
83  result = true;
84  sc_rm(ps);
85  return(result);
86 }
#define CONTRAINTE_NULLE_P(c)
contrainte nulle (non contrainte 0 == 0 ou 0 <= 0)
void sc_creer_base(Psysteme ps)
void sc_creer_base(Psysteme ps): initialisation des parametres dimension et base d'un systeme lineair...
Definition: sc_alloc.c:129
Psysteme sc_copy(Psysteme ps)
Psysteme sc_copy(Psysteme ps): duplication d'un systeme (allocation et copie complete des champs sans...
Definition: sc_alloc.c:230
#define base_rm(b)
#define BASE_NULLE
MACROS SUR LES BASES.

References BASE_NULLE, base_rm, contrainte_copy(), CONTRAINTE_NULLE_P, contrainte_reverse(), OFL_CTRL, sc_add_inegalite(), sc_copy(), sc_creer_base(), sc_rational_feasibility_ofl_ctrl(), and sc_rm().

Referenced by elim_redund_sc_with_sc(), eq_redund_with_sc_p(), extract_nredund_subsystem(), loop_executed_approximation(), and show_nredund().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ sc_elim_triang_integer_redund_constraint_p()

static bool sc_elim_triang_integer_redund_constraint_p ( Pcontrainte  pc2,
Pbase  index_base,
Pcontrainte  ineq,
Variable  var_hr,
tab_info  ,
int rank_max 
)
static

This function returns true if the constraint ineq can be eliminated from the system sc and false oterwise.

It assumes that two constraints at least must be kept for constraining the variable "var_hr" in the system. the array "tab_info" contains the useful informations allowing to know the number of constraints constraining each variable as upper or lower bounds.

This condition is true if the variable is a loop index. As the constraint constrains directly the variable, this constraint must be kept if there is not enough remainding constraints

Definition at line 349 of file sc_build_sc_nredund.c.

357 {
358  int rank_hr = rank_of_variable(index_base,var_hr);
359  Value coeff = vect_coeff(var_hr,ineq->vecteur);
360  int sign = value_sign(coeff);
361  bool result=false;
362  bool trouve=false;
363  *rank_max=rank_hr;
364 
365  if (tab_info[rank_hr][1]) {
366 
367  /* This condition is true if the variable is a loop index.
368  As the constraint constrains directly the variable,
369  this constraint must be kept if there is not enough
370  remainding constraints
371  */
372 
373  if (((sign >0) && (tab_info[rank_hr][2]>1))
374  || ((sign <0) && (tab_info[rank_hr][3]>1)))
375  result = true;
376  }
377  else {
378  register Pcontrainte pc;
379 
380  for (pc = pc2;
381  !CONTRAINTE_UNDEFINED_P(pc) && !trouve;
382  pc = pc->succ) {
383 
384  Value coeff2 = vect_coeff(var_hr,pc->vecteur);
385  int sign2 = value_sign(coeff2);
386  int right_rank, left_rank;
387  Value right_coeff, left_coeff;
388  Variable right_var,left_var;
389 
390  if (value_notzero_p(coeff2) && sign == -sign2) {
391  constraint_integer_combination(index_base,ineq,pc,rank_hr,
392  &right_var,&right_rank,&right_coeff,
393  &left_var,&left_rank,&left_coeff);
394  *rank_max = MAX(right_rank,left_rank);
395  if (((right_rank>left_rank)
396  && (((value_pos_p(right_coeff)) &&
397  (tab_info[right_rank][2] <=1))
398  || (value_neg_p(right_coeff) &&
399  (tab_info[right_rank][3] <=1))))
400  || ((right_rank<left_rank)
401  && ((value_pos_p(left_coeff) &&
402  (tab_info[left_rank][2]<=1))
403  || (value_neg_p(left_coeff) &&
404  (tab_info[left_rank][3] <=1)))))
405  trouve = true;
406  }
407  }
408  if (!trouve) result = true;
409  }
410  return result;
411 
412 }
#define value_notzero_p(val)
#define value_neg_p(val)
int rank_of_variable(Pbase base, Variable var)
this function returns the rank of the variable var in the base 0 encodes TCST, but I do not know why,...
Definition: base.c:497
void constraint_integer_combination(Pbase index_base, Pcontrainte ineq1, Pcontrainte ineq2, int rank, Variable *right_var, int *right_rank, Value *right_coeff, Variable *left_var, int *left_rank, Value *left_coeff)
This function computes the coefficients of the constraint resulting from the elimination of the varia...
#define MAX(x, y)
Definition: string.c:110

References constraint_integer_combination(), CONTRAINTE_UNDEFINED_P, MAX, rank_of_variable(), Scontrainte::succ, value_neg_p, value_notzero_p, value_pos_p, value_sign, vect_coeff(), and Scontrainte::vecteur.

Referenced by build_integer_sc_nredund().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ sc_safe_build_sc_nredund_1pass()

void sc_safe_build_sc_nredund_1pass ( Psysteme volatile *  ps)

*ps = sc_sort_constraints_simplest_first(*ps, b); see version 1.16

Definition at line 243 of file sc_build_sc_nredund.c.

245 {
246 
247  if (!sc_rn_p(*ps) && !sc_empty_p(*ps))
248  {
249  Pbase b = base_copy(sc_base(*ps));
250  /* *ps = sc_sort_constraints_simplest_first(*ps, b); see version 1.16*/
252  if (*ps == SC_EMPTY)
253  *ps = sc_empty(b);
254  else {
255  base_rm(sc_base(*ps));
256  (*ps)->base = base_copy(b);
257  }
258  }
259 }
void build_sc_nredund_1pass(Psysteme volatile *ps)
Computation of a new system sc from the system ps, where each constraint of the system ps is added to...

References base_copy(), base_rm, build_sc_nredund_1pass(), sc_empty(), sc_empty_p(), and sc_rn_p().

Referenced by transformer_normalize().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ sc_safe_build_sc_nredund_2pass()

void sc_safe_build_sc_nredund_2pass ( Psysteme volatile *  ps)

Definition at line 309 of file sc_build_sc_nredund.c.

311 {
312 
313  if (!sc_rn_p(*ps) && !sc_empty_p(*ps))
314  {
315  Pbase b = base_copy(sc_base(*ps));
317  if (*ps == SC_EMPTY)
318  *ps = sc_empty(b);
319  else {
320  base_rm(sc_base(*ps));
321  (*ps)->base = base_copy(b);
322  }
323  }
324 }
void build_sc_nredund_2pass(Psysteme volatile *psc)
void build_sc_nredund_2pass Psysteme *psc;

References base_copy(), base_rm, build_sc_nredund_2pass(), sc_empty(), sc_empty_p(), and sc_rn_p().

+ Here is the call graph for this function: