PIPS
chains.c
Go to the documentation of this file.
1 /*
2 
3  $Id: chains.c 23495 2018-10-24 09:19:47Z 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 /* -- usedef.c
28 
29  Computes (approximate) use/def chains of a structured control graph.
30 
31  */
32 
33 #include <stdio.h>
34 #include <string.h>
35 #include <stdlib.h>
36 
37 #include "linear.h"
38 
39 #include "genC.h"
40 #include "ri.h"
41 #include "effects.h"
42 
43 typedef void * arc_label;
44 typedef void * vertex_label;
45 
46 #include "graph.h"
47 #include "dg.h"
48 
49 #include "misc.h"
50 #include "properties.h"
51 
52 #include "ri-util.h"
53 #include "effects-util.h"
54 
55 #include "ricedg.h"
56 
57 #include "effects-generic.h"
58 #include "effects-simple.h"
59 
60 #include "chains.h"
61 #include "pipsdbm.h"
62 
63 #include "pips-libs.h"
64 
65 /* Some forward declarations */
66 static void reset_effects();
68 static void inout_control();
69 static void inout_statement();
70 //static void usedef_control(); declared but never defined.
71 static void genref_statement();
72 static bool dd_du( effect fin, effect fout );
73 static bool ud( effect fin, effect fout );
74 static void add_conflicts(effect fin,
75  statement stout,
76  vertex vout,
77  cons *effect_outs,
78  bool(*which)());
79 
80 /* Macro to create set */
81 #define MAKE_STATEMENT_SET() (set_make( set_pointer ))
82 
83 /* Default sizes for corresponding sets. This is automatically adjusted
84  according to needs by the hash table package. */
85 #define INIT_STATEMENT_SIZE 20
86 #define INIT_ENTITY_SIZE 10
87 
88 /* Mapping from effects to the associated statement */
90 
91 /* Gen maps each statement to the effects it generates. */
92 static hash_table Gen;
93 #define GEN(st) ((set)hash_get( Gen, (char *)st ))
94 
95 /* Refs maps each statement to the effects it references. */
96 static hash_table Ref;
97 #define REF(st) ((set)hash_get( Ref, (char *)st ))
98 
99 /* current_defs is the set of DEF at the current point of the computation */
102 
103 /* Def_in maps each statement to the statements that are in-coming the statement
104  * It's only used for unstructured, current_defs is used for structured parts */
106 #define DEF_IN(st) ((set)hash_get(Def_in, (char *)st))
107 
108 /* Def_out maps each statement to the statements that are out-coming the statement
109  * It's only used for unstructured, current_defs is used for structured parts */
111 #define DEF_OUT(st) ((set)hash_get(Def_out, (char *)st))
112 
113 /* Ref_in maps each statement to the effects that are in-coming the statement
114  * It's only used for unstructured, current_refs is used for structured parts */
116 #define REF_IN(st) ((set)hash_get(Ref_in, (char *)st))
117 
118 /* Ref_out maps each statement to the effects that are out-coming the statement
119  * It's only used for unstructured, current_refs is used for structured parts */
121 #define REF_OUT(st) ((set)hash_get(Ref_out, (char *)st))
122 
123 /* dg is the dependency graph ; FIXME : should not be static global ? */
124 static graph dg;
125 
126 /* Vertex_statement maps each statement to its vertex in the dependency graph. */
128 
129 /* Some properties */
130 static bool one_trip_do_p;
132 static bool mask_effects_p;
134 
135 /* Access functions for debug only */
136 
137 /**
138  * @brief displays on stderr, the MSG followed by the set of statement numbers
139  * associated to effects present in the set S.
140  *
141  * @param msg a string to be display at the beginning
142  * @param s the set of effects to display
143  */
144 static void local_print_statement_set( string msg, set s ) {
145  fprintf( stderr, "\t%s ", msg );
146  SET_FOREACH( effect, eff, s) {
147  fprintf( stderr,
148  ",%p (%td) ",
149  eff,
151  print_effect( (effect) eff );
152  }
153  fprintf( stderr, "\n" );
154 }
155 
156 /**
157  * @return the vertex associated to the statement ST in the dependence graph DG.
158  */
160  vertex v = (vertex) hash_get( Vertex_statement, (char *) st );
161  pips_assert( "vertex_statement", v != (vertex)HASH_UNDEFINED_VALUE );
162  return ( v );
163 }
164 
165 /**
166  * @brief Initializes the global data structures needed for usedef computation
167  * of one statement.
168  *
169  * @param st the statement to initialize
170  * @return always true (gen_recurse continuation)
171  */
172 static bool init_one_statement( statement st ) {
173 
174  if ( GEN( st ) == (set) HASH_UNDEFINED_VALUE ) {
175  /* First initialization (normal use) */
176 
177  ifdebug(2) {
178  fprintf( stderr,
179  "Init statement %td with effects %p, ordering %tx\n",
180  statement_number( st ),
182  statement_ordering(st) );
184  }
185 
186  /* Create a new vertex in the DG for the statement: */
187  dg_vertex_label l;
188  vertex v;
190  v = make_vertex( l, NIL );
191  hash_put( Vertex_statement, (char *) st, (char *) v );
193 
194  /* If the statement has never been seen, allocate new sets:
195  * This could be optimized : {DEF,REF}_{IN,OUT} are
196  * needed only for unstructured */
197  hash_put( Gen, (char *) st, (char *) MAKE_STATEMENT_SET() );
198  hash_put( Ref, (char *) st, (char *) MAKE_STATEMENT_SET() );
199  hash_put( Def_in, (char *) st, (char *) MAKE_STATEMENT_SET() );
200  hash_put( Def_out, (char *) st, (char *) MAKE_STATEMENT_SET() );
201  hash_put( Ref_in, (char *) st, (char *) MAKE_STATEMENT_SET() );
202  hash_put( Ref_out, (char *) st, (char *) MAKE_STATEMENT_SET() );
203 
204  /* FI: regions are not really proper effects...
205  I should use proper effects for non-call instruction
206  I need a global variable
207  let's kludge this for the time being, 5 August 1992
208  */
211  {
212  hash_put( effects2statement, (char *) e, (char *) st );
213  }
214  }
215  } else {
216  /* If the statement has already been seen, reset the sets associated
217  to it: */
218  set_clear( GEN( st ) );
219  set_clear( REF( st ) );
220  set_clear( DEF_OUT( st ) );
221  set_clear( DEF_IN( st ) );
222  set_clear( REF_OUT( st ) );
223  set_clear( REF_IN( st ) );
224  }
225  /* Go on recursing down: */
226  return true;
227 }
228 
229 /* The genref_xxx functions implement the computation of GEN and REF
230  sets from Aho, Sethi and Ullman "Compilers" (p. 612). This is
231  slightly more complex since we use a structured control graph, thus
232  fixed point computations can be recursively required (the correctness
233  of this is probable, although not proven, as far as I can tell). */
234 
235 /* KILL_STATEMENT updates the KILL set of statement ST on entity LHS. Only
236  effects that modify one reference (i.e., assignments) are killed (see
237  above). Write effects on arrays (see IDXS) don't kill the definitions of
238  the array. Equivalence with non-array entities is managed properly. */
239 /**
240  * @brief Kill the GEN set with a set of KILL effects
241  * @param gen the set to filter, modified by side effects
242  * @param killers the "killer" effects
243  */
244 static void kill_effects(set gen, set killers) {
245  set killed = MAKE_STATEMENT_SET();
246  SET_FOREACH(effect,killer,killers) {
247  /* A killer effect is exact and is a write (environment effects kills !!) */
248  if ( action_write_p(effect_action(killer))
249  // these tests are optimizations to avoid redundant tests inside the
250  // SET_FOREACH loop;
251  // they allow to call first_exact_scalar_effect_certainly_includes_second_effect_p
252  // instead of first_effect_certainly_includes_second_effect_p
253  // if the latter is enhanced, these tests should be updated accordingly.
254  && effect_exact_p(killer) && effect_scalar_p(killer) ) {
255  SET_FOREACH(effect,e,gen) {
256  /* We only kill store effect */
257  if(store_effect_p(e)) {
258  /* We avoid a self killing */
259  if( e != killer
261  set_add_element( killed, killed, e );
262  }
263  }
264  }
265  set_difference(gen,gen,killed);
266  set_clear(killed);
267  }
268  }
269  set_free(killed);
270 }
271 
272 /**
273  * @brief Compute Gen and Ref set for a single statement
274  * @param st the statement to compute
275  */
276 static void genref_one_statement( statement st ) {
277  set gen = GEN( st );
278  set ref = REF( st );
279  set_clear( gen );
280  set_clear( ref );
281  /* Loop over effects to find which one will generates
282  * or references some variables
283  */
285  {
286  action a = effect_action( e );
287 
288  if ( action_write_p( a ) ) {
289  pips_assert("Effect isn't map to this statement !",
290  st == hash_get(effects2statement, e));
291 
292  /* A write effect will always generate a definition */
293  set_add_element( gen, gen, (char *) e );
294  } else if ( action_read_p( a ) ) {
295  /* A read effect will always generate a reference */
296  set_add_element( ref, ref, (char *) e );
297  } else {
298  /* Secure programming */
299  pips_internal_error("Unknow action for effect : "
300  "neither a read nor a write !");
301  }
302  }
303 }
304 
305 /**
306  * @brief Compute Gen and Ref set for a test
307  * @param t the test
308  * @param s the statement to compute
309  */
310 static void genref_test( test t, statement s ) {
311  statement st = test_true(t);
312  statement sf = test_false(t);
313  set ref = REF( s );
314 
315  /* compute true path */
316  genref_statement( st );
317  /* compute false path */
318  genref_statement( sf );
319 
320  /* Combine the two path to summarize the test */
321  set_union( GEN( s ), GEN( st ), GEN( sf ) );
322  set_union( ref, ref, REF( sf ) );
323  set_union( ref, ref, REF( st ) );
324 }
325 
326 /**
327  * @brief MASK_EFFECTS masks the effects in S according to the locals L.
328  * @param s the set of effects
329  * @param l the locals to mask
330  */
331 static void mask_effects( set s, list l ) {
332  cons *to_mask = NIL;
333  /*
334  * Loop over effect and check if they affect a local variable
335  * We mask only read effects (FIXME : why ?)
336  */
337  SET_FOREACH(effect, f, s) {
338  action a = effect_action( f );
339 
340  if ( action_read_p( a ) ) {
341  FOREACH( entity, e, l )
342  {
344  /* Register which one we have to mask */
345  to_mask = CONS( effect, f, to_mask );
346  }
347  }
348  }
349  }
350  /* Do the masking */
351  FOREACH( effect, f, to_mask ) {
352  set_del_element( s, s, (char *) f );
353  }
354 
355  /* We free because we are good programmers and we don't leak ;-) */
356  gen_free_list( to_mask );
357 }
358 
359 /**
360  * @brief Compute Gen and Ref set for any loop (do, for, while,...)
361  * @description It has to deal specially with the loop variable which is not
362  * managed in the Dragon book. Effect masking is performed
363  * on locals (i.e., gen&ref sets are pruned from local definitions).
364  *
365  * For DO loop, if loops are at least one trip (set by property "ONE_TRIP_DO"),
366  * then statements are always killed by execution of loop body.
367  *
368  * @param l the loop to compute
369  * @param st the statement that hold the loop
370  *
371  */
372 static void genref_any_loop(
373  statement body,
374  statement st,
375  list locals,
376  _UNUSED_ bool one_trip_do_p)
377 {
378  set gen = GEN( st );
379  set ref = REF( st );
380 
381  /* Compute genref on the loop body */
382  genref_statement( body );
383 
384  /* Summarize the body to the statement that hold the loop */
385  set_union( gen, gen, GEN( body ) );
386  set_union( ref, ref, REF( body ) );
387 
388  /* Filter effects on local variables */
389  if ( mask_effects_p ) {
390  mask_effects( gen, locals );
391  mask_effects( ref, locals );
392  }
393 
394 }
395 
396 /**
397  * @brief Compute Gen and Ref set for a "do" loop
398  * @description see genref_any_loop()
399  *
400  * @param l the loop to compute
401  * @param st the statement that hold the loop
402  */
403 static void genref_loop( loop l, statement st ) {
404  statement body = loop_body( l );
405 
406  /* Building locals list */
407  list llocals = loop_locals( l );
408  list slocals = statement_declarations(st);
409  list locals = gen_nconc( gen_copy_seq( llocals ), gen_copy_seq( slocals ) );
410 
411  /* Call the generic function handling all kind of loop */
412  genref_any_loop( body, st, locals, one_trip_do_p );
413 
414  /* We free because we are good programmers and we don't leak ;-) */
415  gen_free_list( locals );
416 }
417 
418 /**
419  * @brief Compute Gen and Ref set for a "for" loop
420  * @description see genref_any_loop()
421  *
422  * @param l the loop to compute
423  * @param st the statement that hold the loop
424  *
425  */
426 static void genref_forloop( forloop l, statement st ) {
427  statement body = forloop_body( l );
428  list locals = statement_declarations(st);
429 
430  /* Call the generic function handling all kind of loop */
431  genref_any_loop( body, st, locals, one_trip_do_p );
432 
433 }
434 
435 /**
436  * @brief Compute Gen and Ref set for a "while" loop
437  * @description see genref_any_loop()
438  *
439  * @param l the loop to compute
440  * @param st the statement that hold the loop
441  */
442 static void genref_whileloop( whileloop l, statement st ) {
443  statement body = whileloop_body( l );
444  list locals = statement_declarations(st);
445 
446  /* Call the generic function handling all kind of loop */
447  genref_any_loop( body, st, locals, one_trip_do_p );
448 }
449 
450 /**
451  * @brief Compute Gen and Ref set for a block
452  * @description The Dragon book only deals with a sequence of two statements.
453  * here we generalize to lists, via recursion. Statement are processed in
454  * reversed order (i.e. on the descending phase of recursion)
455  *
456  * @param sts the list of statements inside the block
457  * @param st the statement that hold the block
458  *
459  */
460 static void genref_block( cons *sts, statement st ) {
461  /* Summarize for the block */
462  set gen_st = GEN( st );
463  set ref_st = REF( st );
464 
465  /* loop over statements inside the block */
466  FOREACH( statement, one, sts ) {
467 
468  genref_statement( one );
469 
470  // We no longer use a "kill set" FIXME : one_trip_do, test, ....
471  kill_effects(gen_st,GEN(one));
472  set_union(gen_st,GEN(one),gen_st);
473 
474  set_union( ref_st, REF( one ), ref_st );
475 
476  }
477  // Gen for the block doesn't include locally declared variable
478  if ( mask_effects_p) {
479  mask_effects( gen_st, statement_declarations(st) );
480  mask_effects( ref_st, statement_declarations(st) );
481  }
482 }
483 
484 /**
485  * @brief Compute Gen and Ref set for an unstructured
486  * @description computes the gens, refs, and kills set of the unstructured by
487  * recursing on INOUT_CONTROL. The gens&refs can then be inferred.
488  * The situation for the kills is more fishy; for the moment, we just keep
489  * the kills that are common to all statements of the control graph.
490  *
491  * @param u is the unstructured
492  * @param st is the statement that hold the unstructured
493  */
495  control c = unstructured_control( u );
497  cons *blocs = NIL;
498 
499  set_clear( DEF_IN( st ) );
500  /* recursing */
501  CONTROL_MAP( c, {statement st = control_statement( c );
502  genref_statement( st );
503  },
504  c, blocs );
505 
506  if ( set_undefined_p( DEF_OUT( exit )) ) {
509  CONTROL_MAP( cc, {
510  set_union( ref, ref, REF( control_statement( cc )));
511  }, c, blocs );
512  set_assign( REF( st ), ref );
513  set_free( ref );
514  set_assign( GEN( st ), empty );
515  set_free( empty );
516  } else {
517  set_assign( GEN( st ), DEF_OUT( exit ) );
518  set_difference( REF( st ), REF_OUT( exit ), REF_IN( st ) );
519  }
520  gen_free_list( blocs );
521 }
522 
523 /**
524  * @brief Does the dispatch and recursion loop
525  * @description
526  *
527  * @param i is the instruction
528  * @param st is the statement that hold the instruction
529  */
531  cons *pc;
532  test t;
533  loop l;
534 
535  switch ( instruction_tag(i) ) {
537  genref_block( pc = instruction_block(i), st );
538  break;
539  case is_instruction_test:
540  t = instruction_test(i);
541  genref_test( t, st );
542  break;
543  case is_instruction_loop:
544  l = instruction_loop(i);
545  genref_loop( l, st );
546  break;
549  genref_whileloop( l, st );
550  break;
551  }
552  case is_instruction_forloop: {
554  genref_forloop( l, st );
555  break;
556  }
559  break;
560  case is_instruction_call:
562  case is_instruction_goto:
563  /* no recursion for these kind of instruction */
564  break;
565  default:
566  pips_internal_error("unexpected tag %d", instruction_tag(i));
567  }
568 }
569 
570 /**
571  * @brief Compute recursively Gen and Ref set for a statement.
572  * This is the main entry to this task.
573  * @description computes the gens and refs set of the statement by
574  * recursing
575  *
576  * @param s is the statement to compute
577  */
578 static void genref_statement( statement s ) {
579 
580  /* Compute genref using effects associated to the statement itself */
582 
583  ifdebug(2) {
584  debug( 2,
585  "genref_statement",
586  "Result genref_one_statement for Statement %p [%s]:\n",
587  s,
589  local_print_statement_set( "GEN", GEN( s ) );
590  local_print_statement_set( "REF", REF( s ) );
591  }
592 
593  /* Recurse inside the statement (relevant for blocks, loop, ...) */
595 
596  ifdebug(2) {
597  debug( 2,
598  "genref_statement",
599  "Result for Statement %p [%s]:\n",
600  s,
602  ;
603  local_print_statement_set( "GEN", GEN( s ) );
604  local_print_statement_set( "REF", REF( s ) );
605  }
606 }
607 
608 /**
609  * @brief Propagates in sets of ST (which is inherited) to compute the out sets.
610  *
611  * @param st is the statement that hold the block
612  * @param sts is the list of statement inside the block
613  */
614 static void inout_block( _UNUSED_ statement st, cons *sts ) {
615 
616  /* loop over statements inside the block */
617  FOREACH( statement, one, sts ) {
618  /* Compute the outs from the ins for this statement */
619  inout_statement( one );
620  }
621 }
622 
623 /**
624  * @brief Propagates in sets of ST (which is inherited) to compute the out sets.
625  *
626  * @param st is the statement that hold the test
627  * @param t is the test
628  */
629 static void inout_test( _UNUSED_ statement s, test t ) {
630  statement st = test_true( t );
631  statement sf = test_false( t );
632 
633  // Save DEF and REF
634  set def_in = set_dup(current_defs);
635  set ref_in = set_dup(current_refs);
636 
637  /*
638  * Compute true path
639  */
640  inout_statement( st );
641 
642  // Save DEF and REF
643  set def_out = current_defs;
644  set ref_out = current_refs;
645 
646  // Restore DEF and REF
647  current_defs = def_in;
648  current_refs = ref_in;
649 
650  /*
651  * Compute false path
652  */
653  inout_statement( sf );
654 
655  /* Compute the out for the test */
656  set_union( current_defs, current_defs, def_out );
657  set_union( current_refs, current_refs, ref_out );
658 
659  // Free temporary set
660  set_free(def_out);
661  set_free(ref_out);
662 
663 }
664 
665 /**
666  * @brief Propagates in sets of ST (which is inherited) to compute the out sets.
667  *
668  * @param st is the statement that hold the loop
669  * @param lo is the loop
670  * @param one_trip_do_p tell if there is always at least one trip (do loop only)
671  * @param never_executed_p tell if loop never executed (when it's possible, do loop only) (unused)
672  */
673 static void inout_any_loop( statement st, statement body, bool one_trip_do_p, bool __attribute__ ((unused)) never_executed_p ) {
674  // NL: I don't know how it work to make the optimization with never_executed_p
675  // Maybe decorate the code by
676  // if(!never_executed_p) {
677  set def_in;
678  set ref_in;
679 
680  if ( ! one_trip_do_p ) {
681  // Save DEF and REF
682  def_in = set_dup(current_defs);
683  ref_in = set_dup(current_refs);
684  }
685 
686  /* Compute "in" sets for the loop body */
689 
690  /* Compute loop body */
691  inout_statement( body );
692 
693  /* Compute "out" sets for the loop */
694  if ( ! one_trip_do_p ) {
695  /* Body is not always done, approximation by union */
696  set_union( current_defs, current_defs, def_in );
697  set_union( current_refs, current_refs, ref_in );
698  // Free temporary set
699  set_free(def_in);
700  set_free(ref_in);
701  }
702 }
703 
704 /**
705  * @brief Propagates in sets of ST (which is inherited) to compute the out sets.
706  *
707  * @param st is the statement that hold the loop
708  * @param lo is the loop
709  */
710 static void inout_loop( statement st, loop lo ) {
711  // Try to detect loop executed at least once trivial case
712  bool executed_once_p = one_trip_do_p;
713  if(!executed_once_p) executed_once_p = loop_executed_at_least_once_p(lo);
714 
715  inout_any_loop( st, loop_body( lo ), executed_once_p, loop_executed_never_p(lo) );
716 }
717 
718 /**
719  * @brief Propagates in sets of ST (which is inherited) to compute the out sets.
720  *
721  * @param st is the statement that hold the loop
722  * @param t is the loop
723  */
724 static void inout_whileloop( statement st, whileloop wl ) {
725  statement body = whileloop_body( wl );
726  inout_any_loop( st, body, false, false );
727 }
728 
729 /**
730  * @brief Propagates in sets of ST (which is inherited) to compute the out sets.
731  *
732  * @param st is the statement that hold the loop
733  * @param t is the loop
734  */
735 static void inout_forloop( statement st, forloop fl ) {
736  statement body = forloop_body( fl );
737  inout_any_loop( st, body, one_trip_do_p, false );
738 }
739 
740 /**
741  * @brief Propagates in sets of ST (which is inherited) to compute the out sets.
742  *
743  * @param st is the statement that hold the call
744  * @param c is the call (unused)
745  */
746 static void inout_call( statement st, call __attribute__ ((unused)) c ) {
747  /* Compute "out" sets */
748 
751 
754 }
755 
756 /**
757  * @brief Propagates in sets of ST (which is inherited) to compute the out sets.
758  *
759  * @param st is the statement that hold the unstructured
760  * @param u is the unstructured
761  */
763  control c = unstructured_control( u );
765  statement s_exit = control_statement( exit );
766 
767  /* Compute "in" sets */
770 
771  /* Compute the unstructured */
772  inout_control( c );
773 
774  /* Compute "out" sets */
775  if ( set_undefined_p( DEF_OUT( s_exit )) ) {
776  list blocs = NIL;
779 
780  CONTROL_MAP( cc, {
781  set_union( ref, ref, REF( control_statement( cc )));
782  }, c, blocs );
783  set_assign( REF_OUT( st ), ref );
784  set_assign( DEF_OUT( st ), empty );
785 
786  set_free( ref );
787  set_free( empty );
788  gen_free_list( blocs );
789  } else {
790  set_assign( DEF_OUT( st ), DEF_OUT( s_exit ) );
791  set_assign( REF_OUT( st ), REF_OUT( s_exit ) );
792  }
793 
794  // Exit from unstructured, restore global DEF
795  set_assign( current_defs, DEF_OUT( st ) );
796  set_assign( current_refs, REF_OUT( st ) );
797 
798 }
799 
800 /**
801  * @brief Propagates in sets of ST (which is inherited) to compute the out sets.
802  *
803  * @param st is the statement to compute
804  */
805 static void inout_statement( statement st ) {
806  instruction i;
807  static int indent = 0;
808 
809  ifdebug(2) {
810  pips_debug( 2,
811  "%*s> Computing DEF and REF for statement %p (%td %td):\n"
812  "current_defs %p, current_refs %p\n",
813  indent++,
814  "",
815  st,
816  statement_number( st ),
817  statement_ordering( st ),
818  current_defs,
819  current_refs );
822  }
823  /* Compute Def-Def and Def-Use conflicts from Def_in set */
824  vertex statement_vertex = vertex_statement( st );
826  SET_FOREACH( effect, defIn, current_defs) {
827  add_conflicts( defIn, st, statement_vertex, effects, dd_du );
828  }
829  /* Compute Use-Def conflicts from Ref_in set */
830  SET_FOREACH( effect, refIn, current_refs) {
831  add_conflicts( refIn, st, statement_vertex, effects, ud );
832  }
833 
834  ifdebug(3) {
835  pips_debug( 3,
836  "%*s> After add conflicts for statement %p (%td %td):\n"
837  "current_defs %p, current_refs %p\n",
838  indent,
839  "",
840  st,
841  statement_number( st ),
842  statement_ordering( st ),
843  current_defs,
844  current_refs );
847  }
848 
849  /* Compute "out" sets for the instruction : recursion */
850  switch ( instruction_tag( i = statement_instruction( st )) ) {
852  inout_block( st, instruction_block( i ) );
853  break;
854  case is_instruction_test:
855  inout_test( st, instruction_test( i ) );
856  break;
857  case is_instruction_loop:
858  inout_loop( st, instruction_loop( i ) );
859  break;
862  break;
865  break;
866  case is_instruction_call:
867  inout_call( st, instruction_call( i ) );
868  break;
870  /* The second argument is not used */
871  inout_call( st, (call) instruction_expression( i ) );
872  break;
873  case is_instruction_goto:
874  pips_internal_error("Unexpected tag %d", i );
875  break;
878  break;
879  default:
880  pips_internal_error("Unknown tag %d", instruction_tag(i) );
881  }
882  ifdebug(2) {
883  pips_debug( 2,
884  "%*s> Statement %p (%td %td):\n"
885  "current_defs %p, current_refs %p\n",
886  indent--,
887  "",
888  st,
889  statement_number( st ),
890  statement_ordering( st ),
891  current_defs,
892  current_refs );
893  local_print_statement_set( "DEF_OUT", DEF_OUT( st ) );
894  local_print_statement_set( "REF_OUT", REF_OUT( st ) );
895  }
896 
897 }
898 
899 /**
900  * @brief Propagates in sets of ST (which is inherited) to compute the out sets.
901  * @description It computes the in and out sets of the structured control
902  * graph. This is done by fixed point iteration (see Dragon book, p. 625),
903  * except that the in set of CT is not empty (this explains the set_union
904  * instead of set_assign in the fixed point computation loop on IN( st )).
905  * Once again, the correctness of this modification is not proven.
906  *
907  * @param ct is the control to compute
908  */
909 static void inout_control( control ct ) {
910  bool change;
911  set d_oldout = MAKE_STATEMENT_SET();
912  set d_out = MAKE_STATEMENT_SET();
913  set r_oldout = MAKE_STATEMENT_SET();
914  set r_out = MAKE_STATEMENT_SET();
915  cons *blocs = NIL;
916 
917 
918  ifdebug(2) {
919  fprintf( stderr, "Computing DEF_IN and OUT of control %p entering", ct );
921  }
922 
923  CONTROL_MAP( c, {statement st = control_statement( c );
924  set_assign( DEF_OUT( st ), GEN( st ));
925  set_assign( REF_OUT( st ), REF( st ));
926 
927  if( c != ct ) {
928  set_clear( DEF_IN( st ));
929  set_clear( REF_OUT( st ));
930  }},
931  ct, blocs );
932 
933  for ( change = true; change; ) {
934  ifdebug(3) {
935  fprintf( stderr, "Iterating on %p ...\n", ct );
936  }
937  change = false;
938 
939  CONTROL_MAP( b,
940  { statement st = control_statement( b );
941 
942  set_clear( d_out );
943  set_clear( r_out );
944  MAPL( preds, {control pred = CONTROL( CAR( preds ));
945  statement pst = control_statement( pred );
946 
947  set_union( d_out, d_out, DEF_OUT( pst ));
948  set_union( r_out, r_out, REF_OUT( pst ));},
949  control_predecessors( b ));
950  set_union( DEF_IN( st ), DEF_IN( st ), d_out );
951  set_union( REF_IN( st ), REF_IN( st ), r_out );
952  set_assign( d_oldout, DEF_OUT( st ));
953  set_union( DEF_OUT( st ), GEN( st ),DEF_IN( st ));
954  // FIXME set_difference( diff, DEF_IN( st ), KILL( st )));
955  set_assign( r_oldout, REF_OUT( st ));
956  set_union( REF_OUT( st ), REF( st ), REF_IN( st ));
957  change |= (!set_equal_p( d_oldout, DEF_OUT( st )) ||
958  !set_equal_p( r_oldout, REF_OUT( st )));
959  }, ct, blocs );
960  }
961 
962  CONTROL_MAP( c, {
963  statement st = control_statement( c );
964  /* Prepare "in" sets */
965  set_assign( current_defs, DEF_IN( st ) );
966  set_assign( current_refs, REF_IN( st ) );
967 
968  inout_statement( st);
969 
970  /* Restore out sets */
971  set_assign( DEF_OUT( st ), current_defs );
972  set_assign( REF_OUT( st ), current_refs );
973  },
974  ct, blocs );
975  set_free( d_oldout );
976  set_free( d_out );
977  set_free( r_oldout );
978  set_free( r_out );
979  gen_free_list( blocs );
980 
981 }
982 
983 /**
984  * @brief adds the conflict FIN->FOUT in the list CFS
985  * @description adds the conflict FIN->FOUT in the list CFS (if it's
986  * not already there, and apparently even if it's already there for
987  * performance reason...).
988  *
989  * @param fin is the incoming effect
990  * @param fout is the sink effect
991  * @param cfs is the list of conflict to update
992  */
993 static cons *pushnew_conflict( effect fin, effect fout, cons *cfs ) {
994  conflict c;
995 
996  /* FI: This is a bottleneck for large modules with lots of callees and
997  long effect lists. Let's assume that the pairs (fin, fout) are
998  always unique because the effects are sets. */
999 
1000  /*
1001  MAPL( cs, {
1002  conflict c = CONFLICT( CAR( cs )) ;
1003 
1004  if( conflict_source( c )==fin && conflict_sink( c )==fout ) {
1005  return( cfs ) ;
1006  }
1007  }, cfs ) ;
1008  */
1009 
1010  /* create the conflict */
1011  c = make_conflict( fin, fout, cone_undefined );
1012  ifdebug(2) {
1013  fprintf( stderr,
1014  "Adding %s->%s\n",
1015  entity_name( effect_entity( fin )),
1016  entity_name( effect_entity( fout )) );
1017  }
1018  /* Add the conflict to the list */
1019  return ( CONS( CONFLICT, c, cfs ) );
1020 }
1021 
1022 /**
1023  * @brief DD_DU detects Def/Def, Def/Use conflicts between effects FIN and FOUT.
1024  */
1025 static bool dd_du( effect fin, effect fout ) {
1026  bool conflict_p = action_write_p( effect_action( fin ));
1027 
1029  conflict_p = conflict_p && action_read_p( effect_action( fout ) );
1030  }
1031 
1032  return conflict_p;
1033 }
1034 
1035 /**
1036  * @brief UD detects Use/Def conflicts between effects FIN and FOUT.
1037  */
1038 static bool ud( effect fin, effect fout ) {
1039  return ( action_read_p( effect_action( fin ))
1041 }
1042 
1043 /**
1044  * @brief adds conflict arcs to the dependence graph dg between the in-coming
1045  * statement STIN and the out-going STOUT.
1046  * @description Note that output dependencies are not minimal
1047  * (e.g., i = s ; s = ... ; s = ...) creates an oo-dep between the i assignment
1048  * and the last s assignment.
1049  */
1050 static void add_conflicts(effect fin,
1051  statement stout,
1052  vertex vout,
1053  cons *effect_outs,
1054  bool(*which)()) {
1055  vertex vin;
1056  cons *cs = NIL;
1057 
1058  ifdebug(2) {
1059  statement stin = hash_get( effects2statement, fin );
1060  _int stin_o = statement_ordering(stin);
1061  _int stout_o = statement_ordering(stout);
1062  fprintf( stderr,
1063  "Conflicts %td (%td,%td) (%p) -> %td (%td,%td) (%p) %s"
1064  " for \"%s\"\n",
1065  statement_number(stin),
1066  ORDERING_NUMBER(stin_o),
1067  ORDERING_STATEMENT(stin_o),
1068  stin,
1069  statement_number(stout),
1070  ORDERING_NUMBER(stout_o),
1071  ORDERING_STATEMENT(stout_o),
1072  stout,
1073  ( which == ud ) ? "ud" : "dd_du",
1075  }
1076 
1077  /* To speed up pushnew_conflict() without damaging the integrity of
1078  the use-def chains */
1079  ifdebug(1) {
1080  statement stin = hash_get( effects2statement, fin );
1081  cons *effect_ins = load_statement_effects( stin );
1082  if ( !gen_once_p( effect_ins ) ) {
1083  pips_internal_error("effect_ins are redundant");
1084  }
1085  if ( !gen_once_p( effect_outs ) ) {
1086  pips_internal_error("effect_outs are redundant");
1087  }
1088  }
1089  FOREACH(EFFECT, fout, effect_outs) {
1090  ifdebug(2) {
1091  print_effect(fin);
1092  fprintf(stderr," -> ");
1093  print_effect(fout);
1094  fprintf(stderr,"\n");
1095  }
1096 
1097  // We want to check the conflict even with read/read, because we already
1098  // asserted what we want before (ud/du/dd)
1099  if((*which)(fin, fout) && effects_might_conflict_even_read_only_p(fin, fout)) {
1100  entity ein = effect_entity(fin);
1101  bool ein_abstract_location_p = entity_abstract_location_p(ein);
1102  entity eout = effect_entity(fout);
1103  bool add_conflict_p = true;
1104 
1105  /* I think that most of this is hazardous when mixes of
1106  pointers, arrays and structs are involved. However, there
1107  should be no pointer anymore with CONSTANT_PATH_EFFECTS set
1108  to TRUE! We need to think more about all of this. BC.
1109  */
1110  if(ein_abstract_location_p) {
1111 #if 0 //SG: as is, this code is equivalent to doing nothing
1112  pips_debug(2, "abstract location case \n");
1113  entity alout = variable_to_abstract_location(eout);
1114  /* this test is not correct, rout should be converted to an abstract location, not eout. BC. */
1115  if(abstract_locations_may_conflict_p(ein, alout))
1116  add_conflict_p = true;
1117 #endif
1118  } else {
1119  reference rin = effect_any_reference(fin);
1120  int din = gen_length(reference_indices(rin));
1121  reference rout = effect_any_reference(fout);
1122  int dout = gen_length(reference_indices(rout));
1123  type tin = ultimate_type(entity_type(ein));
1124  type tout = ultimate_type(entity_type(eout));
1125  if(pointer_type_p(tin) && pointer_type_p(tout)) {
1126  pips_debug(2, "pointer type case \n");
1127  /* Second version due to accuracy improvements in effect
1128  computation */
1129  if(din == dout) {
1130  /* This is the standard case */
1131  add_conflict_p = true;
1132  } else if(din < dout) {
1133  /* I'm not sure this can be the case because of
1134  * effects_might_conflict_even_read_only_p(fin, fout) */
1135  /* a write on the shorter memory access path conflicts
1136  * with the longer one. If a[i] is written, then a[i][j]
1137  * depends on it. If a[i] is read, no conflict */
1138  add_conflict_p = action_write_p(effect_action(fin));
1139  } else /* dout > din */{
1140  /* same explanation as above */
1141  add_conflict_p = action_write_p(effect_action(fout));
1142  }
1143  } else {
1144  /* Why should we limit this test to pointers? Structures,
1145  * structures of arrays and arrays of structures with
1146  * pointers embedded somewhere must behave in the very same
1147  * way. Why not unify the two cases? Because we have not
1148  * spent enough time thinking about memory access paths. */
1149  if(din < dout) {
1150  /* a write on the shorter memory access path conflicts
1151  * with the longer one. If a[i] is written, then a[i][j]
1152  * depends on it. If a[i] is read, no conflict */
1153  add_conflict_p = action_write_p(effect_action(fin));
1154  } else if(dout < din) {
1155  /* same explanation as above */
1156  add_conflict_p = action_write_p(effect_action(fout));
1157  }
1158  }
1159  }
1160 
1161  if(add_conflict_p) {
1162  pips_debug(2, "add_conflicts_p is true; checking conflicts with loop indices\n");
1163  bool remove_this_conflict_p = false;
1164  if(!ein_abstract_location_p && store_effect_p(fin)) {
1165  /* Here we filter effect on loop indices except for abstract
1166  locations */
1168  FOREACH( statement, el, loops ) {
1169  entity il = loop_index(statement_loop(el));
1170  pips_debug(2, "checking conflict with %s\n", entity_name(il));
1171  remove_this_conflict_p |= entities_may_conflict_p(ein, il);
1172  pips_debug(2, "remove_this_conflict_ p = %s\n", bool_to_string(remove_this_conflict_p));
1173  }
1174  }
1175  if(!remove_this_conflict_p) {
1176  cs = pushnew_conflict(fin, fout, cs);
1177  }
1178  }
1179  }
1180  }
1181 
1182  /* Add conflicts */
1183  if(!ENDP( cs )) {
1184  statement stin = hash_get( effects2statement, fin );
1185  vin = vertex_statement( stin );
1186 
1187  /* The sink vertex in the graph */
1189  /* Try first to find an existing vertex for this statement */
1190  FOREACH( successor, s, vertex_successors( vin ) ) {
1191  if(successor_vertex(s) == vout) {
1192  sout = s;
1193  break;
1194  }
1195  }
1196  if(successor_undefined_p(sout)) {
1197  /* There is no sink vertex for this statement, create one */
1198  sout = make_successor(make_dg_arc_label(cs), vout);
1199  vertex_successors( vin )
1200  = CONS( SUCCESSOR, sout, vertex_successors( vin ));
1201  } else {
1202  /* Use existing vertex for this statement */
1203  gen_nconc(successor_arc_label(sout), cs);
1204 
1205  }
1206  }
1207 
1208 }
1209 
1210 /**
1211  * @brief Compute from a given statement, the dependency graph.
1212  * @description Statement s is assumed "controlized", i.e. GOTO have been
1213  * replaced by unstructured.
1214  *
1215  * FIXME FI: this function is bugged. As Pierre said, you have to start with
1216  * an unstructured for the use-def chain computation to be correct.
1217  */
1219  /* Initialize some properties */
1220  one_trip_do_p = get_bool_property( "ONE_TRIP_DO" );
1221  keep_read_read_dependences_p = get_bool_property( "KEEP_READ_READ_DEPENDENCE" );
1222  mask_effects_p = get_bool_property("CHAINS_MASK_EFFECTS");
1223  dataflow_dependence_only_p = get_bool_property("CHAINS_DATAFLOW_DEPENDENCE_ONLY");
1224 
1225  /* Initialize global hashtables */
1236 
1237  /* Initialize the dg */
1238  dg = make_graph( NIL );
1239 
1240  /* Initialize data structures for all the statements
1241 
1242  It recursively initializes the sets of gens, ins and outs for
1243  the statements that appear in st. Note that not only call statements are
1244  there, but also enclosing statements (e.g, blocks and loops). */
1246 
1247  /* Compute genref phase */
1248  genref_statement( s );
1249 
1250  /* Compute inout phase and create conflicts*/
1251  inout_statement( s );
1252 
1253 #define TABLE_FREE(t) \
1254  {HASH_MAP( k, v, {set_free( (set)v ) ;}, t ) ; hash_table_free(t);}
1255 
1256  TABLE_FREE(Gen);
1257  TABLE_FREE(Ref);
1258  TABLE_FREE(Def_in);
1260  TABLE_FREE(Ref_in);
1262 
1265 
1268 
1269  return ( dg );
1270 }
1271 
1272 /* functions for effects maps */
1273 static bool rgch = false;
1274 static bool iorgch = false;
1275 
1277  instruction inst = statement_instruction( s );
1278  tag t = instruction_tag( inst );
1279  tag call_t;
1280  list le = NIL;
1281 
1282  switch ( t ) {
1283  case is_instruction_call:
1284  call_t
1286  if ( iorgch && ( call_t == is_value_code ) ) {
1287  list l_in = load_statement_in_regions( s );
1288  list l_out = load_statement_out_regions( s );
1289  le = gen_append( l_in, l_out );
1290  break;
1291  }
1292  /* else, flow thru! */
1293  _FALLTHROUGH_;
1295  /* FI: I wonder about iorgch; I would expect the same kind of
1296  stuff for the case expression, which may also hide a call to
1297  a user defined function, for instance via a for loop
1298  construct. */
1299  case is_instruction_block:
1300  case is_instruction_test:
1301  case is_instruction_loop:
1305  le = load_proper_rw_effects_list( s );
1306  break;
1307  case is_instruction_goto:
1308  pips_internal_error("Go to statement in CODE data structure %d", t );
1309  break;
1310  default:
1311  pips_internal_error("Unknown tag %d", t );
1312  }
1313 
1314  return le;
1315 }
1316 
1317 /* Select the type of effects used to compute dependence chains */
1318 static void set_effects( char *module_name, enum chain_type use ) {
1319  switch ( use ) {
1320 
1321 #ifdef HAVE_PIPS_effects_simple_LIBRARY
1322 
1323  case USE_PROPER_EFFECTS:
1324  rgch = false;
1325  iorgch = false;
1326  string pe =
1327  db_get_memory_resource( DBR_PROPER_EFFECTS, module_name, true );
1329  break;
1330 
1331 #endif // HAVE_PIPS_effects_simple_LIBRARY
1332 
1333 #ifdef HAVE_PIPS_effects_convex_LIBRARY
1334 
1335  /* In fact, we use proper regions only; proper regions of
1336  * calls are similar to regions, except for expressions given
1337  * as arguments, whose regions are simply appended to the list
1338  * (non convex hull). For simple statements (assignments),
1339  * proper regions contain the list elementary regions (there
1340  * is no summarization, i.e no convex hull). For loops and
1341  * tests, proper regions contain the elements accessed in the
1342  * tests and loop range. BC.
1343  */
1344  case USE_REGIONS:
1345  rgch = true;
1346  iorgch = false;
1347  string pr =
1348  db_get_memory_resource( DBR_PROPER_REGIONS, module_name, true );
1350  break;
1351 
1352  /* For experimental purpose only */
1353  case USE_IN_OUT_REGIONS:
1354  rgch = false;
1355  iorgch = true;
1356  /* Proper regions */
1357  string iopr = db_get_memory_resource( DBR_PROPER_REGIONS,
1358  module_name,
1359  true );
1361 
1362  /* in regions */
1363  string ir = db_get_memory_resource( DBR_IN_REGIONS, module_name, true );
1365 
1366  /* out regions */
1367  string or = db_get_memory_resource( DBR_OUT_REGIONS, module_name, true );
1369  break;
1370 
1371 #endif // HAVE_PIPS_effects_convex_LIBRARY
1372 
1373  default:
1374  pips_internal_error("ill. parameter use = %d", use );
1375  }
1376 
1377 }
1378 
1379 static void reset_effects() {
1381  if ( iorgch ) {
1382  reset_in_effects( );
1383  reset_out_effects( );
1384  }
1385 }
1386 
1387 /**
1388  * @brief Compute chain dependence for a module according different kinds of
1389  * store-like effects.
1390  *
1391  * @param module_name is the name of the module we want to compute the chains
1392  * @param use the type of effects we want to use to compute the dependence
1393  * chains
1394  *
1395  * @return true because we are very confident it works :-)
1396  */
1397 static bool chains( char * module_name, enum chain_type use ) {
1398  statement module_stat;
1399  graph module_graph;
1400  void print_graph();
1401 
1403  module_name,
1404  true ) );
1405  module_stat = get_current_module_statement( );
1407  /* set_entity_to_size(); should be performed at the workspace level */
1408 
1409  debug_on("CHAINS_DEBUG_LEVEL");
1410 
1411  pips_debug(1, "finding enclosing loops ...\n");
1413 
1414 
1415  set_effects( module_name, use );
1417 
1418  module_graph = statement_dependence_graph( module_stat );
1419 
1420  ifdebug(2) {
1421  set_ordering_to_statement( module_stat );
1422  prettyprint_dependence_graph( stderr, module_stat, module_graph );
1424  }
1425 
1426  debug_off();
1427 
1428  DB_PUT_MEMORY_RESOURCE(DBR_CHAINS, module_name, (char*) module_graph);
1429 
1430  reset_effects( );
1434 
1435  return true;
1436 }
1437 
1438 /**
1439  * @brief Phase to compute atomic chains based on proper effects (simple memory
1440  accesses)
1441  */
1442 bool atomic_chains(const string module_name) {
1444 }
1445 
1446 /**
1447  * @brief Phase to compute atomic chains based on array regions
1448  */
1449 bool region_chains(const string module_name) {
1450  return chains( module_name, USE_REGIONS );
1451 }
1452 
1453 /**
1454  * @brief Phase to compute atomic chains based on in-out array regions
1455  */
1458 }
float a2sf[2] __attribute__((aligned(16)))
USER generates a user error (i.e., non fatal) by printing the given MSG according to the FMT.
Definition: 3dnow.h:3
dg_arc_label make_dg_arc_label(list a)
Definition: dg.c:138
conflict make_conflict(effect a1, effect a2, cone a3)
Definition: dg.c:96
dg_vertex_label make_dg_vertex_label(intptr_t a1, sccflags a2)
Definition: dg.c:180
graph make_graph(list a)
Definition: graph.c:56
successor make_successor(arc_label a1, vertex a2)
Definition: graph.c:98
vertex make_vertex(vertex_label a1, list a2)
Definition: graph.c:140
static reference ref
Current stmt (an integer)
Definition: adg_read_paf.c:163
bool entity_abstract_location_p(entity al)
entity variable_to_abstract_location(entity v)
returns the smallest abstract locations containing the location of variable v.
bool abstract_locations_may_conflict_p(entity al1, entity al2)
Do these two abstract locations MAY share some real memory locations ?
chain_type
To choose the concepts used to compute dependence chains.
Definition: chains-local.h:27
@ USE_IN_OUT_REGIONS
Definition: chains-local.h:30
@ USE_REGIONS
Definition: chains-local.h:29
@ USE_PROPER_EFFECTS
Definition: chains-local.h:28
static void inout_block(_UNUSED_ statement st, cons *sts)
Propagates in sets of ST (which is inherited) to compute the out sets.
Definition: chains.c:614
static void genref_forloop(forloop l, statement st)
Compute Gen and Ref set for a "for" loop @description see genref_any_loop()
Definition: chains.c:426
#define REF_OUT(st)
Definition: chains.c:121
static bool dd_du(effect fin, effect fout)
DD_DU detects Def/Def, Def/Use conflicts between effects FIN and FOUT.
Definition: chains.c:1025
#define TABLE_FREE(t)
static void genref_any_loop(statement body, statement st, list locals, _UNUSED_ bool one_trip_do_p)
Compute Gen and Ref set for any loop (do, for, while,...) @description It has to deal specially with ...
Definition: chains.c:372
static void genref_test(test t, statement s)
Compute Gen and Ref set for a test.
Definition: chains.c:310
static void inout_any_loop(statement st, statement body, bool one_trip_do_p, bool __attribute__((unused)) never_executed_p)
Propagates in sets of ST (which is inherited) to compute the out sets.
Definition: chains.c:673
static hash_table Vertex_statement
Vertex_statement maps each statement to its vertex in the dependency graph.
Definition: chains.c:127
graph statement_dependence_graph(statement s)
Compute from a given statement, the dependency graph.
Definition: chains.c:1218
static vertex vertex_statement(statement st)
Definition: chains.c:159
static void mask_effects(set s, list l)
MASK_EFFECTS masks the effects in S according to the locals L.
Definition: chains.c:331
static cons * pushnew_conflict(effect fin, effect fout, cons *cfs)
adds the conflict FIN->FOUT in the list CFS @description adds the conflict FIN->FOUT in the list CFS ...
Definition: chains.c:993
bool region_chains(const string module_name)
Phase to compute atomic chains based on array regions.
Definition: chains.c:1449
static void set_effects(char *module_name, enum chain_type use)
Select the type of effects used to compute dependence chains.
Definition: chains.c:1318
#define INIT_STATEMENT_SIZE
Default sizes for corresponding sets.
Definition: chains.c:85
#define DEF_OUT(st)
Definition: chains.c:111
static bool chains(char *module_name, enum chain_type use)
Compute chain dependence for a module according different kinds of store-like effects.
Definition: chains.c:1397
static void inout_call(statement st, call __attribute__((unused)) c)
Propagates in sets of ST (which is inherited) to compute the out sets.
Definition: chains.c:746
static void kill_effects(set gen, set killers)
The genref_xxx functions implement the computation of GEN and REF sets from Aho, Sethi and Ullman "Co...
Definition: chains.c:244
static void local_print_statement_set(string msg, set s)
Access functions for debug only.
Definition: chains.c:144
static void inout_control()
static bool init_one_statement(statement st)
Initializes the global data structures needed for usedef computation of one statement.
Definition: chains.c:172
static bool rgch
functions for effects maps
Definition: chains.c:1273
static bool dataflow_dependence_only_p
Definition: chains.c:133
static void inout_unstructured(statement st, unstructured u)
Propagates in sets of ST (which is inherited) to compute the out sets.
Definition: chains.c:762
static void genref_block(cons *sts, statement st)
Compute Gen and Ref set for a block @description The Dragon book only deals with a sequence of two st...
Definition: chains.c:460
static void genref_unstructured(unstructured u, statement st)
Compute Gen and Ref set for an unstructured @description computes the gens, refs, and kills set of th...
Definition: chains.c:494
static void genref_whileloop(whileloop l, statement st)
Compute Gen and Ref set for a "while" loop @description see genref_any_loop()
Definition: chains.c:442
static hash_table Def_out
Def_out maps each statement to the statements that are out-coming the statement It's only used for un...
Definition: chains.c:110
static list load_statement_effects(statement s)
Definition: chains.c:1276
#define GEN(st)
Definition: chains.c:93
static hash_table Ref_in
Ref_in maps each statement to the effects that are in-coming the statement It's only used for unstruc...
Definition: chains.c:115
static void genref_loop(loop l, statement st)
Compute Gen and Ref set for a "do" loop @description see genref_any_loop()
Definition: chains.c:403
static hash_table effects2statement
Mapping from effects to the associated statement.
Definition: chains.c:89
bool in_out_regions_chains(const string module_name)
Phase to compute atomic chains based on in-out array regions.
Definition: chains.c:1456
static hash_table Def_in
Def_in maps each statement to the statements that are in-coming the statement It's only used for unst...
Definition: chains.c:105
static set current_defs
current_defs is the set of DEF at the current point of the computation
Definition: chains.c:100
static void inout_whileloop(statement st, whileloop wl)
Propagates in sets of ST (which is inherited) to compute the out sets.
Definition: chains.c:724
static void add_conflicts(effect fin, statement stout, vertex vout, cons *effect_outs, bool(*which)())
adds conflict arcs to the dependence graph dg between the in-coming statement STIN and the out-going ...
Definition: chains.c:1050
static void inout_loop(statement st, loop lo)
Propagates in sets of ST (which is inherited) to compute the out sets.
Definition: chains.c:710
static void inout_forloop(statement st, forloop fl)
Propagates in sets of ST (which is inherited) to compute the out sets.
Definition: chains.c:735
static set current_refs
Definition: chains.c:101
#define MAKE_STATEMENT_SET()
Macro to create set.
Definition: chains.c:81
static hash_table Gen
Gen maps each statement to the effects it generates.
Definition: chains.c:92
static void inout_statement()
static bool iorgch
Definition: chains.c:1274
static void genref_one_statement(statement st)
Compute Gen and Ref set for a single statement.
Definition: chains.c:276
static hash_table Ref
Refs maps each statement to the effects it references.
Definition: chains.c:96
static void genref_statement()
static void inout_test(_UNUSED_ statement s, test t)
Propagates in sets of ST (which is inherited) to compute the out sets.
Definition: chains.c:629
static hash_table Ref_out
Ref_out maps each statement to the effects that are out-coming the statement It's only used for unstr...
Definition: chains.c:120
static bool mask_effects_p
Definition: chains.c:132
#define DEF_IN(st)
Definition: chains.c:106
#define REF(st)
Definition: chains.c:97
#define REF_IN(st)
Definition: chains.c:116
void * arc_label
– usedef.c
Definition: chains.c:43
void * vertex_label
Definition: chains.c:44
static void reset_effects()
Some forward declarations.
Definition: chains.c:1379
static bool ud(effect fin, effect fout)
UD detects Use/Def conflicts between effects FIN and FOUT.
Definition: chains.c:1038
static void genref_instruction(instruction i, statement st)
Does the dispatch and recursion loop @description.
Definition: chains.c:530
bool atomic_chains(const string module_name)
Phase to compute atomic chains based on proper effects (simple memory accesses)
Definition: chains.c:1442
static bool keep_read_read_dependences_p
Definition: chains.c:131
static bool one_trip_do_p
Some properties.
Definition: chains.c:130
static graph dg
dg is the dependency graph ; FIXME : should not be static global ?
Definition: chains.c:124
static list loops
#define sccflags_undefined
Definition: dg.h:247
#define CONFLICT(x)
CONFLICT.
Definition: dg.h:134
#define cone_undefined
Definition: dg.h:104
struct _newgen_struct_vertex_ * vertex
Definition: dg.h:28
list load_proper_rw_effects_list(statement)
void reset_out_effects(void)
void reset_proper_rw_effects(void)
void set_proper_rw_effects(statement_effects)
void set_out_effects(statement_effects)
void set_in_effects(statement_effects)
void reset_in_effects(void)
list load_statement_out_regions(statement)
list load_statement_in_regions(statement)
#define effect_any_reference(e)
FI: cannot be used as a left hand side.
#define effect_exact_p(eff)
entity effect_entity(effect)
cproto-generated files
Definition: effects.c:52
bool store_effect_p(effect)
Definition: effects.c:1062
bool effect_scalar_p(effect)
Definition: effects.c:567
entity effect_to_entity(effect)
Returns the entity corresponding to the mutation.
Definition: effects.c:1413
#define effect_action(x)
Definition: effects.h:642
#define action_write_p(x)
Definition: effects.h:314
#define action_read_p(x)
Definition: effects.h:311
#define EFFECT(x)
EFFECT.
Definition: effects.h:608
const char * module_name(const char *s)
Return the module part of an entity name.
Definition: entity_names.c:296
bool get_bool_property(const string)
FC 2015-07-20: yuk, moved out to prevent an include cycle dependency include "properties....
#define gen_recurse(start, domain_number, flt, rwt)
Definition: genC.h:283
#define successor_vertex(x)
Definition: graph.h:118
#define successor_undefined
Definition: graph.h:92
#define successor_arc_label(x)
Definition: graph.h:116
#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
#define successor_undefined_p(x)
Definition: graph.h:93
bool entities_may_conflict_p(entity e1, entity e2)
Check if two entities may conflict.
Definition: conflicts.c:984
bool first_exact_scalar_effect_certainly_includes_second_effect_p(effect eff1, effect eff2)
Definition: conflicts.c:1074
bool effects_might_conflict_even_read_only_p(effect eff1, effect eff2)
Check if two effect might conflict, even if they are read only @description Two effects may conflict ...
Definition: conflicts.c:123
void set_conflict_testing_properties()
conflicts.c
Definition: conflicts.c:68
bool effect_may_read_or_write_memory_paths_from_entity_p(effect ef, entity e)
misc functions
Definition: conflicts.c:1103
#define CONTROL_MAP(ctl, code, c, list)
Macro to walk through all the controls reachable from a given control node of an unstructured.
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
statement set_current_module_statement(statement)
Set the current module statement.
Definition: static.c:165
statement get_current_module_statement(void)
Get the current module statement.
Definition: static.c:208
entity set_current_module_entity(entity)
static.c
Definition: static.c:66
void gen_null(__attribute__((unused)) void *unused)
Ignore the argument.
Definition: genClib.c:2752
bool loop_executed_never_p(loop l)
Check if loop bound are constant and then if upper < lower.
Definition: loop.c:971
bool loop_executed_at_least_once_p(loop l)
Check if loop bound are constant and then if upper >= lower.
Definition: loop.c:937
void clean_enclosing_loops(void)
Definition: loop.c:58
statement_mapping loops_mapping_of_statement(statement stat)
Definition: loop.c:155
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
#define NIL
The empty list (nil in Lisp)
Definition: newgen_list.h:47
list gen_copy_seq(list l)
Copy a list structure.
Definition: list.c:501
size_t gen_length(const list l)
Definition: list.c:150
bool gen_once_p(list l)
FC: ARGH...O(n^2)!
Definition: list.c:758
#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
void gen_free_list(list l)
free the spine of the list
Definition: list.c:327
#define FOREACH(_fe_CASTER, _fe_item, _fe_list)
Apply/map an instruction block on all the elements of a list.
Definition: newgen_list.h:179
#define MAPL(_map_list_cp, _code, _l)
Apply some code on the addresses of all the elements of a list.
Definition: newgen_list.h:203
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
loop statement_loop(statement)
Get the loop of a statement.
Definition: statement.c:1374
string statement_identification(statement)
Like external_statement_identification(), but with internal information, the hexadecimal address of t...
Definition: statement.c:1700
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
#define debug_on(env)
Definition: misc-local.h:157
#define _UNUSED_
Definition: misc-local.h:232
#define pips_debug
these macros use the GNU extensions that allow variadic macros, including with an empty list.
Definition: misc-local.h:145
#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 exit(code)
Definition: misc-local.h:54
#define _FALLTHROUGH_
Definition: misc-local.h:238
void debug(const int the_expected_debug_level, const char *calling_function_name, const char *a_message_format,...)
ARARGS0.
Definition: debug.c:189
string bool_to_string(bool)
Definition: string.c:243
@ hash_pointer
Definition: newgen_hash.h:32
#define HASH_UNDEFINED_VALUE
value returned by hash_get() when the key is not found; could also be called HASH_KEY_NOT_FOUND,...
Definition: newgen_hash.h:56
set set_del_element(set, const set, const void *)
Definition: set.c:265
set set_assign(set, const set)
Assign a set with the content of another set.
Definition: set.c:129
bool set_equal_p(const set, const set)
returns whether s1 == s2
Definition: set.c:316
set set_difference(set, const set, const set)
Definition: set.c:256
#define SET_FOREACH(type_name, the_item, the_set)
enumerate set elements in their internal order.
Definition: newgen_set.h:78
void set_free(set)
Definition: set.c:332
set set_clear(set)
Assign the empty set to s s := {}.
Definition: set.c:326
set set_union(set, const set, const set)
Definition: set.c:211
@ set_pointer
Definition: newgen_set.h:44
#define set_undefined_p(s)
Definition: newgen_set.h:49
set set_dup(const set)
Definition: set.c:143
set set_make(set_type)
Create an empty set of any type but hash_private.
Definition: set.c:102
set set_add_element(set, const set, const void *)
Definition: set.c:152
int tag
TAG.
Definition: newgen_types.h:92
intptr_t _int
_INT
Definition: newgen_types.h:53
int f(int off1, int off2, int n, float r[n], float a[n], float b[n])
Definition: offsets.c:15
hash_table set_ordering_to_statement(statement s)
To be used instead of initialize_ordering_to_statement() to make sure that the hash table ots is in s...
Definition: ordering.c:172
void reset_ordering_to_statement(void)
Reset the mapping from ordering to statement.
Definition: ordering.c:185
#define print_effect(e)
Definition: print.c:336
#define print_effects(e)
Definition: print.c:334
static statement gen(int what, entity src, entity trg, entity lid, entity proc, entity(*create_src)(), entity(*create_trg)(), Psysteme sr, list ldiff)
arguments: all that may be useful to generate some code
Definition: remapping.c:498
#define instruction_block_p(i)
#define ORDERING_NUMBER(o)
#define ORDERING_STATEMENT(o)
#define unstructured_control
After the modification in Newgen: unstructured = entry:control x exit:control we have create a macro ...
#define is_instruction_block
soft block->sequence transition
#define instruction_block(i)
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
type ultimate_type(type)
Definition: type.c:3466
list load_statement_enclosing_loops(statement)
bool pointer_type_p(type)
Check for scalar pointers.
Definition: type.c:2993
void set_enclosing_loops_map(statement_mapping)
#define value_tag(x)
Definition: ri.h:3064
#define loop_body(x)
Definition: ri.h:1644
#define call_function(x)
Definition: ri.h:709
#define control_predecessors(x)
Definition: ri.h:943
#define instruction_loop(x)
Definition: ri.h:1520
#define statement_ordering(x)
Definition: ri.h:2454
#define test_false(x)
Definition: ri.h:2837
#define statement_domain
newgen_sizeofexpression_domain_defined
Definition: ri.h:362
@ is_value_code
Definition: ri.h:3031
#define CONTROL(x)
CONTROL.
Definition: ri.h:910
@ is_instruction_goto
Definition: ri.h:1473
@ is_instruction_unstructured
Definition: ri.h:1475
@ is_instruction_whileloop
Definition: ri.h:1472
@ is_instruction_expression
Definition: ri.h:1478
@ is_instruction_test
Definition: ri.h:1470
@ is_instruction_call
Definition: ri.h:1474
@ is_instruction_forloop
Definition: ri.h:1477
@ is_instruction_loop
Definition: ri.h:1471
#define instruction_tag(x)
Definition: ri.h:1511
#define entity_name(x)
Definition: ri.h:2790
#define test_true(x)
Definition: ri.h:2835
#define reference_indices(x)
Definition: ri.h:2328
#define instruction_forloop(x)
Definition: ri.h:1538
#define unstructured_exit(x)
Definition: ri.h:3006
#define loop_locals(x)
Definition: ri.h:1650
#define instruction_expression(x)
Definition: ri.h:1541
#define instruction_whileloop(x)
Definition: ri.h:1523
#define whileloop_body(x)
Definition: ri.h:3162
#define statement_declarations(x)
Definition: ri.h:2460
#define statement_instruction(x)
Definition: ri.h:2458
#define instruction_call(x)
Definition: ri.h:1529
#define control_statement(x)
Definition: ri.h:941
#define instruction_test(x)
Definition: ri.h:1517
#define entity_type(x)
Definition: ri.h:2792
#define statement_number(x)
Definition: ri.h:2452
#define forloop_body(x)
Definition: ri.h:1372
#define instruction_unstructured(x)
Definition: ri.h:1532
#define loop_index(x)
Definition: ri.h:1640
#define entity_initial(x)
Definition: ri.h:2796
void prettyprint_dependence_graph(FILE *, statement, graph)
Print all edges and arcs.
Definition: util.c:177
int fprintf()
test sc_min : ce test s'appelle par : programme fichier1.data fichier2.data ...
#define ifdebug(n)
Definition: sg.c:47
FI: I do not understand why the type is duplicated at the set level.
Definition: set.c:59
The structure used to build lists in NewGen.
Definition: newgen_list.h:41
@ empty
b1 < bj -> h1/hj = empty
Definition: union-local.h:64