PIPS
prgm_mapping.c
Go to the documentation of this file.
1 /*
2 
3  $Id: prgm_mapping.c 23065 2016-03-02 09:05:50Z coelho $
4 
5  Copyright 1989-2016 MINES ParisTech
6 
7  This file is part of PIPS.
8 
9  PIPS is free software: you can redistribute it and/or modify it
10  under the terms of the GNU General Public License as published by
11  the Free Software Foundation, either version 3 of the License, or
12  any later version.
13 
14  PIPS is distributed in the hope that it will be useful, but WITHOUT ANY
15  WARRANTY; without even the implied warranty of MERCHANTABILITY or
16  FITNESS FOR A PARTICULAR PURPOSE.
17 
18  See the GNU General Public License for more details.
19 
20  You should have received a copy of the GNU General Public License
21  along with PIPS. If not, see <http://www.gnu.org/licenses/>.
22 
23 */
24 #ifdef HAVE_CONFIG_H
25  #include "pips_config.h"
26 #endif
27 
28 /* Name : prgm_mapping.c
29  * Package : prgm_mapping
30  * Author : Alexis Platonoff
31  * Date : april 1993
32  * Historic :
33  * Documents: SOON
34  * Comments : This file contains the functions for the computation of the
35  * placement function. The main function is prgm_mapping().
36  */
37 
38 /* Ansi includes */
39 #include <stdio.h>
40 #include <string.h>
41 #include <stdlib.h>
42 
43 #include <sys/times.h> /* performance purpose */
44 #include <sys/time.h> /* performance purpose */
45 
46 /* Newgen includes */
47 #include "genC.h"
48 
49 /* C3 includes */
50 #include "boolean.h"
51 #include "arithmetique.h"
52 #include "vecteur.h"
53 #include "contrainte.h"
54 #include "ray_dte.h"
55 #include "sommet.h"
56 #include "sg.h"
57 #include "sc.h"
58 #include "polyedre.h"
59 #include "union.h"
60 #include "matrice.h"
61 #include "matrix.h"
62 
63 /* Pips includes */
64 #include "ri.h"
65 #include "constants.h"
66 #include "ri-util.h"
67 #include "misc.h"
68 #include "complexity_ri.h"
69 #include "database.h"
70 #include "graph.h"
71 #include "dg.h"
72 #include "paf_ri.h"
73 #include "parser_private.h"
74 #include "property.h"
75 #include "reduction.h"
76 #include "text.h"
77 #include "text-util.h"
78 #include "tiling.h"
79 #include "text-util.h"
80 #include "pipsdbm.h"
81 #include "resources.h"
82 #include "static_controlize.h"
83 #include "paf-util.h"
84 #include "pip.h"
85 #include "array_dfg.h"
86 #include "prgm_mapping.h"
87 
88 /* Macro functions */
89 #define DOT "."
90 #define BDT_STRING "bdt"
91 #define STMT_HT_SIZE 100 /* hash table max size */
92 #define DTF_HT_SIZE 200 /* hash table max size */
93 #define ENT_HT_SIZE 200 /* hash table max size */
94 
95 /* Internal variables */
96 
97 /* Global variables */
98 plc pfunc; /* The placement function */
99 graph the_dfg; /* The data flow graph */
100 bdt the_bdt; /* The timing function */
101 int nb_nodes, /* The number of nodes in the DFG */
102  nb_dfs; /* The number of dataflows in the DFG */
103 hash_table DtfToSink; /* Mapping from a dataflow to its sink statement */
104 hash_table DtfToDist; /* Mapping from a dataflow to its distance */
105 hash_table DtfToWgh; /* Mapping from a dataflow to its weight */
106 hash_table StmtToProto; /* Mapping from a statement (int) to its prototype */
107 hash_table StmtToPdim; /* Mapping from a statement to the dim of its plc func */
108 hash_table StmtToBdim; /* Mapping from a statement to the dim of its bdt */
109 hash_table StmtToDim; /* Mapping from a stmt to its iteration space dim */
110 hash_table StmtToLamb; /* Mapping from a stmt to its lambda coeff */
111 hash_table StmtToMu; /* Mapping from a stmt to its mu coeff */
112 hash_table UnkToFrenq; /* Mapping from an entity to its frenq in the plc proto */
116 
117 /* Local defines */
120 
121 #define PLC_EXT ".plc_file"
122 
123 /* ======================================================================== */
125 const char* module_name;
126 {
127  char *localfilename;
128  FILE *fd;
129  char *filename;
130  plc the_plc;
131 
132  debug_on( "PRINT_PLC_DEBUG_LEVEL" );
133 
134  if (get_debug_level() > 1)
135  user_log("\n\n *** PRINTING PLC for %s\n", module_name);
136 
137  the_plc = (plc) db_get_memory_resource(DBR_PLC, module_name, true);
138 
139  localfilename = strdup(concatenate(module_name, PLC_EXT, NULL));
141  "/", localfilename, NULL));
142 
143  fd = safe_fopen(filename, "w");
144  fprint_plc(fd, the_plc);
145  safe_fclose(fd, filename);
146 
147  DB_PUT_FILE_RESOURCE(DBR_PLC_FILE, strdup(module_name), localfilename);
148 
149  free(filename);
150 
151  if(get_debug_level() > 0)
152  fprintf(stderr, "\n\n *** PRINT_PLC DONE\n");
153 
154  debug_off();
155 
156  return(true);
157 }
158 
159 
160 /* ======================================================================== */
161 /*
162  * list plc_make_proto():
163  *
164  * computes the prototype of placement function for each statement,
165  * i.e. for each node of the DGF. Returns the list of unknowns
166  * coefficients that have been created.
167  *
168  * For each node, this consists in building a polynome which will be
169  * associated via the hash table "StmtToProto" to the corresponding
170  * statement.
171  *
172  * The placement function is an integer linear function on the indices of
173  * the englobing loops and structure parameters of the statement. We have
174  * to determine the coefficients associated to each index. These unknowns
175  * are represented by variables, so the prototype is a polynome of degree
176  * two (2). Moreover there is an unknown constant term.
177  *
178  * For example, with a statement englobed by three (3) loops (I1, I2, I3)
179  * and having one structure parameter (N), the prototype is :
180  *
181  * COEFF1*I1 + COEFF2*I2 + COEFF3*I3 + COEFF$*N + COEFF5
182  *
183  * Note: The list "l_lamb" that contains all the coefficients is build
184  * during by appending the sublists associated to each statement. Each
185  * sublist is ordered as follow: you have first the coeff for the constant
186  * term, the coeffs for the loop indices (from the outermost to the
187  * innermost) and the coeffs of the structure parameters (the order of the
188  * static_controlize). This order is used in the function
189  * broadcast_conditions().*/
191 {
192  extern graph the_dfg; /* the DFG */
193  extern hash_table StmtToProto, /* Mapping from a statement to its
194  * prototype */
195  StmtToLamb; /* Mapping from a statement to its
196  * lambda coeff */
197 
198 
199  int count_coeff;
200  list l, l_lamb = NIL, stmt_lamb;
201  entity lamb;
202  Ppolynome pp_proto, pp_ind, pp_par, pp_coeff, pp_new;
203 
204  /* We create the hash table that will contain the prototype */
207 
208  /* We initialize the counter of coefficients in order to have all
209  * unknowns represented by different entities.
210  */
211  count_coeff = 0;
212 
213  /* For each node of the data flow graph we compute a prototype. */
214  for(l = graph_vertices(the_dfg); l != NIL; l = CDR(l)) {
215  vertex v;
216  int stmt;
217  static_control stct;
218  list ind_l, par_l, aux_par_l;
219 
220  v = VERTEX(CAR(l));
222 
223  /* We get the "static_control" associated to the statement. */
225 
226  /* We get the list of indices of the englobing loops and structure
227  * parameters.
228  */
229  ind_l = static_control_to_indices(stct);
230  par_l = gen_append(prgm_parameter_l, NIL);
231 
232  stmt_lamb = NIL;
233 
234  /* First, we initialize the polynome in building the constant term. */
235  lamb = make_coeff(CONST_COEFF, ++count_coeff);
236  stmt_lamb = gen_nconc(stmt_lamb, CONS(ENTITY, lamb, NIL));
237  pp_proto = make_polynome(1.0, (Variable) lamb, (Value) 1);
238 
239  /* Then, for each index (ind) we build the monome ind*COEFF#, and add it
240  * to the polynome.
241  */
242  for( ; ind_l != NIL; ind_l = CDR(ind_l)) {
243  entity ind = ENTITY(CAR(ind_l));
244 
245  lamb = make_coeff(INDEX_COEFF, ++count_coeff);
246  stmt_lamb = gen_nconc(stmt_lamb, CONS(ENTITY, lamb, NIL));
247 
248  pp_ind = make_polynome(1.0, (Variable) ind, (Value) 1);
249  pp_coeff = make_polynome(1.0, (Variable) lamb, (Value) 1);
250  pp_new = polynome_mult(pp_ind, pp_coeff);
251 
252  polynome_add(&pp_proto, pp_new);
253  }
254 
255  /* Then, for each parameter (par) we build the monome par*COEFF#, and add it
256  * to the polynome.
257  */
258  for(aux_par_l = par_l ; !ENDP(aux_par_l); POP(aux_par_l)) {
259  entity par = ENTITY(CAR(aux_par_l));
260 
261  lamb = make_coeff(PARAM_COEFF, ++count_coeff);
262  stmt_lamb = gen_nconc(stmt_lamb, CONS(ENTITY, lamb, NIL));
263 
264  pp_par = make_polynome(1.0, (Variable) par, (Value) 1);
265  pp_coeff = make_polynome(1.0, (Variable) lamb, (Value) 1);
266  pp_new = polynome_mult(pp_par, pp_coeff);
267 
268  polynome_add(&pp_proto, pp_new);
269  }
270 
271  /* We put the new prototype on the hash table. */
272  hash_put(StmtToLamb, (char *) stmt , (char *) stmt_lamb);
273  hash_put(StmtToProto, (char *) stmt , (char *) pp_proto);
274 
275  l_lamb = gen_append(stmt_lamb, l_lamb);
276  }
277  return(l_lamb);
278 }
279 
280 /* ======================================================================== */
281 /*
282  * void initialize_mu_list(int stmt, dim)
283  */
285 int stmt, dim;
286 {
287  extern int count_mu_coeff;
288  extern hash_table StmtToMu;
289 
290  list mu_l = NIL;
291  int i;
292 
293  for(i = 0; i < dim; i++) {
295  mu_l = gen_nconc(mu_l, CONS(ENTITY, mu, NIL));
296  }
297  hash_put(StmtToMu, (char *) stmt , (char *) mu_l);
298 }
299 
300 
301 /* ======================================================================== */
302 /*
303  * int plc_make_min_dim():
304  *
305  * computes the minimum number of dimensions for the placement
306  * function.
307  *
308  * It is equal to the dimension associated to the instruction
309  * which is nested into the deepest sequential nest loop, i.e., which has
310  * the schedule with the biggest number of dimensions. In all cases, the
311  * placement has at least one dimension.
312  */
314 {
315  extern graph the_dfg;
316  extern bdt the_bdt;
318 
319  int dmin = 1, bdmax = 1;
320  list l;
321 
325 
326  /* For each node of the data flow graph we compute its dimension. */
327  for(l = graph_vertices(the_dfg); l != NIL; l = CDR(l)) {
328  vertex v;
329  int stmt, dim, b_dim, p_dim;
330  static_control stct;
331  list ind_l;
332 
333  v = VERTEX(CAR(l));
334  stmt = vertex_int_stmt(v);
336  ind_l = static_control_to_indices(stct);
337 
338  /* We compute the dimension of the current node */
339  dim = gen_length(ind_l);
340 
341  /* We get the dimension of the timing and placement function of the
342  * current node */
343  b_dim = (int) hash_get(StmtToBdim, (char *) stmt);
344  p_dim = (int) hash_get(StmtToPdim, (char *) stmt);
345 
346  if((bdmax <= b_dim) && (dmin < p_dim))
347  dmin = p_dim;
348  }
349  return(dmin);
350 }
351 
352 
353 /* ======================================================================== */
354 /*
355  * int plc_make_dim():
356  *
357  * computes the maximum possible dimension of the placement function
358  * associated to each instruction and returns the greatest of these
359  * dimensions.
360  *
361  * For an given instruction, the dimension of its placement function is the
362  * substraction of the englobing space dimension and the timing function
363  * dimension.
364  */
366 {
367  extern graph the_dfg;
368  extern bdt the_bdt;
370 
371  int dmax = 0;
372  list l;
373 
377 
378  /* For each node of the data flow graph we compute its dimension. */
379  for(l = graph_vertices(the_dfg); l != NIL; l = CDR(l)) {
380  vertex v = VERTEX(CAR(l));
381  int stmt = vertex_int_stmt(v);
383  list ind_l = static_control_to_indices(stct);
384  int dim, b_dim = 0, sdim;
385 
386  /* We compute the dimension of the current node */
387  dim = gen_length(ind_l);
388 
389  /* We compute the dimension of the timing function of the current node */
390  if(the_bdt != bdt_undefined) {
391  list bl;
392  b_dim = 0;
393  for(bl = bdt_schedules(the_bdt); bl != NIL; bl = CDR(bl)) {
394  schedule sc = SCHEDULE(CAR(bl));
395  if(schedule_statement(sc) == stmt) {
396  list dl;
397  sdim = 0;
398  for(dl = schedule_dims(sc); dl != NIL; dl = CDR(dl)) {
399  expression e = EXPRESSION(CAR(dl));
400  if(! expression_constant_p(e)) {
401  list l;
402  bool ind_not_null;
403  Pvecteur pv;
404 
407 
408  ind_not_null = false;
409  for(l = ind_l; (!ENDP(l)) && (!ind_not_null); POP(l)) {
410  entity var = ENTITY(CAR(l));
411  if(vect_coeff((Variable) var, pv) != 0)
412  ind_not_null = true;
413  }
414  if(ind_not_null)
415  sdim++;
416  }
417  }
418  if(sdim > b_dim)
419  b_dim = sdim;
420  }
421  }
422  }
423  dim = dim - b_dim;
424  if(dim > dmax)
425  dmax = dim;
426  hash_put(StmtToPdim, (char *) stmt, (char *) dim);
427  hash_put(StmtToBdim, (char *) stmt, (char *) b_dim);
428 
429  initialize_mu_list(stmt, dim);
430  }
431  return(dmax);
432 }
433 
434 
435 /* ======================================================================== */
436 /*
437  * void plc_make_distance():
438  *
439  * computes the distance equation associated to each dataflow of the DFG.
440  *
441  * The distance is : PI(sink, x) - PI(source, h(x))
442  * where "sink" is the sink statement of the dataflow, "source" is the source
443  * statement of the dataflow, "x" is the iteration vector of sink statement,
444  * "h" is the transformation function of the dataflow and "PI" is the
445  * placement function (or prototype).
446  *
447  * So, for one given dataflow, the computation needs both prototypes of sink
448  * and source statements ("pp_sink" and "pp_source"), the transformations
449  * ("trans_l") and the iteration vector of the source ("source_ind_l").
450  *
451  * Each distance is put in a hash table "DtfToDis".
452  */
454 {
455  extern graph the_dfg;
456  extern hash_table StmtToProto, /* Mapping from a stmt to its prototype */
457  DtfToDist; /* Mapping from a dataflow to its distance */
458 
459  list l, su_l, df_l, source_ind_l, trans_l, si_l;
460  int source_stmt, sink_stmt;
461  static_control source_stct;
462  Ppolynome pp_source, pp_sink, pp_dist;
463 
464  /* We create the hash table. */
466 
467  for(l = graph_vertices(the_dfg); l != NIL; l = CDR(l)) {
468  vertex v = VERTEX(CAR(l));
469 
472 
473  /* Prototype of the source statement. */
474  pp_source = (Ppolynome) hash_get(StmtToProto, (char *) source_stmt);
475 
476  /* Iteration vector of the source statement. */
477  source_ind_l = static_control_to_indices(source_stct);
478 
479  su_l = vertex_successors(v);
480 
481  for( ; su_l != NIL; su_l = CDR(su_l)) {
482  successor su = SUCCESSOR(CAR(su_l));
483  vertex sink_v = successor_vertex(su);
484 
485  sink_stmt = vertex_int_stmt(sink_v);
486 
487  /* Prototype of the sink statement. */
488  pp_sink = (Ppolynome) hash_get(StmtToProto, (char *) sink_stmt);
489 
491 
492  /* For each dataflow of the data flow graph we compute a distance. */
493  for( ; df_l != NIL; df_l = CDR(df_l)) {
494  Ppolynome aux_pp;
495  predicate exec_domain, gov_pred;
496  Psysteme impl_sc, elim_sc, sc_ed = SC_UNDEFINED,
497  sc_gp = SC_UNDEFINED, df_domain;
498  list elim_vvs, impl_var, elim_var;
499 
500  dataflow df = DATAFLOW(CAR(df_l));
501 
502  /* Transformations of the dataflows. */
504 
505  /* There should be as much transformation expressions as source
506  * indices in the source iteration vector.
507  */
508  pips_assert("plc_make_distance",
509  gen_length(trans_l) == gen_length(source_ind_l));
510 
511  if(get_debug_level() > 3)
512  {
513  fprintf(stderr, "[plc_make_distance] \t for edge %d ->", source_stmt);
514  fprint_dataflow(stderr, sink_stmt, df);
515  fprintf(stderr, "\n");
516  }
517 
518  /* We now compute PI(source, h(x)). This is done by making the
519  * substitution, in the source prototype, of each index of the
520  * iteration vector of the source statement to the corresponding
521  * transformation expression.
522  *
523  * For this, we duplicate our polynome (source prototype) in
524  * "aux_pp". Then, for each index, we get its factor in "aux_pp",
525  * multiply it with the corresponding transformation, add it to
526  * "pp_dist" (initialized to POLYNOME_NUL) and eliminate the index
527  * in "aux_pp" (we substitute the index by POLYNOME_NUL). Then, we
528  * add "aux_pp" to "pp_dist", it contains the remnants of "pp_source"
529  * that are not factor of one of the indices.
530  */
531  pp_dist = POLYNOME_NUL;
532  aux_pp = polynome_dup(pp_source);
533  si_l = source_ind_l;
534  if(get_debug_level() > 4) {
535  fprintf(stderr, "[plc_make_distance] \t\tSource prototype:\n");
537  fprintf(stderr, "\n");
538  }
539  for( ; si_l != NIL; si_l = CDR(si_l), trans_l = CDR(trans_l)) {
540  entity var = ENTITY(CAR(si_l));
541  expression trans = EXPRESSION(CAR(trans_l));
542 
543  polynome_add(&pp_dist,
546  (Variable) var))));
547 /*
548  polynome_add(&pp_dist,
549  polynome_mult(expression_to_polynome(trans),
550  polynome_factorize(aux_pp, (Variable) var, 1)));
551 */
552 
553  aux_pp = prototype_var_subst(aux_pp, (Variable) var, POLYNOME_NUL);
554 /*
555  di_polynome_var_subst_null(&aux_pp, var);
556  aux_pp = polynome_var_subst(aux_pp, (Variable) var, POLYNOME_NUL);
557 */
558 
559  if(get_debug_level() > 5) {
560  fprintf(stderr, "[plc_make_distance] \t\t\tTransformation for index %s : %s\n",
562  fprintf(stderr, "[plc_make_distance] \t\t\tCrt PI(source, h(x)):\n");
564  fprintf(stderr, "\n");
565  }
566  }
567  polynome_add(&pp_dist, aux_pp);
568 
569  if(get_debug_level() > 5) {
570  fprintf(stderr, "[plc_make_distance] \t\t\tPI(sink, x) :\n");
572  fprintf(stderr, "\n");
573  fprintf(stderr, "[plc_make_distance] \t\t\tPI(source, h(x)) :\n");
575  fprintf(stderr, "\n");
576  }
577 
578  /* We now compute the distance : D = PI(sink, x) - PI(source, h(x))
579  * Still, it is a polynome ("pp_dist").
580  */
581  polynome_negate(&pp_dist);
582  polynome_add(&pp_dist, pp_sink);
583 
584  if(get_debug_level() > 4) {
585  fprintf(stderr, "[plc_make_distance] BEFORE IMPL ELIM \t\tDistance pp:\n");
587  fprintf(stderr, "\n");
588  }
589 
590  /* We now eliminate variables in order to have free variables. This
591  * is done using the implicit equations of the execution domain
592  * intersection the governing predicate.
593  */
594  exec_domain = VERTEX_DOMAIN(sink_v);
596  if(exec_domain == predicate_undefined) {
598  df_domain = sc_new();
599  else
600  df_domain = (Psysteme) predicate_system(gov_pred);
601  }
602  else {
604  df_domain = (Psysteme) predicate_system(exec_domain);
605  else {
606  df_domain = sc_new();
607  sc_ed = (Psysteme) predicate_system(exec_domain);
609  df_domain = sc_intersection(df_domain, sc_ed, sc_gp);
610  }
611  }
612 
613  if(get_debug_level() > 4) {
614  fprintf(stderr, "[plc_make_distance] \t\t Exec domain: ");
615  fprint_psysteme(stderr, sc_ed);
616  fprintf(stderr, "[plc_make_distance] \t\t Gov pred : ");
617  fprint_psysteme(stderr, sc_gp);
618  fprintf(stderr, "[plc_make_distance] \t\t Inter the 2: ");
619  fprint_psysteme(stderr, df_domain);
620  }
621 
622  impl_sc = find_implicit_equation(df_domain);
623 
624  if(get_debug_level() > 4) {
625  fprintf(stderr, "[plc_make_distance] \t\t Impl sys : ");
626  fprint_psysteme(stderr, impl_sc);
627  }
628 
629  if(impl_sc != NULL) {
630  impl_var = base_to_list(impl_sc->base);
631 
632  elim_sc = elim_var_with_eg(impl_sc, &impl_var, &elim_var);
633  elim_vvs = make_vvs_from_sc(elim_sc, elim_var);
634 
635  if(get_debug_level() > 4) {
636  fprintf(stderr, "[plc_make_distance] \t\t New subs :\n");
637  fprint_vvs(stderr, elim_vvs);
638  }
639 
640  pp_dist = vvs_on_polynome(elim_vvs, pp_dist);
641 
642  }
643  if(get_debug_level() > 4) {
644  fprintf(stderr, "[plc_make_distance] \t\tDistance pp:\n");
646  fprintf(stderr, "\n");
647  }
648 
649  /* We put this polynome in the hash table. */
650  hash_put(DtfToDist, (char *) df , (char *) pp_dist);
651 
652  }
653  }
654  }
655 }
656 
657 
658 /* ======================================================================== */
659 /*
660  * Psysteme cutting_conditions(list df_l):
661  *
662  * returns a system of equations to be verified in order to zero out all
663  * the distances associated to each dataflow of the list "df_l".
664  *
665  * The distance is taken from a hash table "DtfToDis".
666  *
667  * In fact, for each distance (i.e. dataflow), we create two systems: one that
668  * nullified the factor of the loop indices (Mi) and one that nullified the
669  * structure parameters and the constant term (Mp).
670  *
671  * For example, with I and J as indices, N as parameter, the distance
672  * I*(C1-C2) + J*(C3+C1) + N*(C2+C3) + C4-C1)
673  * will leave the following systems :
674  * Mi = {C1-C2 = 0, C3+C1 = 0}
675  * Mp = {C2+C3 = 0, C4-C1 = 0}
676  * The C# are unknown coefficients created for the prototypes.
677  *
678  * The return system M is the union of this system so as to place first the
679  * Mi systems (in decreasing weight order) and then the Mp systems (in
680  * decreasing weight order).
681  */
683 list df_l;
684 {
685  extern hash_table DtfToDist; /* Mapping from a dataflow to its distance */
686  extern list prgm_parameter_l;
687 
688  list l, sink_ind_l, sink_par_l;
689  int sink_stmt;
690  static_control sink_stct;
691  Psysteme Mi, Mp, M;
692  Ppolynome pp_dist;
693 
694  Mi = sc_new();
695  Mp = sc_new();
696  for(l = df_l; !ENDP(l); POP(l)) {
697  dataflow df = DATAFLOW(CAR(l));
698  Psysteme Mi_local, Mp_local;
699 
700  sink_stmt = (int) hash_get(DtfToSink, (char *) df);
702 
703  /* Iteration vector of the sink statement. */
704  sink_ind_l = static_control_to_indices(sink_stct);
705 
706  /* Structure parameters. */
707  /* sink_par_l = gen_append(static_control_params(sink_stct),
708  * CONS(ENTITY, (entity) TCST, NIL)); */
709  sink_par_l = gen_append(prgm_parameter_l,
710  CONS(ENTITY, (entity) TCST, NIL));
711 
712  pp_dist = polynome_dup((Ppolynome) hash_get(DtfToDist, (char *) df));
713 
714  /* We transforme this polynome ("pp_dist") into two systems of
715  * equations, Mi and Mp (cf. above).
716  */
717  Mi_local = nullify_factors(&pp_dist, sink_ind_l, false);
718  Mp_local = nullify_factors(&pp_dist, sink_par_l, true);
719 
720  polynome_rm(&pp_dist);
721 
722  if(get_debug_level() > 3) {
723  fprintf(stderr, "[plc_make_distance] \tDistance Mi:\n");
724  fprint_psysteme(stderr, Mi_local);
725  fprintf(stderr, "[plc_make_distance] \tDistance Mp:\n");
726  fprint_psysteme(stderr, Mp_local);
727  }
728  Mi = append_eg(Mi, Mi_local);
729  Mp = append_eg(Mp, Mp_local);
730  }
731  M = append_eg(Mi, Mp);
732  sc_normalize(M);
733  return(M);
734 }
735 
736 
737 /* ======================================================================== */
738 /*
739  * list sort_dfg_node(list l_nodes):
740  *
741  * returns the sorted list of the nodes of the list "l_nodes". The sorting
742  * is based on the dimension of the nodes, in decreasing order.
743  *
744  * We need to compute for each node its dimension. This dimension is the
745  * dimension of the iteration space of its associated statement, i.e. the
746  * length of the list of the loop indices.
747  */
749 list l_nodes;
750 {
751  extern hash_table StmtToDim;
752  extern int nb_nodes;
753 
754  list l, new_l;
755 
757 
758  /* For each node of the data flow graph we compute its dimension. */
759  for(l = l_nodes; l != NIL; l = CDR(l)) {
760  int stmt = vertex_int_stmt(VERTEX(CAR(l)));
762  list ind_l = static_control_to_indices(stct);
763 
764  hash_put(StmtToDim, (char *) stmt, (char *) gen_length(ind_l));
765  }
766  new_l = general_merge_sort(l_nodes, compare_nodes_dim);
767 
769 
770  return(new_l);
771 }
772 
773 
774 /* ======================================================================== */
775 /*
776  * void edge_weight():
777  *
778  * computes the weight of each dataflows of DFG. If a
779  * dataflow is a broadcast or a reduction, its weight is the dimension of
780  * the space on which the data movement is done. Else it is the dimension
781  * of its emitter set Ee = {y/ y = he(x), x in Pe}.
782  *
783  * he: transformations
784  * Pe: execution domain of the sink and governing predicate of the edge
785  * y: indices of the sources
786  * x: indices of the sink
787  *
788  * For the computation of the dimension of this emitter set, we eliminate x
789  * by a combination of Gauss-Jordan and Fourier-Motzkin
790  * algorithms. Ee is then defined by a set of inequalities for which we can
791  * compute the set of implicit equations Eei. The dimension of Ee is then
792  * equal to:
793  * Dim(y) - Card(Eei)
794  */
796 {
797  extern graph the_dfg;
798  extern hash_table DtfToSink,
799  DtfToWgh;
800 
801  list l, su_l, df_l;
802  Psysteme sc_trans, sc_elim;
803  predicate sink_domain;
804  int source_stmt, sink_stmt, n_impl, poids;
805  static_control sink_stct;
806 
807  /* We initialize the weight and sink statement hash tables */
810 
811  /* For each dataflow of the data flow graph we compute its weight. */
812  for(l = graph_vertices(the_dfg); l != NIL; l = CDR(l)) {
813  vertex v = VERTEX(CAR(l));
815 
816  su_l = vertex_successors(v);
817 
818  for( ; su_l != NIL; su_l = CDR(su_l)) {
819  successor su = SUCCESSOR(CAR(su_l));
820 
823  sink_domain = VERTEX_DOMAIN(successor_vertex(su));
824 
825  df_l = SUCC_DATAFLOWS(su);
826 
827  for(; df_l != NIL; df_l = CDR(df_l)) {
828  dataflow df = DATAFLOW(CAR(df_l));
829 
830  if(is_broadcast_p(df) || is_reduction_p(df)) {
831  poids = communication_dim(df);
832  }
833  else {
835  list trans_l, si_l, aux_l;
836 
839 
840  /* Transformation system of equations */
842 
843  /* We append the execution domain of the sink. */
844  if(sink_domain != predicate_undefined)
845  sc_trans = sc_append(sc_trans, (Psysteme) predicate_system(sink_domain));
846 
847  /* We append the governing predicate. "sc_trans" is what we called Ee
848  * (the emitter set, cf. above).
849  */
851  sc_trans = sc_append(sc_trans, (Psysteme) predicate_system(gov_pred));
852 
853  if(get_debug_level() > 3)
854 {
855  fprintf(stderr, "[edge_weight] \tfor edge: %d ->", source_stmt);
856  fprint_dataflow(stderr, sink_stmt, df);
857  fprintf(stderr, "\n");
858  fprintf(stderr, "[edge_weight] \ttrans system is:");
859  fprint_psysteme(stderr, sc_trans);
860  }
861 
862  /* Gauss-Jordan eliminations (with equalities). */
863  si_l = static_control_to_indices(sink_stct);
864 
865  aux_l = NIL;
866 
867  sc_elim = elim_var_with_eg(sc_trans, &si_l, &aux_l);
868 
869  if(get_debug_level() > 5) {
870  fprintf(stderr, "[edge_weight] \t\t\tElim equations are: ");
871  fprint_psysteme(stderr, sc_elim);
872  fprintf(stderr, "[edge_weight] \t\t\tAfter elim equations: ");
873  fprint_psysteme(stderr, sc_trans);
874  }
875  /* Fourier-Motzkin eliminations (with inequalities). */
876  for( ; si_l != NIL; si_l = CDR(si_l)) {
877  entity var = ENTITY(CAR(si_l));
878  sc_trans = sc_integer_projection_along_variable(sc_dup(sc_trans),
879  sc_trans,
880  (Variable) var);
881 
882  debug(7, "edge_weight", "\t\t\t\tElim ineq with %s\n",
883  entity_local_name(var));
884  }
885 
886  /* We compute the number of implicit equations. */
887  n_impl = count_implicit_equation(sc_trans);
888 
889  if(get_debug_level() > 4) {
890  fprintf(stderr, "[edge_weight] \t\tNumber of implicit equa is %d of: ", n_impl);
891  fprint_psysteme(stderr, sc_trans);
892  }
893  /* We compute the weight of the current dataflow. */
894  poids = gen_length(trans_l) - n_impl;
895 
896  }
897 
898  debug(4, "edge_weight", "\tWeight of the edge: %d\n", poids);
899 
900  /* We update the hash tables keyed by the dataflow with its weight
901  * and its sink statement.
902  */
903  hash_put(DtfToWgh, (char *) df , (char *) poids);
904  hash_put(DtfToSink, (char *) df , (char *) sink_stmt);
905  }
906  }
907  }
908 }
909 
910 
911 /* ======================================================================== */
912 /*
913  * bool in_list_p(chunk *c, list l)
914  *
915  * returns true if "c" appears in "l".
916  */
917 bool in_list_p(c, l)
918 chunk *c;
919 list l;
920 {
921  list ll = l;
922  bool not_found = true;
923 
924  for( ; !ENDP(ll) && (not_found); POP(ll) ) {
925  if(c == CHUNK(CAR(ll)))
926  not_found = false;
927  }
928  return(!not_found);
929 }
930 
931 /* ======================================================================== */
932 /*
933  * void add_to_list(chunk *c, list *l)
934  *
935  * Adds "c" in "l" if it does not appears in it yet.
936  *
937  * Note: "l" is a pointer to a list, the usage is add_to_list(c, &l);
938  */
939 void add_to_list(c, l)
940 chunk *c;
941 list *l;
942 {
943  list ll = *l;
944  if(!in_list_p(c, ll))
945  *l = CONS(CHUNK, c, ll);
946 }
947 
948 /* ======================================================================== */
949 /*
950  * int prototype_dimension(Ppolynome pp, list ind_l):
951  *
952  * returns the number of linearly independent vectors we can construct with
953  * "pp" and "ind_l".
954  *
955  * Indeed, "pp" is a prototype, i.e. a 2-dimensional polynome without squared
956  * variables. For instance (x.y + y.z) could be a prototype, but (x^2 + y.z)
957  * could not.
958  *
959  * We distinguish three kinds of variables in this polynome: the indices (from
960  * "ind_l"), the parameters and the coefficients. A monome of this polynome
961  * can be of six kinds:
962  * _ a constant (integer value)
963  * _ a coefficient multiplied by a constant
964  * _ a parameter multiplied by a constant
965  * _ an index multiplied by a constant
966  * _ a parameter multiplied by a coefficient and a constant
967  * _ an index multiplied by a coefficient and a constant
968  *
969  * So "pp" may be represented as: pp = I.A.L + P.B.L + C.L + I.D + P.E + c,
970  * where I and P are respectively row vectors of indices and of parameters,
971  * A and B are 2-D integer matrices, L is a column vector of coefficients,
972  * C, D and E are integer column vectors and c is an integer scalar.
973  *
974  * The goal of this function is to count how many independent vectors we can
975  * have when giving values to the coefficients. These vectors represented as
976  * linear combinations of the indices from "ind_l". So, only the monomes that
977  * contain an index are useful for this computation: ppi = I.A.L + I.D
978  *
979  * So the number of independent vectors is also the number of independent
980  * values of A.L, so it is rank(A).
981  *
982  * Note: this function take advantage of the special form of the prototype
983  * polynome.
984  */
985 int prototype_dimension(pp, ind_l)
986 Ppolynome pp;
987 list ind_l;
988 {
989  int dim, n, m;
990  Value det_q, det_p;
991  matrice mat_A, mat_Z, mat_P, mat_Q, mat_H;
992  list li;
993  Pbase base_L;
994  Psysteme ps_AL = sc_new();
995 
996 if(get_debug_level() > 7) {
997 fprintf(stderr, "[prototype_dimension] Prototype : ");
999 fprintf(stderr, "\n");
1000 fprintf(stderr, "[prototype_dimension] Indices : ");
1001 fprint_entity_list(stderr, ind_l);
1002 fprintf(stderr, "\n");
1003 }
1004 
1005 
1006  /* We construct A.L, in which each line correspond to the factor of one
1007  * index in "pp".
1008  */
1009  for(li = ind_l; !ENDP(li); POP(li)) {
1010  Pvecteur one_line = prototype_factorize(pp, (Variable) ENTITY(CAR(li)));
1011  sc_add_egalite(ps_AL, contrainte_make(one_line));
1012  }
1013  sc_creer_base(ps_AL);
1014 
1015  /* L is the list of variables contained in AL. */
1016  base_L = ps_AL->base;
1017 
1018 if(get_debug_level() > 7) {
1019 fprintf(stderr, "[prototype_dimension] ps_AL : ");
1020 fprint_psysteme(stderr, ps_AL);
1021 fprintf(stderr, "[prototype_dimension] base_L : ");
1022 pu_vect_fprint(stderr, base_L);
1023 fprintf(stderr, "\n");
1024 }
1025 
1026  n = ps_AL->nb_eq;
1027  m = base_dimension(base_L);
1028 
1029  if( (n == 0) || (m == 0) )
1030  dim = 0;
1031  else {
1032  mat_A = matrice_new(n, m);
1033  mat_Z = matrice_new(n, 1);
1034  pu_contraintes_to_matrices(ps_AL->egalites, base_L, mat_A, mat_Z, n, m);
1035  mat_P = matrice_new(n, n);
1036  mat_Q = matrice_new(m, m);
1037  mat_H = matrice_new(n, m);
1038  matrice_hermite(mat_A, n, m, mat_P, mat_H, mat_Q, &det_p, &det_q);
1039  dim = dim_H(mat_H, n, m);
1040 
1041 if(get_debug_level() > 7) {
1042 fprintf(stderr, "[prototype_dimension] A of rank = %d : ", dim);
1043 matrice_fprint(stderr, mat_A, n, m);
1044 fprintf(stderr, "\n");
1045 }
1046 
1047  matrice_free(mat_A);
1048  matrice_free(mat_Z);
1049  matrice_free(mat_P);
1050  matrice_free(mat_Q);
1051  matrice_free(mat_H);
1052  }
1053 
1054 /* OLD VERSION */
1055 /*
1056  for(ppp = pp; ppp != NULL; ppp = ppp->succ) {
1057  entity first = entity_undefined, second = entity_undefined;
1058  pv = (ppp->monome)->term;
1059 
1060  for(; (pv != NULL) && (second == entity_undefined); pv = pv->succ) {
1061  second = first;
1062  first = (entity) pv->var;
1063  }
1064  if(pv != NULL)
1065  pips_internal_error("Not a prototype polynome");
1066 
1067  if( (first != entity_undefined) && (second != entity_undefined) ) {
1068  if(in_list_p(first, ind_l)) {
1069  add_to_list(second, &ivf_l);
1070  }
1071  else if(in_list_p(second, ind_l)) {
1072  add_to_list(first, &ivf_l);
1073  }
1074  }
1075  }
1076 
1077  dim = gen_length(ivf_l);
1078 
1079  gen_free_list(ivf_l);
1080 */
1081 
1082  return(dim);
1083 }
1084 
1085 
1086 /* ======================================================================== */
1087 /*
1088  * bool is_not_trivial_p(list vvs):
1089  *
1090  * returns true if all the prototypes are not trivial after applying "vvs".
1091  * Otherwise, returns FALSE.
1092  *
1093  * A prototype is not trivial if it depends on enough parameters that one may
1094  * construct the required number of linearly independent solutions.
1095  */
1097 list vvs;
1098 {
1099  extern hash_table StmtToProto, /* Mapping from a statement to its prototype */
1100  StmtToBdim;
1101 
1102  hash_table stp;
1103 
1104  list l, ind_l;
1105  int stmt, dim_plc, dim_bdt;
1106  Ppolynome pp;
1107  bool proto_not_triv = true;
1108 
1109  if(get_debug_level() > 5) {
1110  fprintf(stderr, "[is_not_trivial_p] \t\t\tSub is:\n");
1111  fprint_vvs(stderr, vvs);
1112  fprintf(stderr, "\n");
1113  }
1114 
1115  stp = hash_table_make(hash_int, nb_nodes+1);
1116 
1117  /* For each stmt in the dataflow graph we test if its proto is trivial */
1118  for(l = graph_vertices(the_dfg); (l != NIL) && proto_not_triv; l = CDR(l)) {
1119  vertex v = VERTEX(CAR(l));
1120 
1121  stmt = vertex_int_stmt(v);
1123  pp = polynome_dup((Ppolynome) hash_get(StmtToProto, (char *) stmt));
1124 
1125  dim_bdt = (int) hash_get(StmtToBdim, (char *) stmt);
1126 
1127  dim_plc = gen_length(ind_l) - dim_bdt;
1128 
1129  if(get_debug_level() > 6) {
1130  fprintf(stderr, "[is_not_trivial_p] \t\t\t\tProto is:");
1132  fprintf(stderr, "\n");
1133  }
1134 
1135  pp = vvs_on_polynome(vvs, pp);
1136 
1137  if(get_debug_level() > 5) {
1138  fprintf(stderr, "[is_not_trivial_p] must be of dim %d, After apply sub:", dim_plc);
1140  fprintf(stderr, "\n");
1141  }
1142 
1143  /* we carry on if the prototype is not trivial */
1144  if(prototype_dimension(pp, ind_l) < dim_plc)
1145  proto_not_triv = false;
1146  else
1147  hash_put(stp, (char *) stmt, (char *) pp);
1148  }
1149 
1150  if(get_debug_level() > 6) {
1151  fprintf(stderr, "[is_not_trivial_p] \t\t\t\tTriviality:");
1152  if(proto_not_triv)
1153  fprintf(stderr, "NON\n");
1154  else
1155  fprintf(stderr, "OUI\n");
1156  }
1157 
1158  if(proto_not_triv) {
1160  StmtToProto = stp;
1161 
1162  if(get_debug_level() > 3) {
1163  fprintf(stderr, "[is_not_trivial_p] New protos:\n");
1165  }
1166  }
1167  else
1168  hash_table_free(stp);
1169 
1170  return(proto_not_triv);
1171 }
1172 
1173 
1174 /* ======================================================================== */
1175 /*
1176  * list valuer(int dim, list xunks, list pcunks)
1177  *
1178  * valuation for the dimension "dim" of the placement function.
1179  *
1180  * "xunks" is the list of the INDEX coefficients not yet valuated: valuation
1181  * to 1 or 0.
1182  * "punks" is the list of the PARAM coefficients not yet valuated: valuation
1183  * using farkas lemma and PIP. These "punks" can be negative, so for this
1184  * resolution, we do the following: "punks = (p1, p2, p3) => p1 = a1 - a0,
1185  * p2 = a2 - a0, p3 = a3 - a0, with (a0, a1, a2, a3) positive. These a# are
1186  * called AUXIL coefficients, and "a0" is what we call "offset". Our list of
1187  * AUXIL coefficients is called "vl".
1188  */
1189 list valuer(dim, xunks, pcunks)
1190 int dim;
1191 list xunks, pcunks;
1192 {
1193  extern graph the_dfg;
1194 
1195  list l, ll, vl, var_l, sol, farkas_mult;
1196  int count_xc = 0, count_auxil_coeff = 0, stmt, count_farkas_mult;
1197  entity offset, nc;
1198  list new_vvs = NIL, vl_vvs;
1199  Psysteme pip_ps;
1200  Pcontrainte pc;
1201  Pvecteur pv_off;
1202  static_control stct;
1203  quast q_sol;
1204  quast_leaf ql;
1205  quast_value quv;
1206 
1207 if(get_debug_level() > 3) {
1208 fprintf(stderr, "\nPLC at dim %2d :\n===============\n", dim);
1209 }
1210 
1211  offset = find_or_create_coeff(AUXIL_COEFF, count_auxil_coeff);
1212  pv_off = vect_new((Variable) offset, 1);
1213  vl = CONS(ENTITY, offset, NIL);
1214 
1215  for(l = xunks; l != NIL; l = CDR(l)) {
1216  list xus = CONSP(CAR(l));
1217  for(ll = xus; !ENDP(ll); POP(ll)) {
1218  entity e = ENTITY(CAR(ll));
1219  if(count_xc == dim)
1220  new_vvs = compose_vvs(new_vvs, make_vvs(e, 1, vect_new(TCST, 1)));
1221  else
1222  new_vvs = compose_vvs(new_vvs, make_vvs(e, 1, vect_new(TCST, 0)));
1223  }
1224  count_xc++;
1225  }
1226 
1227  for(l = pcunks; l != NIL; l = CDR(l)) {
1228  entity e = ENTITY(CAR(l));
1229  count_auxil_coeff++;
1230  nc = find_or_create_coeff(AUXIL_COEFF, count_auxil_coeff);
1231  vl = CONS(ENTITY, nc, vl);
1232  new_vvs = compose_vvs(new_vvs,
1233  make_vvs(e, 1,
1235  vect_new((Variable) nc,1),
1236  -1,pv_off,
1237  NO_OFL_CTRL)));
1238  }
1239 
1240 if(get_debug_level() > 3) {
1241 fprintf(stderr, "\nNew subs:\n");
1242 fprint_vvs(stderr, new_vvs);
1243 fprintf(stderr, "\n");
1244 }
1245 
1246  pip_ps = sc_new();
1247  farkas_mult = NIL;
1248  count_farkas_mult = 0;
1249  vl_vvs = NIL;
1250  for(l = graph_vertices(the_dfg); l != NIL; l = CDR(l)) {
1251  list vvs, elim_vvs, aux_vvs;
1252  Psysteme elim_ps, farkas_ps, sc_ed;
1253  Ppolynome farkas_pp, sub_pp, proto_pp;
1254  list init_l = NIL, elim_l = NIL, new_vl;
1255  vertex v = VERTEX(CAR(l));
1256 
1257  stmt = vertex_int_stmt(v);
1258  proto_pp = (Ppolynome) hash_get(StmtToProto, (char *) stmt);
1260 
1261  sub_pp = vvs_on_polynome(compose_vvs(vl_vvs, new_vvs),
1262  polynome_dup(proto_pp));
1263  sc_ed = (Psysteme) predicate_system(VERTEX_DOMAIN(v));
1264 
1265 if(get_debug_level() > 3) {
1266 fprintf(stderr, "\nFarkas with %d : ", stmt);
1268 fprint_psysteme(stderr, sc_ed);
1269 fprint_entity_list(stderr, init_l);
1270 fprintf(stderr, "\n");
1271 }
1272 
1273  farkas_pp = apply_farkas(sub_pp, sc_ed, &init_l, &count_farkas_mult);
1274 
1275 if(get_debug_level() > 3) {
1276 fprintf(stderr, "\nFarkas DONE:\n");
1278 fprintf(stderr, "\nCoeff of Farkas: ");
1279 fprint_entity_list(stderr, init_l);
1280 fprintf(stderr, "\n");
1281 }
1282 
1285 
1286 if(get_debug_level() > 3) {
1287 fprintf(stderr, "\n List of Var to elim: ");
1288 fprint_entity_list(stderr, var_l);
1289 fprintf(stderr, "\n");
1290 }
1291 
1292  farkas_ps = nullify_factors(&farkas_pp, var_l, true);
1293 
1294 /* (void) polynome_free(sub_pp);*/
1295  (void) polynome_free(farkas_pp);
1296 
1297 if(get_debug_level() > 3) {
1298 fprintf(stderr, "\nEquations :\n");
1299 fprint_psysteme(stderr, farkas_ps);
1300 fprintf(stderr, "\n");
1301 }
1302 
1303  elim_ps = elim_var_with_eg(farkas_ps, &init_l, &elim_l);
1304 
1305 if(get_debug_level() > 3) {
1306 fprintf(stderr, "\nAfter ELIM LAMBDAS\n");
1307 fprintf(stderr, "\nElim Coeff and System: ");
1308 fprint_entity_list(stderr, elim_l);
1309 fprint_psysteme(stderr, elim_ps);
1310 fprintf(stderr, "Remaining Coeff and System :\n");
1311 fprint_entity_list(stderr, init_l);
1312 fprint_psysteme(stderr, farkas_ps);
1313 fprintf(stderr, "\n");
1314 }
1315 
1316  if(init_l != NIL)
1317  farkas_mult = gen_nconc(farkas_mult, init_l);
1318 
1319  aux_vvs = NIL;
1320  new_vl = gen_concatenate(vl, NIL);
1321  if(farkas_ps->nb_eq != 0) {
1322  list vl_elim = NIL;
1323  Psysteme vl_ps;
1324 
1325  vl_ps = elim_var_with_eg(farkas_ps, &new_vl, &vl_elim);
1326 
1327  aux_vvs = make_vvs_from_sc(vl_ps, vl_elim);
1328 
1329  vl_vvs = compose_vvs(vl_vvs, aux_vvs);
1330 
1331 if(get_debug_level() > 3) {
1332 fprintf(stderr, "\nAfter ELIM AUXIL\n");
1333 fprintf(stderr, "\nElim Coeff and System: ");
1334 fprint_entity_list(stderr, vl_elim);
1335 fprint_psysteme(stderr, vl_ps);
1336 fprintf(stderr, "Remaining Coeff and System :\n");
1337 fprint_entity_list(stderr, new_vl);
1338 fprint_psysteme(stderr, farkas_ps);
1339 fprintf(stderr, "\n");
1340 }
1341  }
1342 
1343  elim_vvs = make_vvs_from_sc(elim_ps, elim_l);
1344 
1345  for(vvs = elim_vvs ; vvs != NIL; vvs = CDR(vvs)) {
1346  var_val vv = VAR_VAL(CAR(vvs));
1349  }
1350  for(pc = farkas_ps->egalites; pc != NULL; pc = pc->succ) {
1351  sc_add_egalite(pip_ps, contrainte_dup(pc));
1352  }
1353  pip_ps = vvs_on_systeme(aux_vvs, pip_ps);
1354  sc_normalize(pip_ps);
1355 
1356 if(get_debug_level() > 3) {
1357 fprintf(stderr, "\nNEW PIP systeme :\n");
1358 fprint_psysteme(stderr, pip_ps);
1359 fprintf(stderr, "\nVL subs:\n");
1360 fprint_vvs(stderr, vl_vvs);
1361 fprintf(stderr, "\n");
1362 }
1363  }
1364 
1365 if(get_debug_level() > 3) {
1366 fprintf(stderr, "\nNEW subs (before):\n");
1367 fprint_vvs(stderr, new_vvs);
1368 fprintf(stderr, "\n");
1369 }
1370 
1371  new_vvs = vvs_on_vvs(vl_vvs, new_vvs);
1372 
1373 if(get_debug_level() > 3) {
1374 fprintf(stderr, "\nNEW subs:\n");
1375 fprint_vvs(stderr, new_vvs);
1376 fprintf(stderr, "\n");
1377 }
1378  vect_rm(pip_ps->base);
1379  pip_ps->base = NULL;
1380  sc_creer_base(pip_ps);
1381 
1382  /* We sort the unknowns in order to have the auxiliary variables first */
1384  pip_ps->base = list_to_base(var_l);
1385 
1386  q_sol = pip_integer_min(pip_ps, SC_EMPTY, pip_ps->base);
1387 
1388 if(get_debug_level() > 3) {
1389 fprintf(stderr, "\nSol to PIP sys :\n\tList of unks:");
1390 fprint_entity_list(stderr, var_l);
1391 fprintf(stderr, "\n");
1392 imprime_quast(stderr, q_sol);
1393 fprintf(stderr, "\n");
1394 }
1395 
1396  if( (q_sol == quast_undefined) || (q_sol == NULL) )
1397  user_error("valuer", "Pip sol undefined\n");
1398  quv = quast_quast_value(q_sol);
1399  if( quv == quast_value_undefined )
1400  user_error("valuer", "Pip sol undefined\n");
1401  switch( quast_value_tag(quv)) {
1403  user_error("valuer", "Pip sol conditional\n");
1404  break;
1405 
1407  ql = quast_value_quast_leaf( quv );
1408  sol = quast_leaf_solution(ql);
1409  for( ; sol != NIL; POP(sol), POP(var_l)) {
1410  expression exp = EXPRESSION(CAR(sol));
1411  entity var = ENTITY(CAR(var_l));
1412  Pvecteur pv;
1413 
1416  else {
1419  }
1420  new_vvs = vvs_on_vvs(make_vvs(var, 1, pv), new_vvs);
1421  }
1422  break;
1423  }
1424 
1425 if(get_debug_level() > 3) {
1426 fprintf(stderr, "\nNEW subs (FINAL):\n");
1427 fprint_vvs(stderr, new_vvs);
1428 fprintf(stderr, "\n");
1429 }
1430 
1431  return(new_vvs);
1432 }
1433 
1434 
1435 
1436 /* ======================================================================== */
1437 /* void sort_unknowns(list *lambda, int dmax) :
1438  *
1439  *
1440  */
1441 void sort_unknowns(lambda, dmax)
1442 list *lambda;
1443 int dmax;
1444 {
1445  extern hash_table StmtToProto;
1446  extern hash_table UnkToFrenq;
1447 
1448  list vl, xl = NIL, cl, newl = *lambda, pl = NIL;
1449  int nb_xl = 0, *frenq_tab, r;
1450 
1451  for(cl = newl; !ENDP(cl); POP(cl)) {
1452  entity u = ENTITY(CAR(cl));
1453  if(is_index_coeff_p(u)) {
1454  nb_xl++;
1455  xl = gen_nconc(xl, CONS(ENTITY, u, NIL));
1456  }
1457  else
1458  pl = CONS(ENTITY, u, pl);
1459  }
1460  newl = pl;
1461  if(nb_xl <= dmax) {
1462  for(; !ENDP(xl); POP(xl)) {
1463  entity e = ENTITY(CAR(xl));
1464  newl = CONS(ENTITY, e, newl);
1465  }
1466  }
1467  else {
1469  frenq_tab = (int *) malloc(sizeof(int) * nb_xl);
1470  for(r = 0; r < nb_xl; r++) {frenq_tab[r] = 0;}
1471 
1472  for(vl = graph_vertices(the_dfg); vl != NIL; vl = CDR(vl)) {
1473  int stmt = vertex_int_stmt(VERTEX(CAR(vl)));
1474  Ppolynome pp = (Ppolynome) hash_get(StmtToProto, (char *) stmt);
1475 
1476  for(cl = xl, r = 0; cl != NIL; cl = CDR(cl), r++) {
1477  Pvecteur pv_fac = prototype_factorize(pp, (Variable) ENTITY(CAR(cl)));
1478  frenq_tab[r] += vect_size(pv_fac);
1479  }
1480  }
1481  for(cl = xl, r = 0 ; cl != NIL; cl = CDR(cl), r++) {
1482  entity ce = ENTITY(CAR(cl));
1483  hash_put(UnkToFrenq, (char *) ce, (char *) frenq_tab[r]);
1484 
1485  debug(5, "sort_unknowns", "Frenq of %s is %d\n",
1486  entity_local_name(ce), frenq_tab[r]);
1487  }
1488  newl = gen_nconc(general_merge_sort(xl, compare_unks_frenq), newl);
1489 
1490  free(frenq_tab);
1492  }
1493  *lambda = newl;
1494 }
1495 
1496 
1497 /* ======================================================================== */
1499 list *unks;
1500 int dmax;
1501 {
1502  extern hash_table StmtToProto;
1503 
1504  list l, xl = NIL, cl, xunks, pcunks, aux_xl, xul;
1505  int nb_xl = 0;
1506 
1507 if(get_debug_level() > 4) {
1508 fprintf(stderr, "[partition_unknowns] BEGIN with dmax = %d, and unks: ", dmax);
1509 fprint_entity_list(stderr, *unks);
1510 fprintf(stderr, "\n");
1511 }
1512 
1513  pcunks = NIL;
1514  for(cl = *unks; !ENDP(cl); POP(cl)) {
1515  entity u = ENTITY(CAR(cl));
1516  if(is_index_coeff_p(u)) {
1517  nb_xl++;
1518  xl = gen_nconc(xl, CONS(ENTITY, u, NIL));
1519  }
1520  else
1521  pcunks = CONS(ENTITY, u, pcunks);
1522  }
1523 
1524 if(get_debug_level() > 4) {
1525 fprintf(stderr, "[partition_unknowns] pcunks: ");
1526 fprint_entity_list(stderr, pcunks);
1527 fprintf(stderr, "\n");
1528 fprintf(stderr, "[partition_unknowns] %d in xl: ", nb_xl);
1529 fprint_entity_list(stderr, xl);
1530 fprintf(stderr, "\n");
1531 }
1532 
1533  *unks = pcunks;
1534  xunks = NIL;
1535  if(nb_xl <= dmax) {
1536  for(; !ENDP(xl); POP(xl)) {
1537  entity e = ENTITY(CAR(xl));
1538  xunks = gen_nconc(xunks, CONS(CONSP, CONS(ENTITY, e, NIL), NIL));
1539  }
1540  }
1541  else {
1542  list rem_xl = gen_append(xl, NIL);
1543  for(l = graph_vertices(the_dfg); !ENDP(l) && !ENDP(rem_xl); POP(l)) {
1544  int stmt = vertex_int_stmt(VERTEX(CAR(l)));
1545  Ppolynome proto_pp = (Ppolynome) hash_get(StmtToProto, (char *) stmt);
1546  list lax, plax = NIL;
1547 
1548  aux_xl = gen_append(xl, NIL);
1549 
1550 if(get_debug_level() > 4) {
1551 fprintf(stderr, "[partition_unknowns] stmt %d, proto: ", stmt);
1553 fprintf(stderr, "\n");
1554 }
1555 
1556  for(cl = xl; cl != NIL; cl = CDR(cl)) {
1557  entity e = ENTITY(CAR(cl));
1558  Pvecteur pv_fac = prototype_factorize(proto_pp, (Variable) e);
1559  if(VECTEUR_NUL_P(pv_fac)) {
1560  gen_remove(&aux_xl, (chunk *) e);
1561  }
1562  }
1563 
1564 if(get_debug_level() > 4) {
1565 fprintf(stderr, "[partition_unknowns] xl of crt proto:");
1566 fprint_entity_list(stderr, aux_xl);
1567 fprintf(stderr, "\n");
1568 }
1569 
1570  for(lax = xunks; !ENDP(lax) && !ENDP(rem_xl) && !ENDP(aux_xl); POP(lax)) {
1571  list crt_ax = CONSP(CAR(lax));
1572  bool not_found = true;
1574 
1575  for(cl = aux_xl; !ENDP(cl) && not_found; cl = CDR(cl)) {
1576  e = ENTITY(CAR(cl));
1577  if(in_list_p((chunk *) e, crt_ax))
1578  not_found = false;
1579  }
1580  if(not_found) {
1581  for(cl = aux_xl; !ENDP(cl) && not_found; cl = CDR(cl)) {
1582  e = ENTITY(CAR(cl));
1583  if(in_list_p((chunk *) e, rem_xl))
1584  not_found = false;
1585  }
1586  if(!not_found) {
1587  CONSP(CAR(lax)) = gen_nconc(crt_ax, CONS(ENTITY, e, NIL));
1588  gen_remove(&rem_xl, (chunk *) e);
1589  gen_remove(&aux_xl, (chunk *) e);
1590  }
1591  }
1592  else
1593  gen_remove(&aux_xl, (chunk *) e);
1594  plax = lax;
1595  }
1596 
1597 if(get_debug_level() > 4) {
1598 fprintf(stderr, "[partition_unknowns] xl of crt proto (again):");
1599 fprint_entity_list(stderr, aux_xl);
1600 fprintf(stderr, "\n");
1601 fprintf(stderr, "[partition_unknowns] Remaining xl:");
1602 fprint_entity_list(stderr, rem_xl);
1603 fprintf(stderr, "\n");
1604 
1605 fprintf(stderr, "[partition_unknowns] Crt unks (addition): ");
1606 for(xul = xunks; !ENDP(xul); POP(xul)) {
1607  fprintf(stderr, "(");
1608  fprint_entity_list(stderr, CONSP(CAR(xul)));
1609  fprintf(stderr, ") ");
1610 }
1611 fprintf(stderr, "\n");
1612 }
1613 
1614  if(!ENDP(rem_xl)) {
1615  for(cl = aux_xl; !ENDP(cl); cl = CDR(cl)) {
1616  entity e = ENTITY(CAR(cl));
1617  if(in_list_p((chunk *) e, rem_xl)) {
1618  if(ENDP(plax)) {
1619  xunks = CONS(CONSP, CONS(ENTITY, e, NIL), NIL);
1620  plax = xunks;
1621  }
1622  else {
1623  CDR(plax) = CONS(CONSP, CONS(ENTITY, e, NIL), NIL);
1624  plax = CDR(plax);
1625  }
1626  gen_remove(&rem_xl, (chunk *) e);
1627  }
1628  }
1629 
1630 if(get_debug_level() > 4) {
1631 fprintf(stderr, "[partition_unknowns] Remaining xl (again):");
1632 fprint_entity_list(stderr, rem_xl);
1633 fprintf(stderr, "\n");
1634 
1635 fprintf(stderr, "[partition_unknowns] Crt unks (appendition): ");
1636 for(xul = xunks; !ENDP(xul); POP(xul)) {
1637  fprintf(stderr, "(");
1638  fprint_entity_list(stderr, CONSP(CAR(xul)));
1639  fprintf(stderr, ") ");
1640 }
1641 fprintf(stderr, "\n");
1642 }
1643 
1644  }
1645  }
1646  }
1647  return(xunks);
1648 }
1649 
1650 
1651 /* ======================================================================== */
1652 /*
1653  * Psysteme system_inversion_restrict(Psysteme sys, list unks_l var_l par_l,
1654  * int nb_restrict, bool is_first):
1655  *
1656  * sys -> B.e, unks_l -> l, ps_res -> l.B^(-1), var_l -> e :
1657  *
1658  * a = B.e
1659  * m.a = l.e
1660  * =>
1661  * m = l.B^(-1)
1662  */
1663 Psysteme system_inversion_restrict(sys, unks_l, var_l, par_l, nb_restrict, is_first)
1664 Psysteme sys;
1665 list unks_l, var_l, par_l;
1666 int nb_restrict;
1667 bool is_first;
1668 {
1669  Psysteme full_ps;
1670  Pcontrainte new_pc;
1671  int n, m1, m2, r, d, i, j;
1672  matrice A, B, inv_A, Bz, R, Rt;
1673 
1674  full_ps = completer_base(sys, var_l, par_l);
1675  n = full_ps->nb_eq;
1676  m1 = gen_length(var_l);
1677  m2 = gen_length(par_l) + 1;
1678 
1679  A = matrice_new(n,n);
1680  B = matrice_new(n,m2);
1682  list_to_base(par_l),A,B,n,n,m2);
1683 
1684  inv_A = matrice_new(n,n);
1685  matrice_general_inversion(A, inv_A, n);
1686 
1687  if(is_first) {
1688  r = nb_restrict;
1689  d = 0;
1690  }
1691  else {
1692  r = n - nb_restrict;
1693  d = nb_restrict;
1694  }
1695 
1696  R = matrice_new(n, r);
1697  for(i = 1; i <= n; i++)
1698  for(j = 1; j <= r; j++)
1699  ACCESS(R, n, i, j) = ACCESS(inv_A, n, i, j+d);
1700  R[0] = 1;
1701 
1702  Rt = matrice_new(r, n);
1703  matrice_transpose(R, Rt, n, r);
1704 
1705  Bz = matrice_new(r, 1);
1706  matrice_nulle(Bz, r, 1);
1707 
1708  pu_matrices_to_contraintes(&new_pc, list_to_base(unks_l), Rt, Bz, r, n);
1709 
1710  matrice_free(A);
1711  matrice_free(B);
1712  matrice_free(inv_A);
1713  matrice_free(Bz);
1714  matrice_free(R);
1715  matrice_free(Rt);
1716 
1717  return(sc_make(new_pc, NULL));
1718 }
1719 
1720 
1721 /* ======================================================================== */
1723 Psysteme sys;
1724 list *sigma;
1725 {
1726  bool result = true;
1727  list sig = *sigma, sigma_p;
1728  Pcontrainte leg;
1729  Pvecteur new_v;
1730 
1731  /* We walk through all the equations of M_ps. */
1732  for(leg = sys->egalites; leg != NULL; leg = leg->succ) {
1733  if(get_debug_level() > 3) {
1734  fprintf(stderr, "[solve_system_by_succ_elim] \tCrt equation:");
1735  pu_egalite_fprint(stderr, leg, pu_variable_name);
1736  fprintf(stderr, "\n");
1737  }
1738 
1739  /* We apply on this expression the substitution "sigma" */
1740  new_v = vvs_on_vecteur(sig, leg->vecteur);
1741  if(get_debug_level() > 1) {
1742  fprintf(stderr, "[solve_system_by_succ_elim] \t\tEqu after apply crt subs:");
1743  pu_vect_fprint(stderr, new_v);
1744  fprintf(stderr, "\n");
1745  }
1746 
1747  /* We create the elementary substitution with a variable not yet
1748  * eliminated.
1749  */
1750  sigma_p = plc_make_vvs_with_vector(new_v);
1751  if(get_debug_level() > 4) {
1752  fprintf(stderr, "[solve_system_by_succ_elim] \t\tSubs of non elim var:\n");
1753  fprint_vvs(stderr, sigma_p);
1754  fprintf(stderr, "\n");
1755  }
1756 
1757  if(sigma_p == NIL) {
1758  /*result = true;*/
1759  }
1760  /* We apply it on all prototypes, if none becomes trivial ... */
1761  else if(is_not_trivial_p(sigma_p)) {
1762 
1763  if(get_debug_level() > 3) {
1764  fprintf(stderr, "[solve_system_by_succ_elim] \tCrt local subs :\n");
1765  fprint_vvs(stderr, sigma_p);
1766  fprintf(stderr, "\n");
1767  }
1768 
1769  sig = compose_vvs(sigma_p, sig);
1770  /*result = true;*/
1771  }
1772  else
1773  result = false;
1774  }
1775  *sigma = sig;
1776 
1777  return(result);
1778 }
1779 
1780 
1781 /* ========================================================================= */
1782 /*
1783  * bool constant_vecteur_p(Pvecteur pv)
1784  */
1786 Pvecteur pv;
1787 {
1788  if(pv == NULL)
1789  return(true);
1790  else
1791  return( (pv->succ == NULL) && (pv->var == TCST) );
1792 }
1793 
1794 
1795 /* ========================================================================= */
1796 /* Psysteme broadcast_dimensions(placement pla, list mu_list)
1797  *
1798  */
1800 placement pla;
1801 list mu_list;
1802 {
1803  list plc_dims, mu_l;
1804  Psysteme ps_bp;
1805 
1806  ps_bp = SC_EMPTY;
1807  mu_l = mu_list;
1808  plc_dims = placement_dims(pla);
1809  if(plc_dims != NIL) {
1810  ps_bp = sc_new();
1811 
1812  for(; !ENDP(plc_dims); POP(plc_dims), POP(mu_l)) {
1813  Ppolynome crt_pp = (Ppolynome) CHUNK(CAR(plc_dims));
1814  Pvecteur pv;
1815  Variable crt_mu;
1816 
1817  crt_mu = (Variable) ENTITY(CAR(mu_l));
1818  pv = prototype_factorize(crt_pp, crt_mu);
1819  if(!constant_vecteur_p(pv))
1820  sc_add_egalite(ps_bp, contrainte_make(pv));
1821  }
1822  }
1823  return(ps_bp);
1824 }
1825 
1826 
1827 /* ======================================================================== */
1828 /*
1829  * Psysteme completer_n_base(Psysteme sys dims_sys, list var_l par_l, int dim)
1830  *
1831  * idem as completer_base(), except that we add dimensions from dims_sys
1832  * until "sys" has "dim" vectors.
1833  */
1834 Psysteme completer_n_base(sys, dims_sys, var_l, par_l, dim)
1835 Psysteme sys, dims_sys;
1836 list var_l, par_l;
1837 int dim;
1838 {
1839  Psysteme ps = sc_dup(sys), new_ps = sc_new();
1840  Pcontrainte pc;
1841  int crt_dim = sys->nb_eq;
1842  Pbase var_b, par_b;
1843 
1844  var_b = list_to_base(var_l);
1845  par_b = list_to_base(par_l);
1846 
1847  if(dim < crt_dim)
1848  pips_internal_error("There should not be so much dims");
1849  else if(dim == crt_dim)
1850  return(ps);
1851 
1852  for(pc = dims_sys->egalites; crt_dim < dim; pc = pc->succ) {
1853  Pvecteur pv = pc->vecteur;
1854  Psysteme aux_ps = sc_dup(ps);
1855  Psysteme aux_new_ps = sc_dup(new_ps);
1856 
1857  sc_add_egalite(aux_new_ps, contrainte_make(pv));
1858  aux_ps = append_eg(aux_ps, aux_new_ps);
1859 
1860  if(vecteurs_libres_p(aux_ps, var_b, par_b)) {
1861  new_ps = aux_new_ps;
1862  crt_dim++;
1863  }
1864  else
1865  sc_rm(aux_ps);
1866  }
1867  ps = append_eg(ps, new_ps);
1868  ps->base = NULL;
1869  sc_creer_base(ps);
1870  return(ps);
1871 }
1872 
1873 
1874 /* ========================================================================= */
1875 /*
1876  * void pm_matrice_scalar_mult(int scal, matrice mat_M, int m n)
1877  */
1878 void pm_matrice_scalar_mult(scal, mat_M, m, n)
1879 int scal, m, n;
1880 matrice mat_M;
1881 {
1882  int i, j;
1883  for(i = 1; i <= m; i++) {
1884  for(j = 1; j <= n; j++) {
1885  ACCESS(mat_M, m, i, j) = scal * ACCESS(mat_M, m, i, j);
1886  }
1887  }
1888 }
1889 
1890 
1891 /* ========================================================================= */
1892 /*
1893  * list partial_broadcast_coefficients(list var_l, list *used_mu)
1894  *
1895  * Takes into account the partial broadcast prototypes (contain in "pfunc") to
1896  * replace some of the coefficients in "var_l" by the "mu" coefficients
1897  * (used by these broadcast prototypes). The returned value the substitution
1898  * resulting of this computation. "used_mu" should be empty at the beginning
1899  * and is equal to the list of the mu coeff actually used.
1900  *
1901  * This computation is done on each statemwent.
1902  *
1903  * For a given statemwent s, we have to get the corresponding placement
1904  * object sp of the list contained in "pfunc" (a global variable). The
1905  * broadcast prototypes are contained in the field dims.
1906  * If this list is empty, we do not have anything to do. Else, this list
1907  * contained at most sd prototypes (sd is the dimension of the distribution
1908  * space for s). Each prototype has been associated to a Mu coefficient.
1909  * First, we have to construct the dimension not filled (if any). After this,
1910  * we will have sd prototypes as:
1911  * for i in {1,...,sd}, bp_i = mu_i.eps_i
1912  * When summed:
1913  * bp = J.M, where J is a row vector of broadcast directions and M is a
1914  * column vector of Mu coefficients.
1915  * These broadcast directions may be expressed with respect to the indices:
1916  * J = I.P, where I is a row vector of indices and P is a 2-D matrice.
1917  *
1918  * Prototype of s may be represented as:
1919  * pp = I.A.L + S.B.L + C.L + I.D + S.E + c, where S is a row vector of
1920  * parameters, A and B are 2-D integer matrices, L is a column vector of
1921  * coefficients (those of "var_l"), C, D and E are integer column vectors
1922  * and c is an integer scalar.
1923  *
1924  * So, we have:
1925  * I.A.L + I.D = J.M = I.P.M
1926  * i.e.:
1927  * A.L + D = P.M
1928  *
1929  * So we have to construct the following system of equation:
1930  * A.L + D - P.M == 0
1931  * From this system, we can express some of coefficients of L with respect to
1932  * the others (of L and M).
1933  *
1934  *
1935  */
1937 list var_l;
1938 list *used_mu;
1939 {
1940  extern plc pfunc;
1941 
1942  list plcs, new_vvs = NIL, uml = NIL;
1943 
1944  for(plcs = plc_placements(pfunc); !ENDP(plcs); POP(plcs)){
1945  placement crt_pla = PLACEMENT(CAR(plcs));
1946  list crt_dims = placement_dims(crt_pla);
1947  int crt_stmt = placement_statement(crt_pla);
1948 
1949 if(get_debug_level() > 4) {
1950 fprintf(stderr, "[partial_broadcast_coefficients] for stmt %d, with dims:\n", crt_stmt);
1951 fprint_pla_pp_dims(stderr, crt_pla);
1952 fprintf(stderr, "\n");
1953 }
1954 
1955  if(crt_dims != NIL) {
1956  list mu_list, ind_l, par_l, vl, il, init_l, elim_l, vvs_L;
1957  Psysteme ps_bp, ps_pp_dims, new_ps, elim_ps;
1958  static_control stct;
1959  int i,j, sd, n, m, l;
1960  Pcontrainte new_pc;
1961  Ppolynome pp;
1962  matrice mat_Q, mat_Qc, mat_P, mat_Pc, mat_A;
1963 
1964  mu_list = (list) hash_get(StmtToMu, (char *) crt_stmt);
1965  uml = gen_append(mu_list, uml);
1967  ind_l = static_control_to_indices(stct);
1968  par_l = gen_append(prgm_parameter_l, NIL);
1969  sd = (int) hash_get(StmtToPdim, (char *) crt_stmt);
1970  pp = (Ppolynome) hash_get(StmtToProto, (char *) crt_stmt);
1971 
1972  /* Construction of the directions that might be generated by the
1973  * prototype.
1974  */
1975  ps_pp_dims = sc_new();
1976  for(vl = var_l; !ENDP(vl); POP(vl)) {
1977  entity crt_var = ENTITY(CAR(vl));
1978  Pvecteur pv = prototype_factorize(pp, (Variable) crt_var);
1979  if(!VECTEUR_NUL_P(pv)) {
1980  Psysteme aux_ps = sc_new();
1981  sc_add_egalite(aux_ps, contrainte_make(pv));
1982  sc_creer_base(aux_ps);
1983  ps_pp_dims = append_eg(ps_pp_dims, aux_ps);
1984  }
1985  }
1986 
1987 if(get_debug_level() > 4) {
1988 fprintf(stderr, "[partial_broadcast_coefficients] Prototype dir:\n");
1989 fprint_psysteme(stderr, ps_pp_dims);
1990 fprintf(stderr, "\n");
1991 }
1992 
1993  /* Construction of -P.M */
1994  ps_bp = broadcast_dimensions(crt_pla, mu_list);
1995 
1996 if(get_debug_level() > 4) {
1997 fprintf(stderr, "[partial_broadcast_coefficients] Broadcast dir:\n");
1998 fprint_psysteme(stderr, ps_bp);
1999 fprintf(stderr, "\n");
2000 }
2001 
2002  ps_bp = completer_n_base(ps_bp, ps_pp_dims, ind_l, par_l, sd);
2003 
2004 if(get_debug_level() > 4) {
2005 fprintf(stderr, "[partial_broadcast_coefficients] FULL Broadcast dir:\n");
2006 fprint_psysteme(stderr, ps_bp);
2007 fprintf(stderr, "\n");
2008 }
2009 
2010  n = sd;
2011  m = gen_length(ind_l);
2012  mat_Q = matrice_new(n, m);
2013  mat_Qc = matrice_new(n, 1);
2015  mat_Q, mat_Qc, n, m);
2016  mat_P = matrice_new(m, n);
2017  mat_Pc = matrice_new(m, 1);
2018  matrice_nulle(mat_Pc, m, 1);
2019  matrice_transpose(mat_Q, mat_P, n, m);
2020  pm_matrice_scalar_mult(-1, mat_P, m, n);
2021 
2022 if(get_debug_level() > 4) {
2023 fprintf(stderr, "[partial_broadcast_coefficients] Matrix -P:\n");
2024 matrice_fprint(stderr, mat_P, m, n);
2025 fprintf(stderr, "\n");
2026 }
2027 
2028  /* Construction of A.L + D */
2029  l = gen_length(var_l)+1;
2030  mat_A = matrice_new(m, l);
2031  for(il = ind_l, i=1; !ENDP(il); POP(il), i++) {
2032  entity crt_ind = ENTITY(CAR(il));
2033  Pvecteur pv = prototype_factorize(pp, (Variable) crt_ind);
2034 
2035  for(vl = var_l, j=1; !ENDP(vl); POP(vl), j++) {
2036  entity crt_v = ENTITY(CAR(vl));
2037  ACCESS(mat_A,m,i,j) = vect_coeff((Variable) crt_v, pv);
2038  }
2039  ACCESS(mat_A,m,i,l) = vect_coeff(TCST, pv);
2040  }
2041  DENOMINATOR(mat_A) = 1;
2042 
2043 if(get_debug_level() > 4) {
2044 fprintf(stderr, "[partial_broadcast_coefficients] Matrix A|D:\n");
2045 matrice_fprint(stderr, mat_A, m, l);
2046 fprintf(stderr, "\n");
2047 }
2048 
2049  /* A.L + D - P.M */
2051  list_to_base(var_l), mat_P, mat_A,
2052  m, n, l);
2053 
2054  matrice_free(mat_Q);
2055  matrice_free(mat_Qc);
2056  matrice_free(mat_P);
2057  matrice_free(mat_Pc);
2058  matrice_free(mat_A);
2059 
2060  new_ps = sc_make(new_pc, NULL);
2061 
2062 if(get_debug_level() > 4) {
2063 fprintf(stderr, "[partial_broadcast_coefficients] A.L + D - P.M:\n");
2064 fprint_psysteme(stderr, new_ps);
2065 fprintf(stderr, "\t Var to eliminate : ");
2066 fprint_entity_list(stderr, var_l);
2067 fprintf(stderr, "\n");
2068 }
2069 
2070  init_l = gen_append(var_l, NIL);
2071  elim_l= NIL;
2072  elim_ps = elim_var_with_eg(new_ps, &init_l, &elim_l);
2073 
2074 if(get_debug_level() > 4) {
2075 fprintf(stderr, "[partial_broadcast_coefficients] After ELIM LAMBDAs\n");
2076 fprintf(stderr, "\tElim Coeff and System: ");
2077 fprint_entity_list(stderr, elim_l);
2078 fprint_psysteme(stderr, elim_ps);
2079 fprintf(stderr, "\tRemaining Coeff and System : ");
2080 fprint_entity_list(stderr, init_l);
2081 fprint_psysteme(stderr, new_ps);
2082 fprintf(stderr, "\n");
2083 }
2084 
2085  vvs_L = make_vvs_from_sc(elim_ps, elim_l);
2086 
2087 if(get_debug_level() > 4) {
2088 fprintf(stderr, "[partial_broadcast_coefficients] Sub for elim lambdas:\n");
2089 fprint_vvs(stderr, vvs_L);
2090 fprintf(stderr, "\n");
2091 }
2092 
2093  if(new_ps->nb_eq != 0) {
2094  Psysteme elim_ps2;
2095  list elim_l2, init_l2;
2096  list vvs_M;
2097 
2098  init_l2 = gen_append(mu_list, NIL);
2099  elim_l2 = NIL;
2100  elim_ps2 = elim_var_with_eg(new_ps, &init_l2, &elim_l2);
2101 
2102 if(get_debug_level() > 4) {
2103 fprintf(stderr, "[partial_broadcast_coefficients] After ELIM MUs\n");
2104 fprintf(stderr, "\tElim Coeff and System: ");
2105 fprint_entity_list(stderr, elim_l2);
2106 fprint_psysteme(stderr, elim_ps2);
2107 fprintf(stderr, "\tRemaining Coeff and System : ");
2108 fprint_entity_list(stderr, init_l2);
2109 fprint_psysteme(stderr, new_ps);
2110 fprintf(stderr, "\n");
2111 }
2112 
2113  vvs_M = make_vvs_from_sc(elim_ps2, elim_l2);
2114 
2115 if(get_debug_level() > 4) {
2116 fprintf(stderr, "[partial_broadcast_coefficients] Sub for elim mus:\n");
2117 fprint_vvs(stderr, vvs_M);
2118 fprintf(stderr, "\n");
2119 }
2120 
2121  vvs_L = compose_vvs(vvs_L, vvs_M);
2122 
2123 if(get_debug_level() > 4) {
2124 fprintf(stderr, "[partial_broadcast_coefficients] Sub for MUs and LAMBDAs:\n");
2125 fprint_vvs(stderr, vvs_L);
2126 fprintf(stderr, "\n");
2127 }
2128  }
2129  new_vvs = compose_vvs(new_vvs, vvs_L);
2130 
2131 if(get_debug_level() > 4) {
2132 fprintf(stderr, "[partial_broadcast_coefficients] Crt sub:\n");
2133 fprint_vvs(stderr, new_vvs);
2134 fprintf(stderr, "\n");
2135 }
2136  }
2137  }
2138  *used_mu = uml;
2139  return(new_vvs);
2140 }
2141 
2142 
2143 /* ======================================================================== */
2145 entity e;
2146 {
2147  return(strncmp(entity_local_name(e), MU_COEFF, 4) == 0);
2148 }
2149 
2150 
2151 /* ========================================================================= */
2152 /*
2153  * list get_mu_coeff(list sigma)
2154  */
2156 list sigma;
2157 {
2158  list mu_list = NIL, vl;
2159 
2160  for(vl = sigma; !ENDP(vl); POP(vl)) {
2161  var_val vv = VAR_VAL(CAR(vl));
2162  entity c = var_val_variable(vv);
2163 
2164  if(is_mu_coeff_p(c))
2165  mu_list = CONS(ENTITY, c, mu_list);
2166  }
2167  return(mu_list);
2168 }
2169 
2170 
2171 /* ========================================================================= */
2172 /*
2173  * void vvs_on_prototypes(list sigma)
2174  */
2176 list sigma;
2177 {
2178  extern hash_table StmtToProto;
2179  extern graph the_dfg;
2180 
2181  list vl;
2182 
2183  for(vl = graph_vertices(the_dfg); vl != NIL; vl = CDR(vl)) {
2184  vertex v = VERTEX(CAR(vl));
2185  int stmt = vertex_int_stmt(v);
2186  Ppolynome pp = (Ppolynome) hash_get(StmtToProto, (char *) stmt);
2187 
2188  (void) hash_del(StmtToProto, (char *) stmt);
2189  hash_put(StmtToProto, (char *) stmt, (char *) vvs_on_polynome(sigma, pp));
2190  }
2191 }
2192 
2193 
2194 /* ========================================================================= */
2195 /*
2196  * void prgm_mapping((char*) module_name):
2197  *
2198  * It computes the placement function for all statement (i.e. nodes of "g").
2199  * This computation is done in three steps: initialization, edges treatment,
2200  * valuation.
2201  *
2202  * 1. The initialization consists in creating a prototype of placement
2203  * function for each statement (cf. plc_make_proto()), in computing the
2204  * placement function dimension and in computing the weight of the edges.
2205  *
2206  * 2. The edges treatment consists in determining some of the coefficients
2207  * of the prototypes using first the broadcast conditions and second the
2208  * distance conditions.
2209  *
2210  * 3. The valuation consists in determining the coefficients not yet
2211  * valuated and in building the dimensions of the placement function.
2212  */
2214 char* module_name;
2215 {
2216  extern plc pfunc; /* The placement function */
2217  extern bdt the_bdt; /* The timing function */
2218  extern graph the_dfg;
2219  extern int nb_nodes, /* The number of nodes in the DFG */
2220  nb_dfs; /* The number of dataflows in the DFG */
2221 
2222  extern hash_table DtfToDist; /* Mapping from a dataflow to its distance */
2223  extern hash_table StmtToProto;/* Mapping from a statement to its prototype */
2224  extern hash_table DtfToSink;
2225  extern hash_table DtfToWgh;
2226 
2227  extern list prgm_parameter_l;
2228 
2229  struct tms chrono1, chrono2; /* Perf.mesurement */
2231 
2232  /* List of the unknowns coefficients */
2233  list lambda, xmu_lambda, mu_lambda, mu,
2234  sigma, sigma1, sigma2, sigma_p, *sigma3,
2235  su_l,
2236  sorted_df_l, l, remnants_df_l, df_l;
2237  Psysteme M_ps;
2238  int dmax, i;
2239  entity ent;
2240  static_control stco;
2242  char *md;
2243 
2244  /* Initialize debugging functions */
2245  debug_on("MAPPING_DEBUG_LEVEL");
2246  if(get_debug_level() > 0)
2247  fprintf(stderr, "\n\n *** COMPUTE MAPPING for %s\n", module_name);
2248 
2249  if(get_debug_level() > 1) {
2250  times(&chrono1);
2251  }
2252 
2253  /* We get the required data: module entity, code, static_control, dataflow
2254  * graph, timing function.
2255  */
2257 
2259 
2261  STS = (statement_mapping) db_get_memory_resource(DBR_STATIC_CONTROL,
2262  module_name, true);
2264  if ( stco == static_control_undefined) {
2265  pips_internal_error("This is an undefined static control !");
2266  }
2267  if ( !static_control_yes( stco )) {
2268  pips_internal_error("This is not a static control program !");
2269  }
2270 
2272 
2274 
2275  if(get_debug_level() > 2) {
2276  fprintf(stderr, "[prgm_mapping] Structure parameters of the program: ");
2278  fprintf(stderr, "\n");
2279  }
2280 
2281  /* The DFG */
2283 
2284  /* the BDT */
2286  the_bdt = (bdt) db_get_memory_resource(DBR_BDT, module_name, true);
2287 
2288  if(get_debug_level() > 2) {
2289  fprint_dfg(stderr, the_dfg);
2290  }
2291  if(get_debug_level() > 0) {
2292  fprint_bdt(stderr, the_bdt);
2293  }
2294  /* First we count the number of nodes and dataflows */
2295  nb_nodes = 0;
2296  nb_dfs = 0;
2297  for(l = graph_vertices(the_dfg); !ENDP(l); POP(l)) {
2298  nb_nodes++;
2299  for(su_l = vertex_successors(VERTEX(CAR(l))); !ENDP(su_l); POP(su_l)) {
2300  for(df_l = SUCC_DATAFLOWS(SUCCESSOR(CAR(su_l))); df_l != NIL; df_l = CDR(df_l)) {
2301  nb_dfs++;
2302  }
2303  }
2304  }
2305 
2306  /* We look for the broadcasts */
2307  broadcast(the_dfg);
2308 
2309  /* We sort the nodes of "the_dfg" in decreasing dimension order. The
2310  * dimension of a node is the dimension of the iteration space of its
2311  * instruction.
2312  */
2314 
2315  if(get_debug_level() > 2)
2316 {
2317  fprintf(stderr, "[prgm_mapping] Nodes order:");
2318  for(l = graph_vertices(the_dfg); ! ENDP(l); POP(l))
2319  fprintf(stderr, " %d,", vertex_int_stmt(VERTEX(CAR(l))));
2320  fprintf(stderr, "\n");
2321  }
2322 
2323 /* INITIALIZATION */
2324  /* We create a prototype for each statement. Each prototype is mapped to
2325  * its statement in the hash table "StmtToProto". An other hash table
2326  * "StmtToProto" associates the unknown coefficients used in the
2327  * prototype and the statement. The returned value "lambda" gives all
2328  * the coefficients that have been created.
2329  */
2330  lambda = plc_make_proto();
2331 
2332  if(get_debug_level() > 2)
2333 {
2334  fprintf(stderr, "[prgm_mapping] Nodes prototypes:\n");
2336  fprintf(stderr, "[prgm_mapping] LAMBDAS: ");
2337  fprint_entity_list(stderr, lambda);
2338  fprintf(stderr, "\n");
2339  }
2340 
2341  /* plc_make_dim() has to initialize the Mu list*/
2342 
2343  /* We compute the dimension of the placement function of each instruction,
2344  * and the greatest one (dmax). This is based on the timing function, if it
2345  * exists.
2346  */
2347  count_mu_coeff = 1;
2348  dmax = plc_make_dim();
2349 
2350  /* The number of mapping dimensions can be computed as a minimum, see
2351  * plc_make_min_dim() */
2352  i = ((md = getenv("MINIMUM_DIMENSION")) != NULL) ? 1 : 0;
2353  if(i == 1) {
2354  int dmin;
2355 
2356  dmin = plc_make_min_dim();
2357 
2358  user_warning("prgm_mapping",
2359  "Minimum number of dimensions: %d instead of %d\n",
2360  dmin, dmax);
2361 
2362  dmax = dmin;
2363  }
2364 
2365  /* Mapping dimension can be fixed with the environment variable
2366  * MAPPING_DIMENSION */
2367  i = ((md = getenv("MAPPING_DIMENSION")) != NULL) ? atoi(md) : dmax;
2368  if(i != dmax) {
2369  user_warning("prgm_mapping",
2370  "environment variable MAPPING_DIMENSION has set the mapping dimension to %d instead of %d\n",
2371  i, dmax);
2372 
2373  dmax = i;
2374  }
2375 
2376  /* We initialize the prgm_mapping function. */
2377  pfunc = make_plc(NIL);
2378  for(l = graph_vertices(the_dfg); l != NIL; l = CDR(l)) {
2379  placement new_func;
2380  vertex v = VERTEX(CAR(l));
2381  int stmt = vertex_int_stmt(v);
2382 
2383  new_func = make_placement(stmt, NIL);
2385  CONS(PLACEMENT, new_func, NIL));
2386  }
2387 
2388  debug(3, "prgm_mapping", "DIM des fonctions de placement : %d\n", dmax);
2389  if(dmax == 0) {
2390  for(l = plc_placements(pfunc); !ENDP(l); POP(l)) {
2391  placement crt_func = PLACEMENT(CAR(l));
2392  placement_dims(crt_func) = CONS(EXPRESSION,
2393  int_to_expression(0),
2394  NIL);
2395  }
2396 
2400  debug_off();
2401  return(true);
2402  }
2403 
2404  /* Computation of the weight of each dataflow of the DFG. */
2405  edge_weight();
2406 
2407  /* We get all the dataflows of the graph */
2408  df_l = get_graph_dataflows(the_dfg);
2409  if(get_debug_level() > 5) {
2410  fprintf(stderr, "[prgm_mapping] Edges UNorder:\n");
2411  plc_fprint_dfs(stderr, df_l, DtfToSink, DtfToWgh);
2412  }
2413 
2414  /* We sort the dataflows in decreasing weight order */
2415  sorted_df_l = general_merge_sort(df_l, compare_dfs_weight);
2416  if(get_debug_level() > 2)
2417  {
2418  fprintf(stderr, "[prgm_mapping] Edges order:\n");
2419  plc_fprint_dfs(stderr, sorted_df_l, DtfToSink, DtfToWgh);
2420  }
2421 
2422 
2423 /* EDGES TREATMENT */
2424 
2425 /* BROADCAST CONDITIONS */
2426  /* We take into account the broadcast conditions */
2427  sigma = NIL;
2428  remnants_df_l = broadcast_conditions(lambda, sorted_df_l, &sigma);
2429  if(get_debug_level() > 2)
2430  {
2431  fprintf(stderr, "[prgm_mapping] Dif Red restriction:\n");
2432  fprint_vvs(stderr, sigma);
2433  fprintf(stderr, "[prgm_mapping] Remnants :\n");
2434  plc_fprint_dfs(stderr, remnants_df_l, DtfToSink, DtfToWgh);
2435  }
2436 
2437  for(sigma_p = sigma; !ENDP(sigma_p); POP(sigma_p))
2438  gen_remove(&lambda, (chunk *) var_val_variable(VAR_VAL(CAR(sigma_p))));
2439 
2440  if(get_debug_level() > 2)
2441  {
2442  fprintf(stderr, "[prgm_mapping] Prototypes after broadcast conditions:\n");
2444  fprintf(stderr, "\n");
2445  }
2446 
2447  mu = NIL;
2448  sigma1 = partial_broadcast_coefficients(lambda, &mu);
2449 
2450  if(get_debug_level() > 3)
2451 {
2452 fprintf(stderr, "[prgm_mapping] ******* Partial broadcast sub:");
2453 fprint_vvs(stderr, sigma1);
2454 fprintf(stderr, "\n");
2455 }
2456 
2457  vvs_on_prototypes(sigma1);
2458 
2459  if(get_debug_level() > 2)
2460 {
2461  fprintf(stderr, "[prgm_mapping] Prototypes after partial broadcast sub:\n");
2463  fprintf(stderr, "\n");
2464 }
2465 
2466  for(sigma_p = sigma1; !ENDP(sigma_p); POP(sigma_p)) {
2467  entity e = var_val_variable(VAR_VAL(CAR(sigma_p)));
2468  gen_remove(&lambda, (chunk *) e);
2469  gen_remove(&mu, (chunk *) e);
2470  }
2471 
2472 if(get_debug_level() > 3) {
2473 fprintf(stderr, "[prgm_mapping] ******* Remaining lambdas and Mus:\n");
2474 fprintf(stderr, "\t LAMBDAs:");
2475 fprint_entity_list(stderr, lambda);
2476 fprintf(stderr, "\n");
2477 fprintf(stderr, "\t MUs:");
2478 fprint_entity_list(stderr, mu);
2479 fprintf(stderr, "\n");
2480 }
2481 
2482 /*MOD : we could give "remnants_df_l" as an arg, in order to only compute the
2483 useful distances. */
2484 
2485 /* DISTANCE COMPUTATION */
2486  /* Computation of the distance of each dataflow. */
2488  if(get_debug_level() > 2) {
2489  fprintf(stderr, "[prgm_mapping] Edges distances:\n");
2491  }
2492 
2493 /* CUTTING CONDITIONS */
2494  /* We compute the list of equations that are to be nullified in order to zero
2495  * out all the distances.
2496  */
2497  M_ps = cutting_conditions(remnants_df_l);
2498  if(get_debug_level() > 2)
2499 {
2500  fprintf(stderr, "[prgm_mapping] Matrix M:\n");
2501  fprint_psysteme(stderr, M_ps);
2502  }
2503 
2504  sigma2 = NIL;
2505  (void) solve_system_by_succ_elim(M_ps, &sigma2);
2506 
2507  if(get_debug_level() > 2)
2508 {
2509  fprintf(stderr, "Crt subs:\n");
2510  fprint_vvs(stderr, sigma2);
2511  }
2512 
2513 if(get_debug_level() > 0) {
2514  fprintf(stderr, "[prgm_mapping] Prototypes after distance conditions:\n");
2516  fprintf(stderr, "\n");
2517 }
2518 
2519  /* We eliminate all the unknowns that are valuated by the substitution
2520  * computed above "sigma"; and then we cut it in two parts, one
2521  * containing the indices coefficients, one containing the parameters
2522  * coefficients, both sorted by decreasing frenquency in the
2523  * prototypes. Before cutting the list "lambda" into two parts, we take
2524  * into account the partial broadcast prototypes (contain in "pfunc") to
2525  * replace some of the "lambda" coeff by the "mu" coeff. The new sigma
2526  * is returned by this function. */
2527 
2528  for(sigma_p = sigma2; !ENDP(sigma_p); POP(sigma_p)) {
2529  entity e = var_val_variable(VAR_VAL(CAR(sigma_p)));
2530  gen_remove(&lambda, (chunk *) e);
2531  gen_remove(&mu, (chunk *) e);
2532  }
2533 
2534 if(get_debug_level() > 3) {
2535 fprintf(stderr, "[prgm_mapping] ******* Remaining lambdas:");
2536 fprint_entity_list(stderr, lambda);
2537 fprintf(stderr, "\n");
2538 fprintf(stderr, "[prgm_mapping] ******* Remaining mus:");
2539 fprint_entity_list(stderr, mu);
2540 fprintf(stderr, "\n");
2541 }
2542 
2543  /* UNELIMINATED COEFF SORTING */
2544  sort_unknowns(&lambda, dmax);
2545  sort_unknowns(&mu, dmax);
2546 
2547 if(get_debug_level() > 3) {
2548 fprintf(stderr, "[prgm_mapping] ******* Sorted lambdas:");
2549 fprint_entity_list(stderr, lambda);
2550 fprintf(stderr, "\n");
2551 fprintf(stderr, "[prgm_mapping] ******* Sorted mus:");
2552 fprint_entity_list(stderr, mu);
2553 fprintf(stderr, "\n");
2554 }
2555 
2556  /* COEFF PARTITION */
2557  mu_lambda = gen_nconc(mu, lambda);
2558  xmu_lambda = partition_unknowns(&mu_lambda, dmax);
2559 
2560  if(get_debug_level() > 2)
2561  {
2562  fprintf(stderr, "[prgm_mapping] \nRemaining unknowns\n");
2563  fprintf(stderr, "\tX COEFF: ");
2564  for(l = xmu_lambda; !ENDP(l); POP(l)) {
2565  fprintf(stderr, "(");
2566  fprint_entity_list(stderr, CONSP(CAR(l)));
2567  fprintf(stderr, ") ");
2568  }
2569  fprintf(stderr, "\tPC COEFF: ");
2570  fprint_entity_list(stderr, mu_lambda);
2571  fprintf(stderr, "\n");
2572 
2573 fprint_plc_pp_dims(stderr, pfunc);
2574 }
2575 
2576 /* VALUATION */
2577  /* We valuate all the remaining unknowns by building successively each
2578  * dimension.
2579  */
2580  sigma3 = (list *) malloc(sizeof(list)*dmax);
2581  for(i = 0; i < dmax; i++) {
2582  list plcs;
2583 
2584  sigma3[i] = valuer(i, xmu_lambda, mu_lambda);
2585 
2586  if(get_debug_level() > 2)
2587  {
2588  fprintf(stderr, "[prgm_mapping] Plc dim %d, new subs is\n", i);
2589  fprint_vvs(stderr, sigma3[i]);
2590  fprintf(stderr, "\n");
2591  }
2592 
2593  for(l = graph_vertices(the_dfg), plcs = plc_placements(pfunc); l != NIL;
2594  l = CDR(l), POP(plcs)) {
2595  placement crt_func = PLACEMENT(CAR(plcs));
2596  list dims;
2597  vertex v = VERTEX(CAR(l));
2598  int stmt = vertex_int_stmt(v);
2599 
2601  (char *) stmt));
2602  Ppolynome sub_pp = vvs_on_polynome(sigma3[i], pp);
2603  Pvecteur sub_vect = polynome_to_vecteur(sub_pp);
2605 
2606  if(i == 0)
2607  dims = NIL;
2608  else
2609  dims = placement_dims(crt_func);
2610 
2611  if(exp == expression_undefined)
2612  exp = int_to_expression(0);
2613 
2614  placement_dims(crt_func) = gen_nconc(dims, CONS(EXPRESSION, exp, NIL));
2615  }
2616  }
2617 
2618  if(get_debug_level() > 0) {
2619  fprintf(stderr, "\n RESULT OF MAPPING:\n**************\n");
2620  df_l = get_graph_dataflows(the_dfg);
2621  for(i = 0; i < dmax; i++) {
2622  fprintf(stderr,
2623  "Distance for dim %d\n=================================\n", i);
2624 
2625  for(l = df_l; !ENDP(l); POP(l)) {
2626  dataflow df = DATAFLOW(CAR(l));
2627  int stmt = (int) hash_get(DtfToSink, (char *) df);
2629  (char *) df));
2630 
2631  pp_dist = vvs_on_polynome(sigma, pp_dist);
2632  pp_dist = vvs_on_polynome(sigma1, pp_dist);
2633  pp_dist = vvs_on_polynome(sigma2, pp_dist);
2634  pp_dist = vvs_on_polynome(sigma3[i], pp_dist);
2635 
2636  fprintf(stderr, "Dataflow ");
2637  fprint_dataflow(stderr, stmt, df);
2638  fprintf(stderr, "\tDist = ");
2640  fprintf(stderr, "\n");
2641  }
2642  }
2643  }
2644 
2645  if(get_debug_level() > 1) {
2646  times(&chrono2);
2647 
2648  fprintf(stderr,
2649  "\n*******\nTIMING:\n*******\n\tuser : %ld, system : %ld \n",
2650  (long) chrono2.tms_utime - chrono1.tms_utime,
2651  (long) chrono2.tms_stime - chrono1.tms_stime );
2652  }
2653 
2654  if(get_debug_level() > 0) {
2655  fprintf(stderr, "\n MAPPING:\n**************\n");
2656  fprint_plc(stderr, pfunc);
2657  fprintf(stderr, "\n\n *** MAPPING done\n");
2658  }
2659 
2661 
2664 
2665  debug_off();
2666 
2667  return(true);
2668 }
void user_log(const char *format,...)
Definition: message.c:234
plc make_plc(list a)
Definition: paf_ri.c:432
placement make_placement(intptr_t a1, list a2)
Definition: paf_ri.c:390
graph adg_pure_dfg(graph in_gr)
======================================================================
Definition: adg_graph.c:56
void fprint_dfg(FILE *fp, graph obj)
===========================================================================
static int sink_stmt
Current source node.
Definition: adg_read_paf.c:160
static list trans_l
Current list of nodes.
Definition: adg_read_paf.c:168
static int source_stmt
Current sink statement.
Definition: adg_read_paf.c:161
static int crt_stmt
Current source statement.
Definition: adg_read_paf.c:162
static hash_table STS
The "STS" global variable is the hash table that maps the static_control on the statements.
Definition: adg_read_paf.c:155
static predicate gov_pred
Current expression.
Definition: adg_read_paf.c:165
statement adg_number_to_statement(int in_nb)
======================================================================
Definition: adg_utils.c:461
void const char const char const int
int Value
void broadcast(graph g)
========================================================================
Definition: broadcast.c:87
list broadcast_conditions(list lambda, list df_l, list *sigma)
========================================================================
Definition: broadcast.c:728
struct _newgen_struct_statement_ * statement
Definition: cloning.h:21
#define A(i, j)
comp_matrice.c
Definition: comp_matrice.c:63
Pcontrainte contrainte_make(Pvecteur pv)
Pcontrainte contrainte_make(Pvecteur pv): allocation et initialisation d'une contrainte avec un vecte...
Definition: alloc.c:73
Pcontrainte contrainte_dup(Pcontrainte c_in)
Pcontrainte contrainte_dup(Pcontrainte c_in): allocation d'une contrainte c_out prenant la valeur de ...
Definition: alloc.c:132
static Value offset
Definition: translation.c:283
const char * module_name(const char *s)
Return the module part of an entity name.
Definition: entity_names.c:296
FILE * safe_fopen(const char *filename, const char *what)
Definition: file.c:67
int safe_fclose(FILE *stream, const char *filename)
Definition: file.c:77
#define CHUNK(x)
Definition: genC.h:90
#define CONSP(x)
Definition: genC.h:88
void * malloc(YYSIZE_T)
void free(void *)
#define successor_vertex(x)
Definition: graph.h:118
#define successor_arc_label(x)
Definition: graph.h:116
#define vertex_vertex_label(x)
Definition: graph.h:152
#define vertex_successors(x)
Definition: graph.h:154
#define SUCCESSOR(x)
SUCCESSOR.
Definition: graph.h:86
#define graph_vertices(x)
Definition: graph.h:82
#define VERTEX(x)
VERTEX.
Definition: graph.h:122
void reset_current_module_entity(void)
Reset the current module entity.
Definition: static.c:97
entity set_current_module_entity(entity)
static.c
Definition: static.c:66
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
void gen_remove(list *cpp, const void *o)
remove all occurences of item o from list *cpp, which is thus modified.
Definition: list.c:685
#define POP(l)
Modify a list pointer to point on the next element of the list.
Definition: newgen_list.h:59
#define NIL
The empty list (nil in Lisp)
Definition: newgen_list.h:47
list gen_concatenate(const list l1x, const list l2x)
concatenate two lists.
Definition: list.c:436
size_t gen_length(const list l)
Definition: list.c:150
#define CONS(_t_, _i_, _l_)
List element cell constructor (insert an element at the beginning of a list)
Definition: newgen_list.h:150
list gen_nconc(list cp1, list cp2)
physically concatenates CP1 and CP2 but do not duplicates the elements
Definition: list.c:344
#define CAR(pcons)
Get the value of the first element of a list.
Definition: newgen_list.h:92
#define CDR(pcons)
Get the list less its first element.
Definition: newgen_list.h:111
list gen_append(list l1, const list l2)
Definition: list.c:471
string db_get_memory_resource(const char *rname, const char *oname, bool pure)
Return the pointer to the resource, whatever it is.
Definition: database.c:755
#define DB_PUT_MEMORY_RESOURCE(res_name, own_name, res_val)
conform to old interface.
Definition: pipsdbm-local.h:66
#define DB_PUT_FILE_RESOURCE
Put a file resource into the current workspace database.
Definition: pipsdbm-local.h:85
hash_table hash_table_make(hash_key_type key_type, size_t size)
Definition: hash.c:294
void * hash_get(const hash_table htp, const void *key)
this function retrieves in the hash table pointed to by htp the couple whose key is equal to key.
Definition: hash.c:449
void hash_put(hash_table htp, const void *key, const void *val)
This functions stores a couple (key,val) in the hash table pointed to by htp.
Definition: hash.c:364
void hash_table_free(hash_table htp)
this function deletes a hash table that is no longer useful.
Definition: hash.c:327
void * hash_del(hash_table htp, const void *key)
this function removes from the hash table pointed to by htp the couple whose key is equal to key.
Definition: hash.c:439
bool expression_constant_p(expression)
HPFC module by Fabien COELHO.
Definition: expression.c:2453
void fprint_entity_list(FILE *fp, list l)
void fprint_entity_list(FILE *fp,list l): prints a list of entities on file fp.
Definition: entity.c:3188
list base_to_list(Pbase base)
Most includes are centralized here.
#define B(A)
Definition: iabrev.h:61
static statement mod_stat
We want to keep track of the current statement inside the recurse.
Definition: impact_check.c:41
int vect_size(Pvecteur v)
package vecteur - reductions
Definition: reductions.c:47
#define DENOMINATOR(matrix)
int DENOMINATEUR(matrix): acces au denominateur global d'une matrice matrix La combinaison *(&()) est...
Definition: matrice-local.h:93
#define matrice_free(m)
Definition: matrice-local.h:78
#define ACCESS(matrix, column, i, j)
Macros d'acces aux elements d'une matrice.
Definition: matrice-local.h:86
#define matrice_new(n, m)
Allocation et desallocation d'une matrice.
Definition: matrice-local.h:77
Value * matrice
package matrice
Definition: matrice-local.h:71
int dim_H(matrice H, int n, int m)
Calcul de la dimension de la matrice de Hermite H.
Definition: hermite.c:197
void matrice_hermite(Value *MAT, int n, int m, Value *P, Value *H, Value *Q, Value *det_p, Value *det_q)
package matrice
Definition: hermite.c:78
void matrice_general_inversion(matrice a, matrice inv_a, int n)
void matrice_general_inversion(matrice a; matrice inv_a; int n) calcul de l'inversion du matrice gene...
Definition: inversion.c:222
void matrice_transpose(matrice a, matrice a_t, int n, int m)
package matrice
Definition: matrice.c:48
void matrice_nulle(matrice Z, int n, int m)
void matrice_nulle(matrice Z, int n, int m): Initialisation de la matrice Z a la valeur matrice nulle
Definition: matrice.c:311
void matrice_fprint(FILE *, matrice, int, int)
matrice_io.c
Definition: matrice_io.c:62
#define debug_on(env)
Definition: misc-local.h:157
#define pips_assert(what, predicate)
common macros, two flavors depending on NDEBUG
Definition: misc-local.h:172
#define pips_internal_error
Definition: misc-local.h:149
#define debug_off()
Definition: misc-local.h:160
#define user_error(fn,...)
Definition: misc-local.h:265
#define user_warning(fn,...)
Definition: misc-local.h:262
int get_debug_level(void)
GET_DEBUG_LEVEL returns the current debugging level.
Definition: debug.c:67
void debug(const int the_expected_debug_level, const char *calling_function_name, const char *a_message_format,...)
ARARGS0.
Definition: debug.c:189
Pbase list_to_base(list l)
Pbase list_to_base(list l): returns the Pbase that contains the variables of list "l",...
#define GET_STATEMENT_MAPPING(map, stat)
Definition: newgen-local.h:49
hash_table statement_mapping
these macros are obsolete! newgen functions (->) should be used instead
Definition: newgen-local.h:42
string concatenate(const char *,...)
Return the concatenation of the given strings.
Definition: string.c:183
@ hash_int
Definition: newgen_hash.h:32
@ hash_pointer
Definition: newgen_hash.h:32
struct cons * list
Definition: newgen_types.h:106
const char * pu_variable_name(Variable)
package mapping : Alexis Platonoff, april 1993
Definition: print.c:421
list general_merge_sort(list, bool(*)(void))
void matrices_to_contraintes_with_sym_cst(Pcontrainte *, Pbase, Pbase, matrice, matrice, int, int, int)
Definition: utils.c:503
Psysteme make_expression_equalities(list)
===========================================================================
Definition: utils.c:931
int vertex_int_stmt(vertex)
===========================================================================
Definition: utils.c:866
Psysteme elim_var_with_eg(Psysteme, list *, list *)
===========================================================================
Definition: utils.c:1361
Pvecteur prototype_factorize(Ppolynome, Variable)
========================================================================
Definition: utils.c:2070
void contraintes_with_sym_cst_to_matrices(Pcontrainte, Pbase, Pbase, matrice, matrice, int, int, int)
Creation de la matrice A correspondant au systeme lineaire et de la matrice correspondant a la partie...
Definition: utils.c:446
void pu_vect_fprint(FILE *, Pvecteur)
===========================================================================
Definition: print.c:446
list static_control_to_indices(static_control)
package mapping : Alexis Platonoff, july 1993
Definition: utils.c:1037
Psysteme find_implicit_equation(Psysteme)
========================================================================
Definition: utils.c:2350
Pvecteur polynome_to_vecteur(Ppolynome)
========================================================================
Definition: utils.c:1063
void reset_current_stco_map(void)
========================================================================
Definition: utils.c:2423
static_control get_stco_from_current_map(statement)
========================================================================
Definition: utils.c:2429
void imprime_quast(FILE *, quast)
===========================================================================
Definition: print.c:514
bool pu_is_inferior_var(Variable, Variable)
void pu_egalite_fprint(FILE *, Pcontrainte, const char *(*)(entity))
void fprint_psysteme(FILE *, Psysteme)
===========================================================================
Definition: print.c:302
Ppolynome prototype_var_subst(Ppolynome, Variable, Ppolynome)
=================================================================
Definition: utils.c:1978
void set_current_stco_map(statement_mapping)
========================================================================
Definition: utils.c:2408
void pu_contraintes_to_matrices(Pcontrainte, Pbase, matrice, matrice, int, int)
===========================================================================
Definition: utils.c:408
void fprint_bdt(FILE *, bdt)
===========================================================================
Definition: print.c:352
void fprint_dataflow(FILE *, int, dataflow)
===========================================================================
Definition: print.c:229
void pu_matrices_to_contraintes(Pcontrainte *, Pbase, matrice, matrice, int, int)
utils.c
Definition: utils.c:350
#define var_val_value(x)
Definition: paf_ri.h:795
#define plc_placements(x)
Definition: paf_ri.h:557
#define var_val_variable(x)
Definition: paf_ri.h:793
#define DATAFLOW(x)
DATAFLOW.
Definition: paf_ri.h:308
#define dataflow_transformation(x)
Definition: paf_ri.h:342
#define quast_undefined
Definition: paf_ri.h:603
#define quast_value_undefined
Definition: paf_ri.h:639
struct _newgen_struct_static_control_ * static_control
Definition: paf_ri.h:184
struct _newgen_struct_bdt_ * bdt
Definition: paf_ri.h:72
#define placement_dims(x)
Definition: paf_ri.h:525
#define SCHEDULE(x)
SCHEDULE.
Definition: paf_ri.h:682
@ is_quast_value_quast_leaf
Definition: paf_ri.h:654
@ is_quast_value_conditional
Definition: paf_ri.h:655
#define dfg_arc_label_dataflows(x)
Definition: paf_ri.h:378
#define static_control_params(x)
Definition: paf_ri.h:755
#define static_control_yes(x)
Definition: paf_ri.h:753
#define PLACEMENT(x)
PLACEMENT.
Definition: paf_ri.h:493
#define quast_leaf_solution(x)
Definition: paf_ri.h:591
#define quast_value_tag(x)
Definition: paf_ri.h:672
#define static_control_undefined
Definition: paf_ri.h:727
#define dataflow_governing_pred(x)
Definition: paf_ri.h:344
struct _newgen_struct_plc_ * plc
Definition: paf_ri.h:144
#define bdt_schedules(x)
Definition: paf_ri.h:226
#define dfg_vertex_label_statement(x)
Definition: paf_ri.h:413
#define schedule_dims(x)
Definition: paf_ri.h:717
#define VAR_VAL(x)
VAR_VAL.
Definition: paf_ri.h:763
#define schedule_statement(x)
Definition: paf_ri.h:713
#define quast_value_quast_leaf(x)
Definition: paf_ri.h:675
#define quast_quast_value(x)
Definition: paf_ri.h:627
#define placement_statement(x)
Definition: paf_ri.h:523
#define bdt_undefined
Definition: paf_ri.h:204
quast pip_integer_min(Psysteme ps_dep, Psysteme ps_context, Pvecteur pv_unknowns)
==================================================================
Definition: pip.c:628
string db_get_current_workspace_directory(void)
Definition: workspace.c:96
Ppolynome make_polynome(float coeff, Variable var, Value expo)
Ppolynome make_polynome(float coeff, Variable var, Value expo) PRIVATE allocates space for,...
Definition: pnome-alloc.c:100
Ppolynome polynome_dup(Ppolynome pp)
Ppolynome polynome_dup(Ppolynome pp) creates and returns a copy of pp.
Definition: pnome-alloc.c:211
void polynome_rm(Ppolynome *ppp)
void polynome_rm(Ppolynome* ppp) frees space occupied by polynomial *ppp returns *ppp pointing to POL...
Definition: pnome-alloc.c:170
Ppolynome polynome_free(Ppolynome pp)
Ppolynome polynome_free(Ppolynome pp) frees space occupied by polynomial pp returns pp == POLYNOME_NU...
Definition: pnome-alloc.c:191
Ppolynome vecteur_to_polynome(Pvecteur pv)
===========================================================================
Definition: pnome-bin.c:406
Ppolynome polynome_mult(Ppolynome pp1, Ppolynome pp2)
Ppolynome polynome_mult(Ppolynome pp1, Ppolynome pp2) returns pp1 * pp2.
Definition: pnome-bin.c:287
void polynome_add(Ppolynome *ppp, Ppolynome pp2)
void polynome_add(Ppolynome* ppp, Ppolynome pp2) (*ppp) = (*ppp) + pp2.
Definition: pnome-bin.c:171
void polynome_fprint(FILE *fd, Ppolynome pp, char *(*variable_name)(Variable), int *is_inferior_var)
void polynome_fprint(FILE* fd, Ppolynome pp, char* (*variable_name)(), bool (*is_inferior_var)()) Out...
Definition: pnome-io.c:173
void polynome_negate(Ppolynome *ppp)
void polynome_negate(Ppolynome *ppp); changes sign of polynomial *ppp.
Definition: pnome-unaires.c:45
#define POLYNOME_NUL
struct Spolynome * Ppolynome
string expression_to_string(expression e)
Definition: expression.c:77
#define SUCC_DATAFLOWS(s)
#define AUXIL_COEFF
#define MU_COEFF
#define VERTEX_DOMAIN(v)
#define INDEX_COEFF
#define PARAM_COEFF
#define CONST_COEFF
void fprint_plc(FILE *fp, plc obj)
========================================================================
Definition: print.c:85
void plc_fprint_dfs(FILE *fp, list df_l, hash_table DtfToStmt, hash_table DtfToWgh)
========================================================================
Definition: print.c:181
void fprint_pla_pp_dims(FILE *fp, placement one_placement)
========================================================================
Definition: print.c:204
void plc_fprint_distance(FILE *fp, graph g, hash_table DtfToDist)
========================================================================
Definition: print.c:143
void plc_fprint_proto(FILE *fp, graph g, hash_table StmtToProto)
========================================================================
Definition: print.c:118
void fprint_plc_pp_dims(FILE *fp, plc one_plc)
========================================================================
Definition: print.c:228
Ppolynome apply_farkas(Ppolynome F, Psysteme D, list *L, int *count_lambdas)
Definition: utils.c:669
bool is_broadcast_p(dataflow df)
========================================================================
Definition: utils.c:1088
bool compare_dfs_weight(chunk *d1, chunk *d2)
========================================================================
Definition: utils.c:181
int count_implicit_equation(Psysteme ps)
========================================================================
Definition: utils.c:562
entity find_or_create_coeff(string prefix, int n)
========================================================================
Definition: utils.c:238
int communication_dim(dataflow df)
========================================================================
Definition: utils.c:1116
bool is_index_coeff_p(entity e)
========================================================================
Definition: utils.c:144
list get_graph_dataflows(graph g)
========================================================================
Definition: utils.c:765
bool is_reduction_p(dataflow df)
========================================================================
Definition: utils.c:1150
Psysteme completer_base(Psysteme sys, list var_l, list par_l)
========================================================================
Definition: utils.c:832
bool vecteurs_libres_p(Psysteme sys, Pbase v_base, Pbase c_base)
========================================================================
Definition: utils.c:903
bool compare_nodes_dim(chunk *n1, chunk *n2)
========================================================================
Definition: utils.c:170
Psysteme append_eg(Psysteme M1, Psysteme M2)
========================================================================
Definition: utils.c:946
entity make_coeff(string prefix, int n)
========================================================================
Definition: utils.c:209
Psysteme nullify_factors(Ppolynome *pp, list var_l, bool with_remnants)
========================================================================
Definition: utils.c:1026
bool compare_coeff(chunk *c1, chunk *c2)
========================================================================
Definition: utils.c:161
list put_source_ind(list le)
========================================================================
Definition: utils.c:596
bool compare_unks_frenq(chunk *e1, chunk *e2)
========================================================================
Definition: utils.c:192
bool prgm_mapping(char *module_name)
=========================================================================
int plc_make_min_dim()
========================================================================
Definition: prgm_mapping.c:313
hash_table StmtToPdim
Mapping from a statement (int) to its prototype.
Definition: prgm_mapping.c:107
int nb_dfs
The number of nodes in the DFG.
Definition: prgm_mapping.c:102
dfg_arc_label arc_label
Definition: prgm_mapping.c:119
bool in_list_p(chunk *c, list l)
========================================================================
Definition: prgm_mapping.c:917
int plc_make_dim()
========================================================================
Definition: prgm_mapping.c:365
Psysteme completer_n_base(Psysteme sys, Psysteme dims_sys, list var_l, list par_l, int dim)
========================================================================
graph the_dfg
The placement function.
Definition: prgm_mapping.c:99
Psysteme system_inversion_restrict(Psysteme sys, list unks_l, list var_l, list par_l, int nb_restrict, bool is_first)
========================================================================
list valuer(int dim, list xunks, list pcunks)
========================================================================
void sort_unknowns(list *lambda, int dmax)
========================================================================
hash_table DtfToDist
Mapping from a dataflow to its sink statement.
Definition: prgm_mapping.c:104
bool solve_system_by_succ_elim(Psysteme sys, list *sigma)
========================================================================
hash_table DtfToWgh
Mapping from a dataflow to its distance.
Definition: prgm_mapping.c:105
void pm_matrice_scalar_mult(int scal, matrice mat_M, int m, int n)
=========================================================================
bool print_plc(char *module_name) const
========================================================================
Definition: prgm_mapping.c:124
list prgm_parameter_l
global variables
Definition: prgm_mapping.c:115
int nb_nodes
The timing function.
Definition: prgm_mapping.c:101
list sort_dfg_node(list l_nodes)
========================================================================
Definition: prgm_mapping.c:748
list partial_broadcast_coefficients(list var_l, list *used_mu)
=========================================================================
Psysteme broadcast_dimensions(placement pla, list mu_list)
=========================================================================
#define ENT_HT_SIZE
Definition: prgm_mapping.c:93
dfg_vertex_label vertex_label
Local defines.
Definition: prgm_mapping.c:118
void edge_weight()
========================================================================
Definition: prgm_mapping.c:795
bool constant_vecteur_p(Pvecteur pv)
=========================================================================
bool is_mu_coeff_p(entity e)
========================================================================
hash_table DtfToSink
The number of dataflows in the DFG.
Definition: prgm_mapping.c:103
hash_table StmtToProto
Mapping from a dataflow to its weight.
Definition: prgm_mapping.c:106
Psysteme cutting_conditions(list df_l)
========================================================================
Definition: prgm_mapping.c:682
hash_table StmtToBdim
Mapping from a statement to the dim of its plc func.
Definition: prgm_mapping.c:108
list partition_unknowns(list *unks, int dmax)
========================================================================
bool is_not_trivial_p(list vvs)
========================================================================
#define PLC_EXT
Definition: prgm_mapping.c:121
list plc_make_proto()
========================================================================
Definition: prgm_mapping.c:190
list get_mu_coeff(list sigma)
=========================================================================
void add_to_list(chunk *c, list *l)
========================================================================
Definition: prgm_mapping.c:939
void plc_make_distance()
========================================================================
Definition: prgm_mapping.c:453
plc pfunc
Internal variables
Definition: prgm_mapping.c:98
int prototype_dimension(Ppolynome pp, list ind_l)
========================================================================
Definition: prgm_mapping.c:985
void vvs_on_prototypes(list sigma)
=========================================================================
hash_table StmtToMu
Mapping from a stmt to its lambda coeff.
Definition: prgm_mapping.c:111
hash_table StmtToDim
Mapping from a statement to the dim of its bdt.
Definition: prgm_mapping.c:109
list subs_l
Definition: prgm_mapping.c:114
hash_table UnkToFrenq
Mapping from a stmt to its mu coeff.
Definition: prgm_mapping.c:112
hash_table StmtToLamb
Mapping from a stmt to its iteration space dim.
Definition: prgm_mapping.c:110
bdt the_bdt
The data flow graph.
Definition: prgm_mapping.c:100
int count_mu_coeff
Mapping from an entity to its frenq in the plc proto.
Definition: prgm_mapping.c:113
void initialize_mu_list(int stmt, int dim)
========================================================================
Definition: prgm_mapping.c:284
static hash_table pl
properties are stored in this hash table (string -> property) for fast accesses.
Definition: properties.c:783
#define NORMALIZE_EXPRESSION(e)
const char * entity_local_name(entity e)
entity_local_name modified so that it does not core when used in vect_fprint, since someone thought t...
Definition: entity.c:453
entity local_name_to_top_level_entity(const char *n)
This function try to find a top-level entity from a local name.
Definition: entity.c:1450
expression Pvecteur_to_expression(Pvecteur vect)
AP, sep 25th 95 : some usefull functions moved from static_controlize/utils.c.
Definition: expression.c:1825
int expression_to_int(expression exp)
================================================================
Definition: expression.c:2205
expression int_to_expression(_int i)
transform an int into an expression and generate the corresponding entity if necessary; it is not cle...
Definition: expression.c:1188
Ppolynome expression_to_polynome(expression exp)
===========================================================================
Definition: expression.c:3650
#define ENTITY(x)
ENTITY.
Definition: ri.h:2755
#define EXPRESSION(x)
EXPRESSION.
Definition: ri.h:1217
#define entity_undefined
Definition: ri.h:2761
#define expression_undefined
Definition: ri.h:1223
#define predicate_undefined
Definition: ri.h:2046
#define expression_normalized(x)
Definition: ri.h:1249
#define normalized_linear(x)
Definition: ri.h:1781
#define predicate_system(x)
Definition: ri.h:2069
struct Ssysteme * Psysteme
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
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
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
void sc_add_egalite(Psysteme p, Pcontrainte e)
void sc_add_egalite(Psysteme p, Pcontrainte e): macro ajoutant une egalite e a un systeme p; la base ...
Definition: sc_alloc.c:389
Psysteme sc_new(void)
Psysteme sc_new(): alloue un systeme vide, initialise tous les champs avec des valeurs nulles,...
Definition: sc_alloc.c:55
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
Psysteme sc_dup(Psysteme ps)
Psysteme sc_dup(Psysteme ps): should becomes a link.
Definition: sc_alloc.c:176
Psysteme sc_append(Psysteme s1, Psysteme s2)
Psysteme sc_append(Psysteme s1, Psysteme s2): calcul de l'intersection des polyedres definis par s1 e...
Psysteme sc_intersection(Psysteme s1, Psysteme s2, Psysteme s3)
Psysteme sc_intersection(Psysteme s1, Psysteme s2, Psysteme s3): calcul d'un systeme de contraintes s...
int fprintf()
test sc_min : ce test s'appelle par : programme fichier1.data fichier2.data ...
char * strdup()
Psysteme sc_normalize(Psysteme ps)
Psysteme sc_normalize(Psysteme ps): normalisation d'un systeme d'equation et d'inequations lineaires ...
Pvecteur vect_multiply(Pvecteur v, Value x)
Pvecteur vect_multiply(Pvecteur v, Value x): multiplication du vecteur v par le scalaire x,...
Definition: scalaires.c:123
Definition: pip__tab.h:25
Pvecteur vecteur
struct Scontrainte * succ
Pcontrainte egalites
Definition: sc-local.h:70
Pbase base
Definition: sc-local.h:75
int nb_eq
Definition: sc-local.h:72
le type des coefficients dans les vecteurs: Value est defini dans le package arithmetique
Definition: vecteur-local.h:89
The structure used to build lists in NewGen.
Definition: newgen_list.h:41
Definition: statement.c:54
#define exp
Avoid some warnings from "gcc -Wshadow".
Definition: vasnprintf.c:207
#define TCST
VARIABLE REPRESENTANT LE TERME CONSTANT.
#define NO_OFL_CTRL
struct Svecteur * Pvecteur
#define VECTEUR_NUL_P(v)
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 base_dimension(b)
Pvecteur vect_new(Variable var, Value coeff)
Pvecteur vect_new(Variable var,Value coeff): allocation d'un vecteur colineaire au vecteur de base va...
Definition: alloc.c:110
void vect_rm(Pvecteur v)
void vect_rm(Pvecteur v): desallocation des couples de v;
Definition: alloc.c:78
Pvecteur vect_cl2_ofl_ctrl(Value x1, Pvecteur v1, Value x2, Pvecteur v2, int ofl_ctrl)
Pvecteur vect_cl2_ofl(Value x1, Pvecteur v1, Value x2, Pvecteur v2): allocation d'un vecteur v dont l...
Definition: binaires.c:204
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
void fprint_vvs(FILE *fp, list vvs)
========================================================================
Definition: vvs.c:146
list compose_vvs(list vv1, list vv2)
========================================================================
Definition: vvs.c:274
list make_vvs_from_sc(Psysteme ps_aux, list var_l)
========================================================================
Definition: vvs.c:610
list vvs_on_vvs(list vv1, list vv2)
========================================================================
Definition: vvs.c:198
Ppolynome vvs_on_polynome(list vvs, Ppolynome pp)
========================================================================
Definition: vvs.c:465
Psysteme vvs_on_systeme(list vvs, Psysteme ps)
========================================================================
Definition: vvs.c:567
list plc_make_vvs_with_vector(Pvecteur v)
========================================================================
Definition: vvs.c:668
Pvecteur vvs_on_vecteur(list vvs, Pvecteur pv)
========================================================================
Definition: vvs.c:530
list make_vvs(entity var, int coeff, Pvecteur val)
========================================================================
Definition: vvs.c:113