PIPS
array_dfg.c File Reference
#include "local.h"
+ Include dependency graph for array_dfg.c:

Go to the source code of this file.

Macros

#define GRAPH_IS_DFG
 Name : array_dfg.c Package : array_dfg Author : Arnauld LESERVOT Date : 93/06/27 Modified : Documents: Platonoff's thesis and Leservot's thesis "Dataflow Analysis of Array and Scalar References" P. More...
 
#define NEXT(cp)   (((cp) == NIL) ? NIL : (cp)->cdr)
 Local defines. More...
 

Functions

bool my_sc_faisabilite (Psysteme in_ps)
 
graph adg_dataflowgraph (statement mod_stat, statement_mapping stco_map, graph dup_dg)
 ====================================================================== More...
 
boolean array_dfg (char *mod_name)
 ====================================================================== More...
 

Variables

hash_table Gvertex_number_to_statement
 Global variables. More...
 
int Gcount_re
 External variables. More...
 
int Gcount_ie
 
statement_mapping Gstco_map
 
list Gstructural_parameters
 
int my_pip_count
 
int my_fai_count
 
static hash_table Gforward_substitute_table
 

Macro Definition Documentation

◆ GRAPH_IS_DFG

#define GRAPH_IS_DFG

Name : array_dfg.c Package : array_dfg Author : Arnauld LESERVOT Date : 93/06/27 Modified : Documents: Platonoff's thesis and Leservot's thesis "Dataflow Analysis of Array and Scalar References" P.

FEAUTRIER Comments :

Definition at line 37 of file array_dfg.c.

◆ NEXT

#define NEXT (   cp)    (((cp) == NIL) ? NIL : (cp)->cdr)

Local defines.

Definition at line 41 of file array_dfg.c.

Function Documentation

◆ adg_dataflowgraph()

graph adg_dataflowgraph ( statement  mod_stat,
statement_mapping  stco_map,
graph  dup_dg 
)

======================================================================

graph adg_dataflowgraph( (statement) module_statement, (statement_mapping) static_control_map, (graph) reversed_dg ) AL 93/07/01 To compute the Array Data Flow Graph, we need : code, static_control, dependance_graph.

Return dfg graph

Return list of vertices

Initialization to have an entry node

We first put entry node in the return list

We run over each vertex of the input graph

Get destination vertex and information linked to it

We search for all the read effects of vertex dest_ver and try to find the source for each read effect in dest_ver.

For debug purpose

Get the current read_effect of destination

For debug purpose

Search for successors (in fact predecessors : input graph is reversed compared to dg graph !) that write the dest_read_eff and put their vertices in sou_l. Then, order them by decreasing order of stat. number.

No sources : Comes from Entry point

Debugging

Build the source leaf label list sou_lll. This list of leaf labels links a vertex number and a depth.

Explode candidates for each depth and then, build the candidate list cand_l by decreasing order.

we will reuse it after

We run over all possible candidates and compute to see how it could contribute to the source

Get possible source vertex and informations linked to it

If this candidate is not possible, see the next. Two cases : candidate and destination are in the same deepest loop and dest is before candidate ; or candidate is not valid with the present source.

Not a possible source => get the next candidate

will be reuse ?

For debug purpose

Get the f(u) = g(b) psystem We first duplicate arguments expressions, then we rename entities that are at a deeper depth than sou_d and forward subsitute those new entities in the expressions

Rename entities at rank > sou_d and update Gforward_substitute_table

Make corresponding indices equal in source and dest F(u) = g(b) and put it in sou_ps.

Build the sequencing predicate

compute indice1 + indice2 + 1

append at the end p.s. of source to those of dest. Concatenate the three lists to build Psys. according to the order : source-variables,sink-variables,struc.params

Build source Psysteme (IF and DO contraints). Build the context and rename variables .

Get predicate that comes from an IF statement

Get predicate that comes from enclosing DO

Rename entities in the source context system

Append sous_ps (F(u) = g(b) and seq. predicate) with prov_ps (IF and DO constraints).

Compute the new candidate source. We try to call PIP only if necesary.

If there is no condition on source...

Order the psysteme according to ent_l

Find the new source and simplify it

Fill "quast_undefined" part of the source with ENTRY node.

Build the new Data Flow Graph with the new source

Definition at line 70 of file array_dfg.c.

74 {
75  graph ret_graph = graph_undefined; /* Return dfg graph */
76  list ret_verl = NIL; /* Return list of vertices */
77  list dest_ver_l = NIL;
78  vertex entry_v = NULL;
79  quast entry_q = NULL;
80 
81  debug(1, "adg_dataflowgraph", "begin \n");
82 
83  /* Initialization to have an entry node */
84  /* We first put entry node in the return list */
88  ADD_ELEMENT_TO_LIST( ret_verl, VERTEX, entry_v );
91  NIL );
92 
94  ENTRY_ORDER );
95 
96 
97  /* We run over each vertex of the input graph */
98  for(dest_ver_l = graph_vertices( dup_dg );!ENDP(dest_ver_l);POP(dest_ver_l)) {
99  vertex ret_dest_ver = NULL, dest_ver = NULL;
100  list dest_succ = NIL, dest_loops = NIL;
101  list dest_readl = NIL, dest_psl = NIL, dest_lcl = NIL;
102  list dest_args = NIL, prov_l = NIL;
103  predicate dest_pred = NULL;
104  Psysteme dest_test_context = NULL, dest_loop_context = NULL;
105  Psysteme dest_context = NULL;
106  static_control dest_stco;
107  int dest_nb, dest_order;
108  dfg_vertex_label ret_dest_dvl = NULL;
109  statement dest_st = NULL;
110  predicate prov_pr = NULL;
111 
112 
113  /* Get destination vertex and information linked to it */
114  dest_ver = VERTEX(CAR( dest_ver_l ));
115  dest_st = adg_vertex_to_statement(dest_ver);
116  dest_succ = vertex_successors( dest_ver );
118  ((dfg_vertex_label) vertex_vertex_label( dest_ver ));
119  dest_order = adg_number_to_ordering( dest_nb );
120  dest_stco = (static_control) GET_STATEMENT_MAPPING(stco_map, dest_st);
121  dest_loops = static_control_loops( dest_stco );
122  dest_psl = static_control_params( dest_stco );
123  dest_lcl = adg_get_loop_indices( dest_loops );
124 
125  dest_pred = dfg_vertex_label_exec_domain(vertex_vertex_label(dest_ver));
126  if (!predicate_undefined_p(dest_pred))
127  dest_test_context = predicate_system( dest_pred );
128  else dest_test_context = SC_RN;
129 
130  prov_pr = adg_get_predicate_of_loops(dest_loops);
131  if (prov_pr != predicate_undefined)
132  dest_loop_context = predicate_system( prov_pr );
133  else dest_loop_context = SC_RN;
134  dest_context = sc_append(sc_dup( dest_test_context ),dest_loop_context);
135  if (dest_context != SC_UNDEFINED) adg_sc_update_base(&dest_context);
136  if ((dest_context != NULL)&&(!my_sc_faisabilite(dest_context))) continue;
137 
138  ret_dest_ver = adg_same_dfg_vertex_number( ret_verl, dest_nb );
139  ret_dest_dvl = make_dfg_vertex_label( dest_nb,
140  make_predicate( sc_dup(dest_context) ),
142  if (ret_dest_ver == vertex_undefined) {
143  ret_dest_ver = make_vertex( ret_dest_dvl, NIL );
144  ADD_ELEMENT_TO_LIST( ret_verl, VERTEX, ret_dest_ver );
145  }
146  else
147  vertex_vertex_label(ret_dest_ver) = ret_dest_dvl;
148 
149 
150 
151  /* We search for all the read effects of vertex dest_ver
152  * and try to find the source for each read effect in dest_ver.
153  */
154  dest_readl = read_reference_list( dest_ver, dest_lcl, dest_psl );
155  if (get_debug_level() > 3) { /* For debug purpose */
156  fprintf(stderr, "\n========================================\n");
157  fprintf(stderr, "Destination Statement (ordering %d) :\n",dest_order);
159  fprintf(stderr, "Read Effects :\n");
160  print_effects( dest_readl );
161  }
162  for(; !ENDP( dest_readl ); POP( dest_readl )) {
163  effect dest_read_eff = NULL;
164  list sou_l = NULL, sou_lll = NIL;
165  list cand_l = NIL;
166  int max_depth = 0;
167  int prov_i;
168  quast source = quast_undefined;
169 
170  /* Get the current read_effect of destination */
171  dest_read_eff = EFFECT(CAR( dest_readl ));
172  dest_args = reference_indices(effect_any_reference(dest_read_eff));
173  if (get_debug_level() > 3) { /* For debug purpose */
174  fprintf(stderr, "\n\n--> Source of Effect ? ");
175  print_effects( CONS(EFFECT, dest_read_eff, NIL) );
176  }
177 
178 
179  /* Search for successors (in fact predecessors : input
180  * graph is reversed compared to dg graph !) that write
181  * the dest_read_eff and put their vertices in sou_l.
182  * Then, order them by decreasing order of stat. number.
183  */
184  sou_l = adg_write_reference_list( dest_ver, dest_read_eff );
185  if (sou_l == NIL) {
186  /* No sources : Comes from Entry point */
187  adg_fill_with_quast( &source, entry_q );
188 
189  /* Debugging */
190  debug(9,"adg_dataflowgraph","No candidates => Entry Flow\n");
191  if (get_debug_level() > 2) {
192  fprintf(stderr, "\n ------ Final Source ------\n");
193  imprime_special_quast( stderr, source );
194  }
195 
196  adg_update_dfg( source,
197  effect_any_reference( dest_read_eff ),
198  ret_dest_ver,
199  pa_full(),
200  NULL,
201  NULL,
202  dup_dg,
203  &ret_verl );
204 
205  continue;
206  }
207  sou_l = adg_decreasing_stat_order_sort( sou_l );
208 
209 
210  /* Build the source leaf label list sou_lll.
211  * This list of leaf labels links a vertex number and a depth.
212  */
213  for(; !ENDP(sou_l); POP(sou_l)) {
214  vertex v = VERTEX(CAR( sou_l ));
215  int dep = stco_common_loops_of_statements(stco_map,
216  adg_vertex_to_statement( v ), dest_st);
219  ADD_ELEMENT_TO_LIST(sou_lll, LEAF_LABEL, lel);
220  debug(9,"adg_dataflowgraph", "\nPossible source : stat %d at depth %d\n",
222  }
223 
224 
225  /* Explode candidates for each depth and then,
226  * build the candidate list cand_l by decreasing order.
227  */
228  max_depth = 0;
229  for(prov_l = sou_lll; !ENDP(prov_l); POP(prov_l)) {
230  int dep2 = leaf_label_depth(LEAF_LABEL(CAR( prov_l )));
231  if( dep2 > max_depth ) max_depth = dep2;
232  }
233  for(prov_i = max_depth; prov_i >= 0; prov_i-- ) {
234  prov_l = sou_lll;
235  for(; !ENDP(prov_l); POP(prov_l) ) {
236  leaf_label prov_lel = LEAF_LABEL(CAR(prov_l));
237  int dd = leaf_label_depth( prov_lel );
238  int nb = leaf_label_statement( prov_lel );
239  if( prov_i <= dd )
240  ADD_ELEMENT_TO_LIST(cand_l, LEAF_LABEL,make_leaf_label( nb, prov_i ));
241  }
242  }
243  max_depth = 0; /* we will reuse it after */
244 
245 
246  /* We run over all possible candidates
247  * and compute to see how it could contribute to the source
248  */
249  for(; !ENDP( cand_l ); POP(cand_l) ) {
250  vertex sou_v;
251  int sou_order, sou_d;
252  leaf_label sou_lel;
253  predicate sou_pred = NULL;
254  list sou_lcl = NULL, sou_args = NIL;
255  Psysteme sou_ps = SC_RN;
256  statement sou_s;
257  static_control sou_stco;
258  list sou_psl;
259  list sou_loops;
260  list ent_l = NULL, renamed_l = NULL, merged_l = NULL;
261  list prov_l1 = NIL, prov_l2 = NIL;
262  Psysteme prov_ps = SC_RN;
263  Psysteme loc_context = SC_RN;
264  Pvecteur prov_pv = NULL;
265  quast prov_q = NULL, sou_q = NULL;
266  Pposs_source poss = NULL;
267  quast *local_source = NULL;
268  Ppath local_path;
269 
270 
271  /* Get possible source vertex and informations linked to it */
272  sou_lel = LEAF_LABEL(CAR( cand_l ));
273  sou_v = adg_number_to_vertex( dup_dg, leaf_label_statement(sou_lel) );
274  sou_s = adg_vertex_to_statement( sou_v );
275  sou_d = leaf_label_depth( sou_lel );
276  sou_order = statement_ordering( sou_s );
277  sou_stco = (static_control) GET_STATEMENT_MAPPING( stco_map, sou_s );
278  sou_psl = static_control_params( sou_stco );
279  sou_loops = static_control_loops(sou_stco);
280  max_depth = adg_number_of_same_loops(sou_loops, dest_loops );
281  sou_lcl = adg_get_loop_indices( sou_loops );
282 
283 
284  /* If this candidate is not possible, see the next.
285  * Two cases : candidate and destination are in the
286  * same deepest loop and dest is before candidate ;
287  * or candidate is not valid with the present source.
288  */
289  if ((sou_d == max_depth) && adg_is_textualy_after_p(sou_s, dest_st)) continue;
290  poss = adg_path_possible_source(&source, sou_v, sou_d, pa_full(), TAKE_LAST);
291  local_path = (Ppath) poss->pat;
292  /* Not a possible source => get the next candidate */
293  if (pa_empty_p( local_path )) continue;
294 
295  if PA_UNDEFINED_P(local_path) prov_ps = SC_UNDEFINED;
296  else prov_ps = local_path->psys;
297  local_source = (quast*) (poss->qua);
298  loc_context = sc_append(sc_dup(prov_ps), dest_context);
299  prov_ps = SC_UNDEFINED; /* will be reuse ? */
300 
301  /* For debug purpose */
302  if (get_debug_level() > 3) {
303  fprintf(stderr, "\nPossible Source Statement (ordering %d) ",sou_order);
304  fprintf(stderr, "at depth %d :\n", sou_d);
305  print_statement( sou_s );
306  }
307 
308 
309  /* Get the f(u) = g(b) psystem
310  * We first duplicate arguments expressions,
311  * then we rename entities that are at
312  * a deeper depth than sou_d and forward
313  * subsitute those new entities in the
314  * expressions
315  */
318  statement_instruction(sou_s) )))) )));
319  if(gen_length(sou_args) != gen_length(dest_args)) {
320  pips_internal_error("No coherence between the source array and destination array !");
321  }
322 
323 
324  /* Rename entities at rank > sou_d
325  * and update Gforward_substitute_table
326  */
327  for(prov_i=0; prov_i < sou_d; prov_i++) POP(sou_lcl);
329  renamed_l = adg_rename_entities(sou_lcl, Gforward_substitute_table);
330 
331 
332  /* Make corresponding indices equal in source and dest
333  * F(u) = g(b) and put it in sou_ps.
334  */
335  prov_l1 = dest_args;
336  for(prov_l2=sou_args;!ENDP(prov_l2);POP(prov_l2)){
337  expression sou_e = NULL, dest_e = NULL;
338  Pvecteur pvec = NULL;
339  Psysteme pss = NULL;
340 
341  dest_e = EXPRESSION(CAR(prov_l1));
342  POP( prov_l1 );
343  sou_e = copy_expression( EXPRESSION(CAR(prov_l2)));
345 
346  pvec = vect_substract(EXPRESSION_PVECTEUR(sou_e),
347  EXPRESSION_PVECTEUR(dest_e));
348  if (pvec != NULL) {
350  sou_ps = sc_append(sou_ps, sc_dup(pss));
351  }
352  }
353 
354 
355  /* Build the sequencing predicate */
356  if ( (sou_d >= 0) && (sou_d < max_depth) ) {
357  entity indice1 = ENTITY( gen_nth(sou_d,dest_lcl) );
358  entity indice2 = ENTITY( gen_nth(sou_d,dest_lcl) );
359 
360  if (renamed_l != NIL) indice1 = ENTITY(CAR(renamed_l));
361  /* compute indice1 + indice2 + 1 */
362  prov_pv = vect_add( vect_new(TCST, VALUE_ONE),
364  vect_new((Variable) indice2, VALUE_ONE)) );
365  sou_ps = sc_append(sou_ps,
367  }
368 
369  /* append at the end p.s. of source to those of dest.
370  * Concatenate the three lists to build Psys.
371  * according to the order :
372  * source-variables,sink-variables,struc.params
373  */
374  merged_l = adg_merge_entities_lists(dest_psl,sou_psl);
375  ent_l = gen_append( renamed_l, gen_append( dest_lcl, merged_l ) );
376 
377 
378 
379  /* Build source Psysteme (IF and DO contraints).
380  * Build the context and rename variables .
381  */
382  /* Get predicate that comes from an IF statement */
383  sou_pred = dfg_vertex_label_exec_domain(
384  vertex_vertex_label( sou_v ));
385  if (sou_pred != predicate_undefined) prov_ps = adg_sc_dup(predicate_system(sou_pred));
386  /* Get predicate that comes from enclosing DO */
387  prov_pr = adg_get_predicate_of_loops( sou_loops );
388  if (prov_pr != predicate_undefined) {
389  prov_ps = sc_append( prov_ps, predicate_system( prov_pr ) );
390  }
391  /* Rename entities in the source context system */
392  HASH_MAP( k, v, {
393  char* vval = (char *) reference_variable(
395  sc_variable_rename(prov_ps, (Variable) k, (Variable) vval);
398 
399 
400  /* Append sous_ps (F(u) = g(b) and seq. predicate)
401  * with prov_ps (IF and DO constraints).
402  */
403  sou_ps = adg_suppress_2nd_in_1st_ps( sc_append(sou_ps, prov_ps), loc_context);
404  if ((sou_ps != NULL) && !my_sc_faisabilite( sou_ps )) continue;
405 
406  /* Compute the new candidate source.
407  * We try to call PIP only if necesary.
408  */
409  if (get_debug_level() > 4) {
410  fprintf(stderr, "\nSource Psysteme :\n");
411  fprint_psysteme(stderr, sou_ps);
412  if (sou_ps != SC_UNDEFINED) pu_vect_fprint(stderr, sou_ps->base);
413 
414  fprintf(stderr, "\nContext Psysteme :\n");
415  fprint_psysteme(stderr, loc_context);
416  if (loc_context != SC_RN) pu_vect_fprint(stderr,loc_context->base);
417  }
418  /* If there is no condition on source...*/
419  if (sou_ps == SC_UNDEFINED) {
422  }
423  else if (gen_length(renamed_l) == 0) {
424  prov_ps = sc_append( sc_dup(sou_ps), loc_context );
425  if( (prov_ps == NULL) || my_sc_faisabilite(prov_ps)) {
430  prov_q, quast_undefined)
431  ), NIL );
432  }
433  else sou_q = quast_undefined;
434  }
435  else {
436  Pvecteur pv_unknowns;
437 
438  /* Order the psysteme according to ent_l */
439  sort_psysteme( sou_ps, adg_list_to_vect(ent_l, true) );
440  pv_unknowns = list_to_base(renamed_l);
441  sou_q = pip_integer_max(sou_ps, loc_context, pv_unknowns);
442  my_pip_count++;
443  if (get_debug_level() > 4) imprime_special_quast( stderr, sou_q );
444  sou_q = adg_compact_quast( sou_q );
445  }
446  adg_enrichir( sou_q, sou_lel );
447  if (get_debug_level() > 4) {
448  fprintf(stderr, "\nPresent source quast :\n");
449  imprime_special_quast( stderr, sou_q );
450  }
451 
452 
453  /* Find the new source and simplify it */
454  adg_path_max_source(local_source, &sou_q, local_path, dest_psl, TAKE_LAST );
455 
456  if (get_debug_level() > 4) {
457  fprintf(stderr, "\n Updated Source :\n");
458  imprime_special_quast( stderr, source );
459  }
460  }
461 
462 
463  /* Fill "quast_undefined" part of the source
464  * with ENTRY node.
465  */
466  adg_fill_with_quast( &source, entry_q );
467 
468 
469  /* Build the new Data Flow Graph with the new source*/
470  if (get_debug_level() > 2) {
471  fprintf(stderr, "\n ------ Final Source ------\n");
472  imprime_special_quast( stderr, source );
473  }
474 
475  adg_update_dfg( source,
476  effect_any_reference( dest_read_eff ),
477  ret_dest_ver,
478  pa_full(),
479  dest_context,
480  dest_test_context,
481  dup_dg,
482  &ret_verl );
483  }
484  }
485 
486  ret_graph = make_graph( ret_verl );
487  debug(1, "adg_dataflowgraph", "end \n");
488  return( ret_graph );
489 
490 }
graph make_graph(list a)
Definition: graph.c:56
vertex make_vertex(vertex_label a1, list a2)
Definition: graph.c:140
leaf_label make_leaf_label(intptr_t a1, intptr_t a2)
Definition: paf_ri.c:306
quast_value make_quast_value(enum quast_value_utype tag, void *val)
Definition: paf_ri.c:565
quast make_quast(quast_value a1, list a2)
Definition: paf_ri.c:516
conditional make_conditional(predicate a1, quast a2, quast a3)
Definition: paf_ri.c:138
quast_leaf make_quast_leaf(list a1, leaf_label a2)
Definition: paf_ri.c:474
dfg_vertex_label make_dfg_vertex_label(intptr_t a1, predicate a2, sccflags a3)
Definition: paf_ri.c:264
predicate make_predicate(Psysteme a1)
Definition: ri.c:1820
expression copy_expression(expression p)
EXPRESSION.
Definition: ri.c:850
list adg_write_reference_list(vertex ver, effect reff)
======================================================================
Definition: adg_graph.c:688
int adg_number_to_ordering(int in_nb)
======================================================================
Definition: adg_graph.c:227
statement adg_vertex_to_statement(vertex in_ver)
======================================================================
Definition: adg_graph.c:266
vertex adg_number_to_vertex(graph in_dfg, int in_nb)
======================================================================
Definition: adg_graph.c:239
list read_reference_list(vertex ver, list ent_l1, list ent_l2)
======================================================================
Definition: adg_graph.c:748
void adg_update_dfg(quast in_sou, reference in_ref, vertex in_dest, Ppath in_pa, Psysteme in_context, Psysteme in_test, graph in_gr, list *in_lp)
======================================================================
Definition: adg_graph.c:386
vertex adg_same_dfg_vertex_number(list in_l, int in_i)
======================================================================
Definition: adg_graph.c:358
predicate adg_get_predicate_of_loops(list loops)
======================================================================
Definition: adg_predicate.c:55
void imprime_special_quast(FILE *fp, quast qu)
===========================================================================
list adg_merge_entities_lists(list l1, list l2)
======================================================================
Definition: adg_utils.c:1093
statement adg_number_to_statement(int in_nb)
======================================================================
Definition: adg_utils.c:461
quast adg_path_max_source(quast *tsou, quast *tsou2, Ppath in_pa, list psl, boolean take_last)
======================================================================
Definition: adg_utils.c:726
quast adg_compact_quast(quast in_q)
======================================================================
Definition: adg_utils.c:129
Pvecteur adg_list_to_vect(list in_list, bool with_tcst)
======================================================================
Definition: adg_utils.c:865
void adg_fill_with_quast(quast *in_pq, quast in_q)
======================================================================
Definition: adg_utils.c:52
int adg_number_of_same_loops(list in_l1, list in_l2)
======================================================================
Definition: adg_utils.c:438
void adg_sc_update_base(Psysteme *in_pps)
======================================================================
Definition: adg_utils.c:384
list adg_decreasing_stat_order_sort(list in_list)
======================================================================
Definition: adg_utils.c:1028
bool adg_is_textualy_after_p(statement in_s1, statement in_s2)
======================================================================
Definition: adg_utils.c:373
Psysteme adg_sc_dup(Psysteme in_ps)
======================================================================
Definition: adg_utils.c:331
Pposs_source adg_path_possible_source(quast *in_tsou, vertex in_ver, int in_dep, Ppath in_pa, bool take_last)
======================================================================
Definition: adg_utils.c:929
list adg_get_loop_indices(list ll)
======================================================================
Definition: adg_utils.c:1186
void adg_enrichir(quast in_qu, leaf_label in_ll)
======================================================================
Definition: adg_utils.c:474
list adg_rename_entities(list le, hash_table fst)
======================================================================
Definition: adg_utils.c:1125
Psysteme adg_suppress_2nd_in_1st_ps(Psysteme in_ps1, Psysteme in_ps2)
======================================================================
Definition: adg_utils.c:403
#define VALUE_ONE
#define EXPRESSION_PVECTEUR(e)
#define ENTRY_ORDER
#define TAKE_LAST
bool my_sc_faisabilite(Psysteme in_ps)
Definition: array_dfg.c:55
hash_table Gvertex_number_to_statement
Global variables.
Definition: adg_graph.c:42
static hash_table Gforward_substitute_table
Definition: array_dfg.c:53
int my_pip_count
Definition: array_dfg.c:50
#define CONTRAINTE_UNDEFINED
Pcontrainte contrainte_make(Pvecteur pv)
Pcontrainte contrainte_make(Pvecteur pv): allocation et initialisation d'une contrainte avec un vecte...
Definition: alloc.c:73
#define sccflags_undefined
Definition: dg.h:247
#define effect_any_reference(e)
FI: cannot be used as a left hand side.
#define EFFECT(x)
EFFECT.
Definition: effects.h:608
if(!(yy_init))
Definition: genread_lex.c:1029
#define vertex_undefined
Definition: graph.h:128
#define vertex_vertex_label(x)
Definition: graph.h:152
#define vertex_successors(x)
Definition: graph.h:154
#define graph_vertices(x)
Definition: graph.h:82
#define graph_undefined
Definition: graph.h:60
#define VERTEX(x)
VERTEX.
Definition: graph.h:122
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
#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
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
#define CAR(pcons)
Get the value of the first element of a list.
Definition: newgen_list.h:92
list gen_append(list l1, const list l2)
Definition: list.c:471
gen_chunk gen_nth(int n, const list l)
to be used as ENTITY(gen_nth(3, l))...
Definition: list.c:710
hash_table hash_table_make(hash_key_type key_type, size_t size)
Definition: hash.c:294
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
#define ADD_ELEMENT_TO_LIST(_list, _type, _element)
Definition: icfg-local.h:50
#define pips_internal_error
Definition: misc-local.h:149
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
#define HASH_MAP(k, v, code, ht)
Definition: newgen_hash.h:60
@ hash_pointer
Definition: newgen_hash.h:32
int stco_common_loops_of_statements(statement_mapping, statement, statement)
AP, sep 25th 1995 : I have added a function from static_controlise/utils.c.
Definition: utils.c:2497
void pu_vect_fprint(FILE *, Pvecteur)
===========================================================================
Definition: print.c:446
void fprint_psysteme(FILE *, Psysteme)
===========================================================================
Definition: print.c:302
#define static_control_loops(x)
Definition: paf_ri.h:757
#define quast_undefined
Definition: paf_ri.h:603
struct _newgen_struct_static_control_ * static_control
Definition: paf_ri.h:184
#define leaf_label_statement(x)
Definition: paf_ri.h:451
@ is_quast_value_quast_leaf
Definition: paf_ri.h:654
@ is_quast_value_conditional
Definition: paf_ri.h:655
#define static_control_params(x)
Definition: paf_ri.h:755
#define dfg_vertex_label_statement(x)
Definition: paf_ri.h:413
#define quast_leaf_undefined
Definition: paf_ri.h:567
#define leaf_label_depth(x)
Definition: paf_ri.h:453
#define dfg_vertex_label_exec_domain(x)
Definition: paf_ri.h:415
#define LEAF_LABEL(x)
LEAF_LABEL.
Definition: paf_ri.h:421
Ppath pa_full()
Ppath pa_full() AL 18/11/93 Returns full space path : pa_full = pa_new()
Definition: path.c:117
bool pa_empty_p(Ppath in_pa)
pa_empty_p( (Ppath) in_pa ) AL 18/11/93 Returns True if in_pa = (1*TCST = 0) ^ (NIL)
Definition: path.c:141
quast pip_integer_max(Psysteme ps_dep, Psysteme ps_context, Pvecteur pv_unknowns)
==================================================================
Definition: pip.c:637
void sort_psysteme(Psysteme ps, Pvecteur pv)
==================================================================
Definition: pip.c:729
#define print_effects(e)
Definition: print.c:334
void print_statement(statement)
Print a statement on stderr.
Definition: statement.c:98
#define syntax_reference(x)
Definition: ri.h:2730
#define reference_variable(x)
Definition: ri.h:2326
#define ENTITY(x)
ENTITY.
Definition: ri.h:2755
#define statement_ordering(x)
Definition: ri.h:2454
#define predicate_undefined_p(x)
Definition: ri.h:2047
#define EXPRESSION(x)
EXPRESSION.
Definition: ri.h:1217
#define predicate_undefined
Definition: ri.h:2046
#define reference_indices(x)
Definition: ri.h:2328
#define statement_instruction(x)
Definition: ri.h:2458
#define instruction_call(x)
Definition: ri.h:1529
#define call_arguments(x)
Definition: ri.h:711
#define statement_number(x)
Definition: ri.h:2452
#define expression_syntax(x)
Definition: ri.h:1247
#define predicate_system(x)
Definition: ri.h:2069
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
Psysteme sc_variable_rename(Psysteme s, Variable v_old, Variable v_new)
Psysteme sc_variable_rename(Psysteme s, Variable v_old, Variable v_new): reecriture du systeme s remp...
Definition: sc.c:157
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...
int fprintf()
test sc_min : ce test s'appelle par : programme fichier1.data fichier2.data ...
void forward_substitute_in_exp(expression *, hash_table)
Definition: utils.c:1148
Psysteme psys
Definition: union-local.h:19
Structure for return of a possible source.
Pbase base
Definition: sc-local.h:75
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
#define PA_UNDEFINED_P(pa)
Definition: union-local.h:110
struct Spath * Ppath
#define TCST
VARIABLE REPRESENTANT LE TERME CONSTANT.
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
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
Pvecteur vect_add(Pvecteur v1, Pvecteur v2)
package vecteur - operations binaires
Definition: binaires.c:53
Pvecteur vect_substract(Pvecteur v1, Pvecteur v2)
Pvecteur vect_substract(Pvecteur v1, Pvecteur v2): allocation d'un vecteur v dont la valeur est la di...
Definition: binaires.c:75

References ADD_ELEMENT_TO_LIST, adg_compact_quast(), adg_decreasing_stat_order_sort(), adg_enrichir(), adg_fill_with_quast(), adg_get_loop_indices(), adg_get_predicate_of_loops(), adg_is_textualy_after_p(), adg_list_to_vect(), adg_merge_entities_lists(), adg_number_of_same_loops(), adg_number_to_ordering(), adg_number_to_statement(), adg_number_to_vertex(), adg_path_max_source(), adg_path_possible_source(), adg_rename_entities(), adg_same_dfg_vertex_number(), adg_sc_dup(), adg_sc_update_base(), adg_suppress_2nd_in_1st_ps(), adg_update_dfg(), adg_vertex_to_statement(), adg_write_reference_list(), Ssysteme::base, call_arguments, CAR, CONS, contrainte_make(), CONTRAINTE_UNDEFINED, copy_expression(), debug(), dfg_vertex_label_exec_domain, dfg_vertex_label_statement, EFFECT, effect_any_reference, ENDP, ENTITY, ENTRY_ORDER, EXPRESSION, EXPRESSION_PVECTEUR, expression_syntax, forward_substitute_in_exp(), fprint_psysteme(), fprintf(), gen_append(), gen_length(), gen_nth(), get_debug_level(), GET_STATEMENT_MAPPING, Gforward_substitute_table, graph_undefined, graph_vertices, Gvertex_number_to_statement, HASH_MAP, hash_pointer, hash_put(), hash_table_free(), hash_table_make(), if(), imprime_special_quast(), instruction_call, is_quast_value_conditional, is_quast_value_quast_leaf, LEAF_LABEL, leaf_label_depth, leaf_label_statement, list_to_base(), make_conditional(), make_dfg_vertex_label(), make_graph(), make_leaf_label(), make_predicate(), make_quast(), make_quast_leaf(), make_quast_value(), make_vertex(), my_pip_count, my_sc_faisabilite(), NIL, pa_empty_p(), pa_full(), PA_UNDEFINED_P, Sposs_source::pat, pip_integer_max(), pips_internal_error, POP, predicate_system, predicate_undefined, predicate_undefined_p, print_effects, print_statement(), Spath::psys, pu_vect_fprint(), Sposs_source::qua, quast_leaf_undefined, quast_undefined, read_reference_list(), reference_indices, reference_variable, sc_append(), sc_dup(), sc_make(), sc_variable_rename(), sccflags_undefined, sort_psysteme(), statement_instruction, statement_number, statement_ordering, static_control_loops, static_control_params, stco_common_loops_of_statements(), syntax_reference, TAKE_LAST, TCST, VALUE_ONE, vect_add(), vect_new(), vect_substract(), VERTEX, vertex_successors, vertex_undefined, and vertex_vertex_label.

Referenced by array_dfg().

+ Here is the caller graph for this function:

◆ array_dfg()

boolean array_dfg ( char*  mod_name)

======================================================================

stubs.c

void array_dfg( (char*) module_name ) AL 93/06/29

It computes the array data flow graph using Feautrier's algorithm. This kind of graph detects the real dependances between arrays. It could be computed on a static control program. The original code is prepared by the static_controlize package. See its comments for more details.

summary or not ?

Initialize debugging functions

Initialization of the pass

set current_module_entity to ent ...

If the input program is not a static_control one, return

What will we compute ?

We need the dependance graph for a first source approximation. The graph is first reversed to have the possible source statement. Then we take only the WR dependances. At the end : duplicate nodes "a la Redon" for IF statement.

We reorder the statement number linked to each vertex in order to distinguich duplicated vertices

We compute the core of the pass

End of the program

Parameters
mod_nameodule

Definition at line 501 of file array_dfg.c.

503 {
504  extern int Gcount_re;
505  extern int Gcount_ie;
506  graph dg = NULL, rev_dg = NULL, wr_dg = NULL;
507  graph dup_dg = NULL, ret_dfg = NULL;
508  entity ent = NULL;
509  statement mod_stat = NULL;
510  static_control stco = NULL;
511  string ss = NULL; /* summary or not ? */
512  bool SUMMARY = false;
513 
514  /* Initialize debugging functions */
515  debug_on("ARRAY_DFG_DEBUG_LEVEL");
516  if (get_debug_level() > 0)
517  user_log("\n\n *** COMPUTE ARRAY DATA FLOW GRAPH for %s\n",mod_name);
518 
519 
520  my_pip_count = 0;
521  my_fai_count = 0;
522 
523  /* Initialization of the pass */
524  Gcount_re = 0;
525  Gcount_ie = 0;
526  ent = local_name_to_top_level_entity( mod_name );
527  set_current_module_entity(ent); /* set current_module_entity to ent ... */
528 
529  mod_stat = (statement) db_get_memory_resource(DBR_CODE, mod_name, true);
530  Gstco_map = (statement_mapping) db_get_memory_resource(DBR_STATIC_CONTROL,
531  mod_name, true);
532 
533  /* If the input program is not a static_control one, return */
535  if ( !static_control_yes( stco )) {
536  pips_user_error("\n"
537  " CAN'T APPLY FEAUTRIER'S ALGORITHM:\n"
538  " This is not a static control program !");
539  }
542  db_get_memory_resource(DBR_PROPER_EFFECTS, mod_name, true));
543 
544  /* What will we compute ? */
545  SUMMARY = ((ss = getenv("SUMMARY")) != NULL)? atoi(ss) : false;
546 
547 
548  /* We need the dependance graph for a first source approximation.
549  * The graph is first reversed to have the possible source statement.
550  * Then we take only the WR dependances.
551  * At the end : duplicate nodes "a la Redon" for IF statement.
552  */
553  dg = (graph) db_get_memory_resource( DBR_DG, mod_name, true );
554  rev_dg = adg_reverse_graph( dg );
555  wr_dg = adg_only_call_WR_dependence( rev_dg );
556  dup_dg = adg_dup_disjunctive_nodes( wr_dg, Gstco_map );
557 
558  /* We reorder the statement number linked to each vertex
559  * in order to distinguich duplicated vertices
560  */
562 
563  /* We compute the core of the pass */
564  if (!SUMMARY)
565  { ret_dfg = adg_dataflowgraph( mod_stat, Gstco_map, dup_dg );}
566  else ret_dfg = adg_dataflowgraph_with_extremities(mod_stat, Gstco_map, dup_dg);
567 
568 
569  /* End of the program */
570  if (get_debug_level() > 0) fprint_dfg(stderr, ret_dfg);
571  if (get_debug_level() > 8) fprint_dfg(stderr, adg_pure_dfg(ret_dfg));
572 
573  DB_PUT_MEMORY_RESOURCE( DBR_ADFG, strdup(mod_name), ret_dfg);
574 
575  if (get_debug_level() > 0) {
576  printf("\n PIP CALLS : %d\n", my_pip_count);
577  printf("\n FAI CALLS : %d\n", my_fai_count);
578  }
579 
580  if (get_debug_level() > 0) user_log("\n\n *** ARRAY_DFG done\n");
581  debug_off();
582 
586 
587  return(true);
588 }
void user_log(const char *format,...)
Definition: message.c:234
graph adg_dup_disjunctive_nodes(graph g, statement_mapping stco_map)
======================================================================
Definition: adg_graph.c:581
graph adg_pure_dfg(graph in_gr)
======================================================================
Definition: adg_graph.c:56
graph adg_only_call_WR_dependence(graph g)
======================================================================
Definition: adg_graph.c:784
void adg_reorder_statement_number(graph in_dfg)
======================================================================
Definition: adg_graph.c:318
graph adg_reverse_graph(graph g)
======================================================================
Definition: adg_graph.c:1047
void fprint_dfg(FILE *fp, graph obj)
===========================================================================
graph adg_dataflowgraph_with_extremities(statement mod_stat, statement_mapping stco_map, graph dup_dg)
======================================================================
Definition: adg_summary.c:230
int my_fai_count
Definition: array_dfg.c:51
graph adg_dataflowgraph(statement mod_stat, statement_mapping stco_map, graph dup_dg)
======================================================================
Definition: array_dfg.c:70
int Gcount_re
External variables.
Definition: array_dfg.c:45
list Gstructural_parameters
Definition: array_dfg.c:48
statement_mapping Gstco_map
Definition: array_dfg.c:47
int Gcount_ie
Definition: array_dfg.c:46
static graph dg
dg is the dependency graph ; FIXME : should not be static global ?
Definition: chains.c:124
struct _newgen_struct_statement_ * statement
Definition: cloning.h:21
void reset_proper_rw_effects(void)
void set_proper_rw_effects(statement_effects)
#define SUMMARY
struct _newgen_struct_graph_ * graph
Definition: graph.h:31
void reset_current_module_entity(void)
Reset the current module entity.
Definition: static.c:97
void reset_current_module_statement(void)
Reset the current module statement.
Definition: static.c:221
entity set_current_module_entity(entity)
static.c
Definition: static.c:66
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
static statement mod_stat
We want to keep track of the current statement inside the recurse.
Definition: impact_check.c:41
#define debug_on(env)
Definition: misc-local.h:157
#define debug_off()
Definition: misc-local.h:160
#define pips_user_error
Definition: misc-local.h:147
hash_table statement_mapping
these macros are obsolete! newgen functions (->) should be used instead
Definition: newgen-local.h:42
#define false
Definition: newgen_types.h:80
#define static_control_yes(x)
Definition: paf_ri.h:753
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
char * strdup()
int printf()

References adg_dataflowgraph(), adg_dataflowgraph_with_extremities(), adg_dup_disjunctive_nodes(), adg_only_call_WR_dependence(), adg_pure_dfg(), adg_reorder_statement_number(), adg_reverse_graph(), db_get_memory_resource(), DB_PUT_MEMORY_RESOURCE, debug_off, debug_on, dg, fprint_dfg(), Gcount_ie, Gcount_re, get_debug_level(), GET_STATEMENT_MAPPING, Gstco_map, Gstructural_parameters, local_name_to_top_level_entity(), mod_stat, my_fai_count, my_pip_count, pips_user_error, printf(), reset_current_module_entity(), reset_current_module_statement(), reset_proper_rw_effects(), set_current_module_entity(), set_proper_rw_effects(), static_control_params, static_control_yes, strdup(), SUMMARY, and user_log().

+ Here is the call graph for this function:

◆ my_sc_faisabilite()

bool my_sc_faisabilite ( Psysteme  in_ps)

Definition at line 55 of file array_dfg.c.

57 {
58  my_fai_count++;
59  return(sc_rational_feasibility_ofl_ctrl(in_ps, NO_OFL_CTRL,true));
60 }
bool sc_rational_feasibility_ofl_ctrl(Psysteme sc, int ofl_ctrl, bool ofl_res)
#define NO_OFL_CTRL

References my_fai_count, NO_OFL_CTRL, and sc_rational_feasibility_ofl_ctrl().

Referenced by adg_dataflowgraph(), and adg_dataflowgraph_with_extremities().

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

Variable Documentation

◆ Gcount_ie

int Gcount_ie

Definition at line 46 of file array_dfg.c.

Referenced by adg_get_integer_entity(), and array_dfg().

◆ Gcount_re

int Gcount_re

External variables.

Global variables.

Definition at line 45 of file array_dfg.c.

Referenced by adg_rename_entities(), and array_dfg().

◆ Gforward_substitute_table

hash_table Gforward_substitute_table
static

Definition at line 53 of file array_dfg.c.

Referenced by adg_dataflowgraph().

◆ Gstco_map

◆ Gstructural_parameters

list Gstructural_parameters

Definition at line 48 of file array_dfg.c.

Referenced by adg_dataflowgraph_with_extremities(), and array_dfg().

◆ Gvertex_number_to_statement

hash_table Gvertex_number_to_statement
extern

Global variables.

Definition at line 42 of file adg_graph.c.

Referenced by adg_dataflowgraph(), adg_number_to_ordering(), adg_reorder_statement_number(), and adg_vertex_to_ordering().

◆ my_fai_count

int my_fai_count

Definition at line 51 of file array_dfg.c.

Referenced by array_dfg(), and my_sc_faisabilite().

◆ my_pip_count

int my_pip_count

Definition at line 50 of file array_dfg.c.

Referenced by adg_dataflowgraph(), adg_dataflowgraph_with_extremities(), and array_dfg().