PIPS
isolate_statement.c
Go to the documentation of this file.
1 /*
2  Copyright 1989-2016 MINES ParisTech
3 
4  This file is part of PIPS.
5 
6  PIPS is free software: you can redistribute it and/or modify it
7  under the terms of the GNU General Public License as published by
8  the Free Software Foundation, either version 3 of the License, or
9  any later version.
10 
11  PIPS is distributed in the hope that it will be useful, but WITHOUT ANY
12  WARRANTY; without even the implied warranty of MERCHANTABILITY or
13  FITNESS FOR A PARTICULAR PURPOSE.
14 
15  See the GNU General Public License for more details.
16 
17  You should have received a copy of the GNU General Public License
18  along with PIPS. If not, see <http://www.gnu.org/licenses/>.
19 
20 */
21 
22 /**
23  * @file isolate_statement.c
24  * transfer statement to isolate memory
25  * @author Serge Guelton <serge.guelton@enst-bretagne.fr>
26  * @date 2010-05-01
27  */
28 #ifdef HAVE_CONFIG_H
29 #include "pips_config.h"
30 #endif
31 #include <ctype.h>
32 
33 #include "genC.h"
34 #include "linear.h"
35 
36 #include "ri.h"
37 #include "effects.h"
38 
39 #include "misc.h"
40 #include "properties.h"
41 
42 #include "ri-util.h"
43 #include "workspace-util.h"
44 #include "effects-util.h"
45 
46 #include "pipsdbm.h"
47 
48 // for AddEntityToModuleCompilationUnit
49 #include "preprocessor.h"
50 
51 #include "conversion.h"
52 
53 // for module_reorder
54 #include "control.h"
55 
56 #include "effects-generic.h"
57 // for print_effect (one debug):
58 #include "effects-simple.h"
59 #include "effects-convex.h" // used
60 #include "semantics.h" // used
61 #include "callgraph.h" // used
62 
63 #include "accel-util.h"
64 
65 /**
66  * isolate_statement
67  */
68 
69 struct dma_pair {
72 };
73 
74 
75 /* Some constant intended to have a more readable code */
76 // unused: static const int dmaScalar = 0;
77 static const int dma1D = 1;
78 
79 static size_t get_dma_dimension(region reg_from) {
80  /* It should be the number of variable phis and stop at first field*/
81  size_t n=0;
86  if(variable_phi_p(var) ) {
87  ++n;
88  }
89  else {
90  pips_assert("not a phi means a field",entity_field_p(var));
91  break;
92  }
93  }
94  }
95  return n;
96 }
97 
98 /**
99  * converts a region_to_dma_switch to corresponding dma name
100  * according to properties
101  */
102 static const char* get_dma_name(enum region_to_dma_switch m, size_t d) {
103  const char *seeds[] = {
104  "KERNEL_LOAD_STORE_LOAD_FUNCTION",
105  "KERNEL_LOAD_STORE_STORE_FUNCTION",
106  "KERNEL_LOAD_STORE_ALLOCATE_FUNCTION",
107  "KERNEL_LOAD_STORE_DEALLOCATE_FUNCTION"
108  };
109  const char * propname = seeds[(int)m];
110  /* If the DMA is not scalar, the DMA function name is in the property
111  of the form KERNEL_LOAD_STORE_LOAD/STORE_FUNCTION_dD: */
112  char * apropname= NULL;
113  if(d > 0 /* not scalar*/ && (int)m < 2)
114  asprintf(&apropname,"%s_%dD", seeds[(int)m], (int)d);
115  const char* dmaname = get_string_property(apropname?apropname:propname);
116  if(apropname) free(apropname);
117  return dmaname;
118 }
119 
120 #if 0
121 /*
122  * Build a fake region and try to build dimensions from it
123  */
124 static bool declaration_region_to_dimensions(effect reg,
125  transformer tr,
126  list *dimensions,
127  list * offsets,
128  expression *condition) {
129  pips_assert("effects are regions\n", effect_region_p(reg));
130  bool success_p=true;
131 
132  /* Apply partial eval on the declaration, better chance to get a
133  * "usable" region
134  */
135  effects dummy_effect = make_effects(NIL);
140  dummy_effect);
142  free_effects(dummy_effect);
143 
144  /* Create a new region corresponding to the declaration dimensions */
145  effect decl_region = region_dup(reg);
147 
148  /* Try again to compute the dimensions, based on the array declaration
149  * Mehdi: I don't understand why we want to use a "region" to do that ?
150  */
152  tr,
153  dimensions,
154  offsets,
155  true,
156  condition)) {
157  success_p = false;
158  pips_user_warning("failed to compute DMA from the array declaration based region\n");
159  ifdebug(4) {
160  pips_user_warning("Original Region:");
161  print_region(decl_region);
162  pips_user_warning("Declaration based Region:");
163  print_region(decl_region);
164  pips_user_warning("Entity is :");
166  }
167  }
168  region_free(decl_region);
169  return success_p;
170 }
171 #endif
172 
173 
174 // Build DMA dimensions directly from the entity declaration
175 static bool declarations_to_dimensions(entity e, list *dimensions, list * offsets) {
176  if(!entity_array_p(e)) {
177  return false;
178  }
179 
180  // Populate "dimensions" and "offsets" by looking to the declaration
182  FOREACH(dimension, d, ldim) {
183  // FIXME Unsure who cares about the free....
184  dimension d_dup = copy_dimension(d);
185  expression dl = dimension_lower(d);
186 
187  // Check if we have an offset (impossible in C!)
189  bool dl_is_int_p=expression_integer_value(dl,&offset);
190  pips_assert("lower bound is int",dl_is_int_p);
191  if(offset!=0) {
192  pips_internal_error("We shouldn't have an offset in the array declaration"
193  ", are you using Fortran?");
194  }
195 
196  *dimensions = CONS(DIMENSION, d_dup, *dimensions );
197  *offsets = CONS(EXPRESSION, dl, *offsets);
198  }
199  return true;
200 
201 }
202 
203 
204 void region_to_dimensions(effect reg, transformer tr, list *dimensions, list * offsets, expression *condition) {
205  pips_assert("effects are regions\n",effect_region_p(reg));
206  if( ! region_to_minimal_dimensions(reg,tr,dimensions,offsets,true,condition) ) {
207  pips_user_warning("failed to convert regions to minimal array dimensions, using whole array instead\n");
208 
209  bool success_p = false;
210  // Try using a region based on the declaration (Old way)
211  //success_p=declaration_region_to_dimensions(reg,tr,dimensions,offsets,condition);
212 
213  // Use directly the dimensions from the declaration without building a region!
215  success_p=declarations_to_dimensions(e, dimensions, offsets);
216 
217  if(!success_p) {
218  // Don't know how to recover from that...
219  pips_internal_error("Abort");
220  }
221  }
222 }
223 
224 
226  bool is_fortran = fortran_module_p(get_current_module_entity());
227  int indice_first = (is_fortran == true) ? 1 : 0;
230  pips_assert("region indices only contain references",expression_reference_p(exp));
232  entity var =reference_variable(expr);
233  if(variable_phi_p(var)) {
234  expression index = int_to_expression(indice_first);
235  if(expression_reference_p(address)) {
238  make_expression_list(index));
239  }
240  else
241  address= make_expression(
243  make_subscript(address,make_expression_list(index))
244  )
245  ,
247  );
248  }
249  else {
250  address= MakeBinaryCall(
252  address,
254  );
255  }
256  }
257  expression result;
260  address);
261  else
263  address);
264  return result;
265 }
266 
267 /* generate an expression of the form
268  * sizeof(typeof(variable[indices]))
269  *
270  * It also handles the fields:
271  * fields reference are converted to proper expression
272  * then an approximation is made to ensure there is no stride
273  * e.g
274  * struct { int x,y; } a [10];
275  * a[1][x] -> sizeof(a[1])
276  * struct { int x[10], y[10] } a;
277  * a[x][1] -> sizeof(a.x)
278  */
279 
281  expression sizeof_exp;
283 
285 
286  /* extract the constant indices of the region */
288  pips_assert("region indices are only references",expression_reference_p(exp)) ;
291  if(entity_field_p(var)) {
292  break;
293  }
294  else if(variable_phi_p(var)) {
296  }
297  else pips_internal_error("not a field and not a phi variable ?");
298  }
300 
302  NIL,
303  NIL));
304 
305  /* Here we make a special case for struct because of nvcc/C++ doesn't like construct like :
306  * sizeof(struct {data_t latitude; data_t longitude; data_t stock;})
307  * so we produce a sizeof(var); instead
308  */
309  if(type_struct_variable_p(element_type)) {
311  sizeof_exp = MakeSizeofExpression(exp);
312  free_type(element_type);
313  } else {
314  sizeof_exp = MakeSizeofType(element_type);
315  }
316  return sizeof_exp;
317 }
318 
320  /* We may skip the size of the first dimension since it is not
321  used in address calculation. But since it depends of Fortran
322  or C in the runtime, postpone this micro-optimization... */
323  reference r =region_any_reference(reg_from);
324  entity from = reference_variable(r);
326  list dims = variable_dimensions(from_tv);
327  list out=NIL;
329  pips_assert("a region only contains references", expression_reference_p(exp));
331  entity var = reference_variable(rexp);
332  if(variable_phi_p(var)) {
333  /* we are in trouble, as we don't know anything about the size of the underlying array. It is the fist dimension, so not very important anyway ... except for FORTRAN :-( But there are no pointer in FORTRAN :p */
334  if(ENDP(dims) && basic_pointer_p(variable_basic(from_tv))) {
335  pips_assert("no pointer in fortran", c_module_p(get_current_module_entity()));
337  Psysteme sc_reg = sc_dup(region_system(reg_from));
338  sc_transform_eg_in_ineg(sc_reg);
339  Pcontrainte lower,upper;
341  &sc_inegalites(sc_reg), &lower, &upper);
342  if( !CONTRAINTE_UNDEFINED_P(upper))
343  {
345  }
346  else {
347  pips_internal_error("Should not happen at this point, should it ?");
348  }
349 
351  make_dimension(int_to_expression(0), eupper, NIL),
352  out);
354  dims = variable_dimensions(from_tv);
355  }
356  else {
357  pips_assert("some dims stacked", !ENDP(dims));
359  POP(dims);
360  }
361  }
362  else if(entity_field_p(var)) {
363  break;
364  }
365  }
366  return gen_nreverse(out);
367 }
368 
369 /**
370  * converts dimensions to a dma call from a memory @a from to another memory @a to
371  *
372  * @param from expression giving the adress of the input memory
373  * @param to expression giving the adress of the output memory
374  * @param ld list of dimensions to analyze
375  * @param m kind of call to generate
376  *
377  * @return
378  */
380  entity to,
381  list/*of dimensions*/ ld,
382  list/*of offsets*/ lo,
383  enum region_to_dma_switch m)
384 {
386  expression dest;
387  list args = NIL;
388  const char* function_name = get_dma_name(m,get_dma_dimension(reg_from));
389 
390  entity mcpy = module_name_to_entity(function_name);
391  if (entity_undefined_p(mcpy)) {
393  pips_user_warning("Cannot find \"%s\" method. Are you sure you have set\n"
394  "KERNEL_LOAD_STORE_..._FUNCTION "
395  "to a defined entity and added the correct .c file?\n",function_name);
396  }
399  } else
401 
402  /* Scalar detection: */
403  bool scalar_entity = entity_scalar_p(from);
404 
405  if (dma_allocate_p(m)) {
406  /* Need the address for the allocator to modify the pointer itself: */
408  /* Generate a "void **" type: */
409  type voidpp = make_type_variable(
416  ),
417  NIL,NIL
418  )
419  )
420  ),
421  NIL,NIL
422  )
423  );
424  /* dest = "(void **) &to" */
425  dest = make_expression(
427  make_cast(voidpp,dest)
428  ),
430  }
431  else if (!dma_deallocate_p(m) && !scalar_entity)
432  /* Except for the deallocation or if we have a scalar and then we have
433  already created a pointer to it, the original array is referenced
434  through pointer dereferencing: */
437  else
438  dest=entity_to_expression(to);
439 
440 
441  switch(m) {
442  case dma_deallocate:
443  args = make_expression_list(dest);
444  break;
445  case dma_allocate:
446  {
447  expression sizeof_exp = get_sizeofexpression_for_region(reg_from);
448 
449  /* sizeof(element)*number elements of the array: */
450  expression transfer_size = SizeOfDimensions(ld);
451  transfer_size=MakeBinaryCall(
453  sizeof_exp,
454  transfer_size);
455 
456  args = make_expression_list(dest, transfer_size);
457  } break;
458  case dma_load:
459  case dma_store:
460  /* Generate communication functions: */
461  {
462  //if(!scalar_entity) {
463  /* Build the sizes of the array block to transfer: */
464  list /*of expressions*/ transfer_sizes = NIL;
465  FOREACH(DIMENSION,d,ld) {
466  expression transfer_size=
467  SizeOfDimension(d);
468  transfer_sizes=CONS(EXPRESSION,transfer_size,transfer_sizes);
469  }
470  transfer_sizes=gen_nreverse(transfer_sizes);
471 
472  /* Build the sizes of the array with element to transfer: */
473  list/* of expressions*/ from_dims = NIL;
474  list vardims = variable_to_dimensions(reg_from);
475  FOREACH(DIMENSION,d, vardims) {
476  from_dims=CONS(EXPRESSION,SizeOfDimension(d),from_dims);
477  }
478  gen_full_free_list(vardims);
479  from_dims=gen_nreverse(from_dims);
480 
481  /* Build the offsets of the array block to transfer: */
482  list/* of expressions*/ offsets = NIL;
483  FOREACH(EXPRESSION,e,lo)
484  offsets=CONS(EXPRESSION,e,offsets);
485  offsets=gen_nreverse(offsets);
486  /* Use a special transfert function for scalars instead of reusing
487  the 1D function. It may useful for example if it is implemented
488  as a FIFO at the hardware level: */
489  //} else {
490  // /* If we have a scalar variable to transfert, generate
491  // synthetic transfer parameters: */
492  // /* 1 element to transfert */
493  // transfer_sizes = make_expression_list(int_to_expression(1));
494  // /* 1 dimension */
495  // from_dims = make_expression_list(int_to_expression(1));
496  // /* At the begining of the « array »: */
497  // offsets = make_expression_list(int_to_expression(0));
498  // }
499 
500  expression source = region_to_address(reg_from);
501  /* Generate host and accel adresses: */
502  args = CONS(EXPRESSION,source,CONS(EXPRESSION,dest,NIL));
503  //if(dma_load_p(m))
504  // args=gen_nreverse(args);
505  /* Output parameters in an order compatible with some C99
506  implementation of the runtime: size and block size first, so
507  that some arguments can be defined with them: */
508  /* Insert offset: */
509  args = gen_append(offsets, args);
510  /* Insert the block size to transfert: */
511  args = gen_append(transfer_sizes, args);
512  /* Insert the array sizes: */
513  args = gen_append(from_dims, args);
514  /* Insert the element size expression: */
515  expression sizeof_exp = get_sizeofexpression_for_region(reg_from);
516  args = CONS(EXPRESSION,
517  sizeof_exp,
518  args);
519  } break;
520  default:
521  pips_internal_error("should not happen");
522  }
523  return make_call(mcpy, args);
524 }
525 
526 /* perform the convex hull between r0 and r1, and merge them if they have a common prefix
527  * e.g. a[phi1].re[phi2] U_ex a[phi3].im[phi4] = a[phi1] U_may a[phi3]
528  */
529 static
533  list n0 = NIL, n1=NIL;
534  while(!ENDP(i0)&&!ENDP(i1)) {
535  expression e0 = EXPRESSION(CAR(i0)),
536  e1 = EXPRESSION(CAR(i1));
537  // stop there: we have found the common prefix
540  n0=gen_nreverse(n0);
541  n1=gen_nreverse(n1);
547  region_approximation_tag(out)=is_approximation_may; // better pessimistic than nothing.
550  gen_free_list(n0);
551  gen_free_list(n1);
552  return out;
553  }
554  // else keep on pushing
555  n0=CONS(EXPRESSION,e0,n0);
556  n1=CONS(EXPRESSION,e1,n1);
557  POP(i0);
558  POP(i1);
559  }
560  gen_free_list(n0);
561  gen_free_list(n1);
562  return regions_must_convex_hull(r0, r1);
563 
564 }
565 
566 /* Compute a call to a DMA function from the effects of a statement
567 
568  @param[in] stat is the statement we want to generate communication
569  operations for
570  @param[in] prefix is the prefix to be used for added variable.
571  operations for
572 
573  @return a statement of the DMA transfers or statement_undefined if
574  nothing is needed or if the dma function has been set
575  to "" in the relevant property
576 
577  If this cannot be done, it throws a pips_user_error
578  */
579  static
581  enum region_to_dma_switch s,
582  hash_table e2e, expression * condition,
583  bool fine_grain_analysis, const char* prefix,
584  const char* suffix)
585 {
586  /* if no dma is provided, skip the computation
587  * it is used for scalope at least */
589  return statement_undefined;
590 
591  /* work on a copy because we compute the rectangular hull in place
592  and keep only store effects: we do not care for environment effects here (BC)
593  */
595  list rw_effects = gen_full_copy_list(l_eff_tmp);
596  gen_free_list(l_eff_tmp); /* free the spine, as effects are shared with the database */
598 
599  /* ensure we only have a rectangular region
600  * as a side effect, strided accesses are handled by region_rectangular_hull
601  */
602  for(list iter = rw_effects;!ENDP(iter);POP(iter)) {
603  region *tmp = (region*)REFCAR(iter);
604  region new = region_rectangular_hull(*tmp,true);
605  // free_effect(*tmp); SG: why does this lead to a segfault ?
606  // I find no sharing in region_rectangular_hull
607  *tmp=new;
608  }
609 
610  /* merge copy in and copy out for allocation
611  * this is entity-based, we could do a better job if we were reference-based
612  */
613  if (dma_allocate_p(s) || dma_deallocate_p(s)) {
614  list out = NIL;
615  set visited_entities = set_make(set_pointer);
616  FOREACH(EFFECT,self,rw_effects) {
618  if(!set_belong_p(visited_entities,svar)) {
619  set_add_element(visited_entities, visited_entities, svar);
620  FOREACH(EFFECT,other, rw_effects) {
621  if(self!=other) {
623  if(same_entity_p(svar,ovar)) {
624  effect etmp = extended_regions_must_convex_hull(self,other);
625  if(region_write_p(other))
626  region_action(etmp) = copy_action(region_action(other));
627  //free_effect(self);
628  self=etmp;
629  }
630  }
631  }
632  out=CONS(EFFECT,self,out);
633  }
634  }
635  set_free(visited_entities);
636  gen_free_list(rw_effects);
637  rw_effects=gen_nreverse(out);
638  }
639  /* merge regions with same prefix but different suffixes (in presence of fields ...) */
640  if (dma_load_p(s) || dma_store_p(s) || dma_allocate_p(s) ) {
641  list out = NIL;
642  set r_visited_entities = set_make(set_pointer);
643  set w_visited_entities = set_make(set_pointer);
644  FOREACH(EFFECT,self, rw_effects) {
646  enum action_utype sa = action_tag(region_action(self));
647  set this = is_action_read ==sa ? r_visited_entities : w_visited_entities;
648  if(!set_belong_p(this ,svar)) {
649  set_add_element(this, this, svar);
650  FOREACH(EFFECT,other,rw_effects) {
651  if(self!=other) {
653  if(same_entity_p(svar,ovar) && (sa == action_tag(region_action(other))) ) {
654  effect etmp = extended_regions_must_convex_hull(self,other);
655  //free_effect(self);
656  self=etmp;
657  }
658  }
659  }
660  out=CONS(EFFECT,self,out);
661  }
662  }
663  set_free(r_visited_entities);
664  set_free(w_visited_entities);
665  gen_free_list(rw_effects);
666  rw_effects=gen_nreverse(out);
667  }
668 
669  /* SG: to do: merge convex hulls when they refer to *all* fields of a region
670  * to do this, according to BC, I should iterate over all regions,
671  * detect fields and then iterate again over regions to find combinable regions
672  * that way I would not generate needless read effects when all fields are accessed using the same pattern
673  *
674  * some more dev I am not willing to do right now :)
675  */
676 
677 
678  list effects = NIL;
679 
680  /* filter out relevant effects depending on operation mode */
681  FOREACH(EFFECT,e,rw_effects) {
682  if ((dma_load_p(s) || dma_allocate_p(s) || dma_deallocate_p(s))
685  else if ((dma_store_p(s) || dma_allocate_p(s) || dma_deallocate_p(s))
688  }
690 
691 
692  /* if we failed to provide a fine_grain_analysis, we can still rely on the definition region to over approximate the result
693  */
694  if(!fine_grain_analysis) {
695  FOREACH(EFFECT,eff,rw_effects) {
697  && ! std_file_effect_p(eff)) {
698  print_effect(eff);
699  pips_user_error("pointers wreak havoc with isolate_statement\n");
700  }
701  descriptor d = effect_descriptor(eff);
702  if(descriptor_convex_p(d)) {
703  Psysteme sc_old = descriptor_convex(d);
707  sc_old=sc_normalize2(sc_old);
709  if(!sc_equal_p(sc_old,sc_new)) {
710  sc_free(sc_old);
713  }
714  }
715  }
716  }
717 
718  /* handle the may approximations here: if the approximation is may,
719  * we have to load the data, otherwise the store may store
720  * irrelevant data
721  */
722  if (dma_load_p(s) || dma_allocate_p(s) || dma_deallocate_p(s)) {
723  /* first step is to check for may-write effects */
724  list may_write_effects = NIL;
725  FOREACH(EFFECT,e,rw_effects) {
728  effect fake = copy_effect(e);
730  may_write_effects=CONS(EFFECT,fake,may_write_effects);
731  }
732  }
733  may_write_effects=gen_nreverse(may_write_effects);
734  /* then we will merge these effects with those
735  * that were already gathered
736  * because we are manipulating lists, it is not very efficient
737  * but there should not be that many effects anyway
738  */
739  FOREACH(EFFECT,e_new,may_write_effects) {
740  bool merged = false; // if we failed to merge e_new in effects, we just add it to the list */
741  for(list iter=effects;!ENDP(iter);POP(iter)){
742  effect * e_origin = (effect*)REFCAR(iter); // get a reference to change it in place if needed
743  if(same_entity_p(
744  effect_any_entity(*e_origin),
745  effect_any_entity(e_new))) {
746  merged=true;
747  region tmp = extended_regions_must_convex_hull(*e_origin,e_new);
748  // there should be a free there, but it fails
749  *e_origin=tmp;
750  }
751  }
752  /* no data was copy-in, add this effect */
753  if(!merged) {
755  }
756  }
757  gen_full_free_list(may_write_effects);
759  }
760 
761 
762 
763  /* builds out transfer from gathered effects */
764  list statements = NIL;
765  FOREACH(EFFECT,eff,effects) {
766  statement the_dma = statement_undefined;
768  entity re = reference_variable(r);
769 
771  pips_user_error("We can't handle abstract locations here. Please try to "
772  "avoid using pointer or activate some pointer analyzes.\n");
773  }
774 
775 
776  struct dma_pair * val = (struct dma_pair *) hash_get(e2e, re);
777 
778  if( val == HASH_UNDEFINED_VALUE || (val->s != s) ) {
779  if( !io_effect_p(eff) && !std_file_effect_p(eff) &&
780  (!entity_scalar_p(re) || get_bool_property("KERNEL_LOAD_STORE_SCALAR"))
781  ) {
782  list /*of dimensions*/ the_dims = NIL,
783  /*of expressions*/the_offsets = NIL;
784  region_to_dimensions(eff,tr,&the_dims,&the_offsets,condition);
785 
786  entity eto;
787  if(val == HASH_UNDEFINED_VALUE) {
788 
789  /* initialized with NULL value */
791 
792  /* Replace the reference to the array re to *eto: */
793  type re_type = ultimate_array_type(entity_type(re));
794  basic re_basic = basic_undefined;
795  pips_assert("the type of the considered effect is expected to be variable",
796  type_variable_p(re_type));
797  re_basic = variable_basic(type_variable(re_type));
798  if(basic_pointer_p(re_basic)) {
799  type pointed_type = basic_pointer(re_basic);
801  }
803  entity declaring_module =
805  // PIER Here we need to add a P4A variable prefix to the name to help
806  // p4a postprocessing
807  string str = strdup (concatenate (prefix,entity_user_name(re), suffix, NULL));
808  eto = make_temporary_pointer_to_array_entity_with_prefix(str,renew,declaring_module,init);
809  free (str);
811  isolate_patch_entities(stat,re,eto,the_offsets);
812 
813  val=malloc(sizeof(*val));
814  val->new_ent=eto;
815  val->s=s;
816  hash_put(e2e,re,val);
817  }
818  else {
819  eto = val->new_ent;
820  val->s=s;/*to avoid duplicate*/
821  }
822  the_dma = instruction_to_statement(make_instruction_call(dimensions_to_dma(eff,eto,the_dims,the_offsets,s)));
823  statements=CONS(STATEMENT,the_dma,statements);
824  }
825  }
826  }
828  gen_full_free_list(rw_effects);
829  if (statements == NIL)
830  return statement_undefined;
831  else
832  return make_block_statement(statements);
833 }
834 
835 typedef struct {
838  bool ok;
839 } param_t;
840 
843  /* get parent statement */
845  pips_assert("found ancestor",!statement_undefined_p(s));
846  /* get associated regions */
848  /* verify the conditions : no complex offset handling */
849  FOREACH(REGION,reg,regions) {
851  entity eref = reference_variable(ref);
853  size_t nbdims;
854  type ut = ultimate_type(entity_type(eref));
857  else if(pointer_type_p(ut))
858  nbdims = gen_length(indices);
859  else
861  if(nbdims>1) { // unhandled
862  pips_user_warning("Trying to isolate a statement with a call that touches a multi-dimensional array `%s'\n", entity_user_name(eref));
863  p->ok=false;
864  }
865  /* we are left with a scalar or an unidimensional array */
866  else if(nbdims==1 && !ENDP(indices) ) { // see if we can approximate the region with an offset at zero
867  expression exp_phi1 = EXPRESSION(CAR(indices));
868  entity phi1 = expression_to_entity(exp_phi1);
869  Psysteme sc_reg = sc_dup(region_system(reg));
870  sc_transform_eg_in_ineg(sc_reg);
871  Pcontrainte lower,upper;
873  &sc_inegalites(sc_reg), &lower, &upper);
874  if( !CONTRAINTE_UNDEFINED_P(upper))
875  {
877  normalized nupper = NORMALIZE_EXPRESSION(eupper);
878  if(normalized_linear_p(nupper)) {
879  /* we can do it! leave it for later */
881  }
882  else {
883  pips_user_warning("Failed to normalized the upper bound for accesses to array `%s'\n",entity_user_name(eref));
884  p->ok=false;
885  }
886  free_expression(eupper);
887 
888  }
889  else {
890  pips_user_warning("Failed to find an upper bound for accesses to array `%s'\n",entity_user_name(eref));
891  p->ok=false;
892  }
893  contrainte_rm(lower);
894  contrainte_rm(upper);
895  sc_rm(sc_reg);
896  }
897  if(!p->ok) {
898  gen_recurse_stop(0);
899  return false;
900  }
901  }
902 
903  // verify the call does not references globals
907  entity eref = reference_variable(ref);
909  /* The following test could be refined, but it is OK right now if we can
910  override it with the following property when generating code for GPU
911  for example. */
912  if (!get_bool_property("ISOLATE_STATEMENT_EVEN_NON_LOCAL") &&
913  !io_effect_p(sr) && !std_file_effect_p(sr) ) {
914  pips_user_error("Cannot handle with some effects on non local variables in isolate_statement\n");
915  /* Should not return from previous exception anyway... */
916  }
917 
918  }
919  }
920  }
921 
922  return true;
923 }
924 
926 {
927  callees c = compute_callees(s);
928  list thecallees = callees_callees(c);
929  /* we have to make sure every callee access no global variables and that
930  * the associated regions has no offset
931  */
932  param_t p = { .ok=true, .regions_to_extend=NIL };
933  FOREACH(STRING, callee_module_name, thecallees) {
934  p.callee_module_name=callee_module_name;
936  if(!p.ok) break;
937  }
938  free_callees(c);
939  if(p.ok) { // this mean that all checks are ok, but some patching is needed
940  // maybe we have registered some regions to extend to avoid interprocedural offset management?
943  for(list iter=regions;!ENDP(iter);POP(iter)){ // change the region in place, thus the refcar
944  region * reg = (region*)REFCAR(iter);
947  if(!ENDP(indices)) { // only entities with indices are considered
948  entity eref = reference_variable(ref);
949  if(same_entity_p(eref,e)) { // we got the right entity
950  expression exp_phi1 = EXPRESSION(CAR(indices));
951  entity phi1 = expression_to_entity(exp_phi1);
952  Psysteme sc_reg = sc_dup(region_system(*reg));
953  sc_transform_eg_in_ineg(sc_reg);
954  Pcontrainte lower,upper;
956  &sc_inegalites(sc_reg), &lower, &upper);
957  if( !CONTRAINTE_UNDEFINED_P(upper))
958  {
960  normalized nupper = NORMALIZE_EXPRESSION(eupper);
961  if(normalized_linear_p(nupper)) {
962  Psysteme sc =sc_new();
963  /* add a constraint 0 <= phi1 and the upperbound constraint*/
964  sc_add_phi_equation(&sc, int_to_expression(0), 1, false, false);
965  sc_add_phi_equation(&sc, eupper, 1, false, true);
966 
967  bool must = false;
968  if(!CONTRAINTE_UNDEFINED_P(lower)) {
970  intptr_t p;
971  must=(expression_integer_value(elower,&p)&&p==0);
972  free_expression(elower);
973  }
974  /* duplicate the region */
976  copy_action(region_action(*reg)),
978  /* add it to current region */
979  region nreg = extended_regions_must_convex_hull(*reg,copy);
980  //free_effect(*reg);
981  //free_effect(copy);
982  *reg=nreg;
983  }
984  else pips_internal_error("This case should have been filtered out by `do_check_isolate_statement_preconditions_on_call'");
985  }
986  else pips_internal_error("This case should have been filtered out by `do_check_isolate_statement_preconditions_on_call'");
987  }
988  }
989  }
990  }
991  /* prune out read effects on pointers ...
992  * the assumption is that reading a pointer is not that important and most certainly comes from passing a pointer as parameter to a function
993  * if the pointer itself is not written, it should be ok.
994  * Well this indeed very optimistic ...
995  */
996  list rdup = gen_copy_seq(regions);
997  FOREACH(REGION,r,rdup) {
998  if(region_read_p(r) ) {
1002  gen_remove_once(&regions,r);
1003  }
1004  }
1005  }
1007  gen_free_list(rdup);
1009  }
1010  return p.ok;
1011 }
1012 
1013 
1014 /* perform statement isolation on statement @p s
1015  * that is make sure that all access to variables in @p s
1016  * are made either on private variables or on new entities declared on a new memory space. The @p prefix is used as a prefix to new entities' name.
1017  */
1018 void do_isolate_statement(statement s, const char* prefix, const char* suffix) {
1019  bool fine_grain_analysis = true;
1020  statement allocates, loads, stores, deallocates;
1021  /* this hash table holds an entity to (entity + tag ) binding */
1022  hash_table e2e ;
1024  pips_user_warning("isolated statement has callees, transfers will be approximated\n");
1025  fine_grain_analysis = false; // FIXME : This could be true most of the time, especially in Par4All !
1026  }
1028  expression condition = expression_undefined;
1029  allocates = effects_to_dma(s,dma_allocate,e2e,&condition,
1030  fine_grain_analysis,prefix,suffix);
1031  loads = effects_to_dma(s,dma_load,e2e,NULL,fine_grain_analysis,prefix,
1032  suffix);
1033  stores = effects_to_dma(s,dma_store,e2e,NULL,fine_grain_analysis,prefix,
1034  suffix);
1035  deallocates = effects_to_dma(s,dma_deallocate,e2e,NULL,fine_grain_analysis,
1036  prefix,suffix);
1037  HASH_MAP(k,v,free(v),e2e);
1038  hash_table_free(e2e);
1039 
1040  /* Add the calls now if needed, in the correct order: */
1041  if (loads != statement_undefined)
1042  insert_statement(s, loads,true);
1043  if (stores != statement_undefined)
1044  insert_statement(s, stores,false);
1045  if (deallocates != statement_undefined)
1046  insert_statement(s, deallocates,false);
1047  if (allocates != statement_undefined)
1048  insert_statement(s, allocates,true);
1049  /* guard the whole block by according conditions */
1050  if(!expression_undefined_p(condition)) {
1051 
1052  /* prends ton couteau suisse et viens jouer avec moi dans pips */
1053  pips_assert("statement is a block",statement_block_p(s));
1054  for(list prev=NIL,iter=statement_block(s);!ENDP(iter);POP(iter)) {
1055  if(declaration_statement_p(STATEMENT(CAR(iter)))) prev=iter;
1056  else {
1057  pips_assert("there should be at least one declaration inserted by isolate_statement\n",!ENDP(prev));
1058  statement cond =
1061  make_test(
1062  condition,
1063  make_block_statement(iter),
1065  )
1066  )
1067  );
1068  CDR(prev)=CONS(STATEMENT,cond,NIL);
1069  break;
1070  }
1071  }
1072  }
1073 }
1074 
1075 typedef struct {
1077  entity new;
1079 } isolate_param;
1080 
1081 /**
1082  * replace reference @p r on entity @p p->old by a reference on entity @p p->new with offsets @p p->offsets
1083  */
1085 {
1087  {
1088  list offsets = p->offsets;
1090  FOREACH(EXPRESSION,index,indices)
1091  {
1092  if(!ENDP(offsets)) {
1093  expression offset = EXPRESSION(CAR(offsets));
1097  make_call(
1100  copy_expression(index),
1102  )
1103  )
1104  )
1105  );
1106  }
1107  POP(offsets);
1108  }
1109  }
1110  /* build up the replacement */
1111  syntax syn =
1113  make_call(
1116  )
1117  );
1118 
1119  /* it is illegal to create a subscript without indices
1120  * quoting RK, at the airport back from SC 2010 */
1121  syntax snew = ENDP(indices) ?
1122  syn:
1125  );
1128  update_expression_syntax(parent,snew);
1129 
1130  }
1131 }
1132 
1133 /**
1134  * run isolate_patch_entities on all declared entities from @p s
1135  */
1137 {
1139  {
1142  }
1143 }
1144 
1145 /**
1146  * replace all references on entity @p old by references on entity @p new and adds offset @p offsets to its indices
1147  */
1148 void isolate_patch_entities(void * where,entity old, entity new,list offsets)
1149 {
1150  isolate_param p = { old,new,offsets };
1151  gen_context_multi_recurse(where,&p,
1154  0);
1155 }
1156 
1157 
1158 /* replaces expression @p e by its upper or lower bound under preconditions @p tr
1159  * @p is_upper is used to choose among lower and upperbound*/
1160 static void bounds_of_expression(expression e, transformer tr,bool is_upper)
1161 {
1162  intptr_t lbound, ubound;
1163  if(precondition_minmax_of_expression(e,tr,&lbound,&ubound) &&
1164  // FC: minmax returns max/min int, which does not make much sense
1165  // and result in later possibly undetected integer overflows...
1166  // so explicitely disallow these special values.
1167  ( (is_upper && ubound < VALUE_MAX) || (!is_upper && lbound > VALUE_MIN)))
1168  {
1169  fprintf(stderr, "bound=%"_intFMT"\n", is_upper? ubound: lbound);
1172  expression new = int_to_expression(is_upper ? ubound : lbound);
1177  free_expression(new);
1178  }
1179 }
1180 
1181 /* replaces expression @p e by its upperbound under preconditions @p tr*/
1183 {
1184  bounds_of_expression(e,tr,true);
1185 }
1186 
1187 /* replaces expression @p e by its lowerbound under preconditions @p tr*/
1189 {
1190  bounds_of_expression(e,tr,false);
1191 }
1192 
1193 
1194 
1195 /**
1196  * generate a list of dimensions @p dims and of offsets @p from a region @p r
1197  * for example if r = a[phi0,phi1] 0<=phi0<=2 and 1<=phi1<=4
1198  * we get dims = ( (0,3), (0,4) )
1199  * and offsets = ( 0 , 1 )
1200  * if @p exact is set to false, we are allowed to give an upper bound to the dimensions
1201  *
1202  * if at least one of the resulting dimension can be 0 (according to preconditions)
1203  * @p dimension_may_be_null is set to true
1204  *
1205  * @return false if we were enable to gather enough informations
1206  */
1207 bool region_to_minimal_dimensions(region r, transformer tr, list * dims, list *offsets,bool exact, expression *condition)
1208 {
1209  pips_assert("empty parameters\n",ENDP(*dims)&&ENDP(*offsets));
1211  bool fortran_p = fortran_module_p(get_current_module_entity());
1212  for(list iter = reference_indices(ref);!ENDP(iter); POP(iter))
1213  {
1214  expression index = EXPRESSION(CAR(iter));
1215  Variable phi = expression_to_entity(index);
1216  if(variable_phi_p((entity)phi)) {
1217  Psysteme sc = sc_dup(region_system(r));
1219  Pcontrainte lower,upper;
1220  constraints_for_bounds(phi, &sc_inegalites(sc), &lower, &upper);
1221  if( !CONTRAINTE_UNDEFINED_P(lower) && !CONTRAINTE_UNDEFINED_P(upper))
1222  {
1223  /* this is a constant : the dimension is 1 and the offset is the bound */
1224  if(bounds_equal_p(phi,lower,upper))
1225  {
1226 #if 1
1228  if (fortran_p) {
1229  // in fortran remove -1 to the bound since index 1 is
1230  // offset 0
1231  bound = add_integer_to_expression (bound, -1);
1232  }
1234  *offsets=CONS(EXPRESSION,bound,*offsets);
1235 #endif
1236  }
1237  /* this is a range : the dimension is eupper-elower +1 and the offset is elower */
1238  else
1239  {
1240 
1243  simplify_minmax_expression(elower,tr);
1244  simplify_minmax_expression(eupper,tr);
1245  expression offset = copy_expression(elower);
1246  if (fortran_p) {
1247  // in fortran remove -1 to the offset since index 1 is
1248  // offset 0
1250  }
1251 
1252  bool compute_upperbound_p =
1253  !exact && (expression_minmax_p(elower)||expression_minmax_p(eupper));
1254  expression dim = make_op_exp(MINUS_OPERATOR_NAME,eupper,elower);
1255  if(compute_upperbound_p)
1256  upperbound_of_expression(dim,tr);
1257 
1258  /* sg : check if lower bound can be 0, in that case issue a ward */
1259  if(condition!=0) {
1260  expression lowerbound = copy_expression(dim);
1261  lowerbound_of_expression(lowerbound,tr);
1262  intptr_t lowerbound_value;
1263  if(!expression_integer_value(lowerbound,&lowerbound_value) ||
1264  lowerbound_value<=0) {
1265  expression thetest =
1268  copy_expression(dim),
1270  );
1271  if(expression_undefined_p(*condition))
1272  *condition=thetest;
1273  else
1274  *condition=MakeBinaryCall(
1276  *condition,
1277  thetest
1278  );
1279  }
1280  }
1281 
1282  *dims=CONS(DIMENSION,
1284  int_to_expression(0),
1285  dim,
1286  NIL),
1287  *dims);
1288  *offsets=CONS(EXPRESSION,offset,*offsets);
1289  }
1290  }
1291  else {
1292  pips_user_warning("failed to analyse region\n");
1293  sc_free(sc);
1294  /* reset state */
1295  gen_full_free_list(*dims); *dims=NIL;
1296  gen_full_free_list(*offsets); *offsets=NIL;
1297  return false;
1298  }
1299  sc_free(sc);
1300  }
1301  /* index is a field ... */
1302  else { /* and the last field, store it as an extra dimension */
1303 #if 0
1304  *dims=CONS(DIMENSION,
1306  int_to_expression(0),
1307  int_to_expression(0),
1308  NIL
1309  ),*dims);
1310  *offsets=CONS(EXPRESSION,copy_expression(index),*offsets);
1311 #else
1312  break;
1313 #endif
1314  }
1315  }
1316  *dims=gen_nreverse(*dims);
1317  *offsets=gen_nreverse(*offsets);
1318  return true;
1319 }
1320 
1321 /**
1322  *
1323  * @return region from @p regions on entity @p e
1324  */
1326 {
1327  FOREACH(REGION,r,regions)
1329  return region_undefined;
1330 }
1331 
1332 
1333 /**
1334  * @return a range suitable for iteration over all the elements of dimension @p d
1335  */
1337 {
1338  return make_range(
1341  int_to_expression(1));
1342 }
1343 
1344 /**
1345  * @return a statement holding the loop necessary to initialize @p new from @p old,
1346  * knowing the dimension of the isolated entity @p dimensions and its offsets @p offsets and the direction of the transfer @p t
1347  */
1348 
1350 {
1351  /* init stuff */
1358 
1359 
1360  /* get user input */
1361  const char* stmt_label=get_string_property("ISOLATE_STATEMENT_LABEL");
1362  statement statement_to_isolate;
1363  if(!empty_string_p(stmt_label)) {
1365  } else {
1366  statement_to_isolate = get_current_module_statement();
1367  }
1368  /* and proceed */
1369  if(statement_undefined_p(statement_to_isolate))
1370  pips_user_error("statement labeled '%s' not found\n",stmt_label);
1371  else
1372  {
1373  const char* prefix = get_string_property ("ISOLATE_STATEMENT_VAR_PREFIX");
1374  const char* suffix = get_string_property ("ISOLATE_STATEMENT_VAR_SUFFIX");
1375  pips_debug (5, "isolate_statement prefix : %s\n", prefix);
1376  pips_debug (5, "isolate_statement suffix : %s\n", suffix);
1377  do_isolate_statement(statement_to_isolate, prefix, suffix);
1378  }
1379 
1380 
1381 
1382  /* validate */
1386 
1393 
1394  return true;
1395 }
1396 
action copy_action(action p)
ACTION.
Definition: effects.c:77
effects make_effects(list a)
Definition: effects.c:568
approximation make_approximation_exact(void)
Definition: effects.c:185
approximation make_approximation_may(void)
Definition: effects.c:179
void free_effects(effects p)
Definition: effects.c:535
effect copy_effect(effect p)
EFFECT.
Definition: effects.c:448
void free_normalized(normalized p)
Definition: ri.c:1407
cast make_cast(type a1, expression a2)
Definition: ri.c:311
call make_call(entity a1, list a2)
Definition: ri.c:269
syntax make_syntax_call(call _field_)
Definition: ri.c:2500
expression make_expression(syntax a1, normalized a2)
Definition: ri.c:886
subscript make_subscript(expression a1, list a2)
Definition: ri.c:2327
type make_type_variable(variable _field_)
Definition: ri.c:2715
basic copy_basic(basic p)
BASIC.
Definition: ri.c:104
void free_callees(callees p)
Definition: ri.c:194
type make_type_void(list _field_)
Definition: ri.c:2727
basic make_basic_pointer(type _field_)
Definition: ri.c:179
expression copy_expression(expression p)
EXPRESSION.
Definition: ri.c:850
reference make_reference(entity a1, list a2)
Definition: ri.c:2083
language copy_language(language p)
LANGUAGE.
Definition: ri.c:1202
test make_test(expression a1, statement a2, statement a3)
Definition: ri.c:2607
dimension make_dimension(expression a1, expression a2, list a3)
Definition: ri.c:565
dimension copy_dimension(dimension p)
DIMENSION.
Definition: ri.c:529
variable make_variable(basic a1, list a2, list a3)
Definition: ri.c:2895
instruction make_instruction_test(test _field_)
Definition: ri.c:1172
instruction make_instruction_call(call _field_)
Definition: ri.c:1184
void free_expression(expression p)
Definition: ri.c:853
reference copy_reference(reference p)
REFERENCE.
Definition: ri.c:2047
syntax make_syntax_cast(cast _field_)
Definition: ri.c:2503
void free_type(type p)
Definition: ri.c:2658
void free_syntax(syntax p)
Definition: ri.c:2445
syntax make_syntax_subscript(subscript _field_)
Definition: ri.c:2509
range make_range(expression a1, expression a2, expression a3)
Definition: ri.c:2041
#define dma_allocate_p(e)
#define dma_deallocate_p(e)
#define dma_store_p(e)
#define dma_load_p(e)
Add NewGen-like methods:
region_to_dma_switch
@ dma_store
@ dma_allocate
@ dma_deallocate
@ dma_load
static reference ref
Current stmt (an integer)
Definition: adg_read_paf.c:163
static FILE * out
Definition: alias_check.c:128
struct _newgen_struct_expression_ * expression
Definition: alias_private.h:21
bool entity_abstract_location_p(entity al)
void const char const char const int
#define VALUE_MIN
#define VALUE_MAX
callees compute_callees(const statement stat)
Recompute the callees of a module statement.
Definition: callgraph.c:355
struct _newgen_struct_statement_ * statement
Definition: cloning.h:21
#define CONTRAINTE_UNDEFINED_P(c)
#define contrainte_rm(c)
the standard xxx_rm does not return a value
void constraints_for_bounds(Variable, Pcontrainte *, Pcontrainte *, Pcontrainte *)
void constraints_for_bounds(var, pinit, plower, pupper) Variable var; Pcontrainte *pinit,...
Definition: unaires.c:176
expression constraints_to_loop_bound(Pcontrainte, Variable, bool, entity)
expression constraints_to_loop_bound(c, var, is_lower)
bool bounds_equal_p(Variable, Pcontrainte, Pcontrainte)
this function checks whether the lower and upper constraints are going to generate the same bound on ...
#define region_any_reference(reg)
To be avoided.
#define region_write_p(reg)
#define region_action(reg)
#define region_system(reg)
#define region_undefined
#define effect_region_p(e)
#define region_read_p(reg)
useful region macros
#define region_approximation_tag(reg)
#define make_region(reference, action, approximation, system)
#define REGION
#define region
simulation of the type region
effect regions_must_convex_hull(region f1, region f2)
1- Union :
static Value offset
Definition: translation.c:283
void region_free(effect)
bool sc_add_phi_equation(Psysteme *, expression, int, bool, bool)
bool summary_regions(const string)
effect region_dup(effect)
expression region_reference_to_expression(reference)
Psysteme entity_declaration_sc(entity)
effect region_rectangular_hull(effect, bool)
list effects_store_effects(list)
void update_cumulated_rw_effects_list(statement, list)
void reset_proper_rw_effects(void)
void set_proper_rw_effects(statement_effects)
void set_cumulated_rw_effects(statement_effects)
list load_cumulated_rw_effects_list(statement)
void reset_cumulated_rw_effects(void)
#define effect_any_reference(e)
FI: cannot be used as a left hand side.
#define effect_approximation_tag(eff)
#define effect_any_entity(e)
some useful SHORTHANDS for EFFECT:
#define variable_phi_p(e)
true if e is a phi variable PHI entities have a name like: REGIONS:PHI#, where # is a number.
list effects_to_list(effects)
Definition: effects.c:209
bool std_file_effect_p(effect)
Definition: effects.c:519
bool io_effect_p(effect)
Definition: effects.c:501
#define effect_action(x)
Definition: effects.h:642
#define approximation_may_p(x)
Definition: effects.h:363
#define action_write_p(x)
Definition: effects.h:314
#define action_tag(x)
Definition: effects.h:310
#define action_read_p(x)
Definition: effects.h:311
#define descriptor_convex_p(x)
Definition: effects.h:599
#define effect_descriptor(x)
Definition: effects.h:646
#define descriptor_convex(x)
Definition: effects.h:601
action_utype
Definition: effects.h:291
@ is_action_read
Definition: effects.h:292
@ is_approximation_may
Definition: effects.h:341
#define effect_approximation(x)
Definition: effects.h:644
#define EFFECT(x)
EFFECT.
Definition: effects.h:608
bool empty_string_p(const char *s)
Definition: entity_names.c:239
const char * module_name(const char *s)
Return the module part of an entity name.
Definition: entity_names.c:296
void set_live_loop_indices(void)
cproto-generated files
Definition: partial_eval.c:129
void partial_eval_declaration(entity, Psysteme, effects)
assumes conditions checked by partial_eval_declarations()
void reset_live_loop_indices(void)
Definition: partial_eval.c:135
char * get_string_property(const char *)
bool get_bool_property(const string)
FC 2015-07-20: yuk, moved out to prevent an include cycle dependency include "properties....
#define gen_context_recurse(start, ctxt, domain_number, flt, rwt)
Definition: genC.h:285
#define STRING(x)
Definition: genC.h:87
void gen_full_free_list(list l)
Definition: genClib.c:1023
void * malloc(YYSIZE_T)
void free(void *)
statement make_block_statement(list)
Make a block statement from a list of statement.
Definition: statement.c:616
statement instruction_to_statement(instruction)
Build a statement from a give instruction.
Definition: statement.c:597
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
const char * get_current_module_name(void)
Get the name of the current module.
Definition: static.c:121
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
entity get_current_module_entity(void)
Get the entity of the current module.
Definition: static.c:85
void gen_recurse_stop(void *obj)
Tells the recursion not to go in this object.
Definition: genClib.c:3251
void gen_context_multi_recurse(void *o, void *context,...)
Multi-recursion with context function visitor.
Definition: genClib.c:3373
gen_chunk * gen_get_ancestor(int, const void *)
return the first ancestor object found of the given type.
Definition: genClib.c:3560
void gen_null2(__attribute__((unused)) void *u1, __attribute__((unused)) void *u2)
idem with 2 args, to please overpeaky compiler checks
Definition: genClib.c:2758
bool gen_true(__attribute__((unused)) gen_chunk *unused)
Return true and ignore the argument.
Definition: genClib.c:2780
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
list gen_nreverse(list cp)
reverse a list in place
Definition: list.c:304
#define POP(l)
Modify a list pointer to point on the next element of the list.
Definition: newgen_list.h:59
void gen_remove_once(list *pl, const void *o)
Remove the first occurence of o in list pl:
Definition: list.c:691
#define REFCAR(pc)
Get the adress of the first element of a list.
Definition: newgen_list.h:119
#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
#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 CDR(pcons)
Get the list less its first element.
Definition: newgen_list.h:111
list gen_append(list l1, const list l2)
Definition: list.c:471
list gen_full_copy_list(list l)
Copy a list structure with element copy.
Definition: list.c:535
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
list statement_block(statement)
Get the list of block statements of a statement sequence.
Definition: statement.c:1338
void insert_statement(statement, statement, bool)
This is the normal entry point.
Definition: statement.c:2570
statement find_statement_from_label_name(statement, const char *, const char *)
Definition: statement.c:3816
bool declaration_statement_p(statement)
Had to be optimized according to Beatrice Creusillet.
Definition: statement.c:224
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
static list indices
Definition: icm.c:204
static bool declarations_to_dimensions(entity e, list *dimensions, list *offsets)
range dimension_to_range(dimension d)
static statement effects_to_dma(statement stat, enum region_to_dma_switch s, hash_table e2e, expression *condition, bool fine_grain_analysis, const char *prefix, const char *suffix)
Compute a call to a DMA function from the effects of a statement.
void region_to_dimensions(effect reg, transformer tr, list *dimensions, list *offsets, expression *condition)
isolate_statement.c
static void upperbound_of_expression(expression e, transformer tr)
replaces expression e by its upperbound under preconditions tr
static const char * get_dma_name(enum region_to_dma_switch m, size_t d)
converts a region_to_dma_switch to corresponding dma name according to properties
bool isolate_statement(const char *module_name)
static void isolate_patch_reference(reference r, isolate_param *p)
replace reference r on entity p->old by a reference on entity p->new with offsets p->offsets
static size_t get_dma_dimension(region reg_from)
void do_isolate_statement(statement s, const char *prefix, const char *suffix)
perform statement isolation on statement s that is make sure that all access to variables in s are ma...
static expression get_sizeofexpression_for_region(region reg)
generate an expression of the form sizeof(typeof(variable[indices]))
static bool do_check_isolate_statement_preconditions_on_call(call c, param_t *p)
region find_region_on_entity(entity e, list regions)
static bool do_isolate_statement_preconditions_satisified_p(statement s)
static void bounds_of_expression(expression e, transformer tr, bool is_upper)
replaces expression e by its upper or lower bound under preconditions tr is_upper is used to choose a...
static const int dma1D
Some constant intended to have a more readable code.
bool region_to_minimal_dimensions(region r, transformer tr, list *dims, list *offsets, bool exact, expression *condition)
generate a list of dimensions dims and of offsets from a region r for example if r = a[phi0,...
list variable_to_dimensions(region reg_from)
static expression region_to_address(region reg)
call dimensions_to_dma(effect reg_from, entity to, list ld, list lo, enum region_to_dma_switch m)
converts dimensions to a dma call from a memory from to another memory to
static region extended_regions_must_convex_hull(region r0, region r1)
perform the convex hull between r0 and r1, and merge them if they have a common prefix e....
static void lowerbound_of_expression(expression e, transformer tr)
replaces expression e by its lowerbound under preconditions tr
void isolate_patch_entities(void *where, entity old, entity new, list offsets)
replace all references on entity old by references on entity new and adds offset offsets to its indic...
static void isolate_patch_statement(statement s, isolate_param *p)
run isolate_patch_entities on all declared entities from s
#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_user_warning
Definition: misc-local.h:146
#define asprintf
Definition: misc-local.h:225
#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 pips_user_error
Definition: misc-local.h:147
string concatenate(const char *,...)
Return the concatenation of the given strings.
Definition: string.c:183
#define HASH_MAP(k, v, code, ht)
Definition: newgen_hash.h:60
@ 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
#define HASH_DEFAULT_SIZE
Definition: newgen_hash.h:26
#define same_string_p(s1, s2)
void set_free(set)
Definition: set.c:332
bool set_belong_p(const set, const void *)
Definition: set.c:194
@ set_pointer
Definition: newgen_set.h:44
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
#define _intFMT
Definition: newgen_types.h:57
void print_entity_variable(entity e)
print_entity_variable(e)
Definition: entity.c:56
#define print_effect(e)
Definition: print.c:336
#define print_region(x)
Definition: print.c:343
static const char * prefix
bool module_reorder(statement body)
Reorder a module and recompute order to statement if any.
Definition: reorder.c:244
#define make_expression_list(stats...)
#define GREATER_THAN_OPERATOR_NAME
#define MINUS_OPERATOR_NAME
#define NORMALIZE_EXPRESSION(e)
#define statement_block_p(stat)
#define DEREFERENCING_OPERATOR_NAME
Definition: ri-util-local.h:93
#define FIELD_OPERATOR_NAME
Definition: ri-util-local.h:91
#define C_LOC_FUNCTION_NAME
F2003.
#define AND_OPERATOR_NAME
FI: intrinsics are defined at a third place after bootstrap and effects! I guess the name should be d...
#define ADDRESS_OF_OPERATOR_NAME
#define module_language(e)
implemented as a macro to allow lhs
#define DIVIDE_OPERATOR_NAME
#define MULTIPLY_OPERATOR_NAME
#define make_empty_statement
An alias for make_empty_block_statement.
const char * entity_user_name(entity e)
Since entity_local_name may contain PIPS special characters such as prefixes (label,...
Definition: entity.c:487
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
bool entity_array_p(entity e)
Is e a variable with an array type?
Definition: entity.c:754
bool same_entity_p(entity e1, entity e2)
predicates on entities
Definition: entity.c:1321
bool entity_local_variable_p(entity var, entity module)
Check if a variable "var" is local to a module "module".
Definition: entity.c:3104
bool c_module_p(entity m)
Test if a module "m" is written in C.
Definition: entity.c:2777
entity AddEntityToModule(entity e, entity module)
!!! caution, it may not be a module, but a common...
Definition: entity.c:3171
entity module_name_to_entity(const char *mn)
This is an alias for local_name_to_top_level_entity.
Definition: entity.c:1479
entity make_empty_subroutine(const char *name, language l)
Definition: entity.c:268
bool entity_field_p(entity e)
e is the field of a structure
Definition: entity.c:857
static int init
Maximal value set for Fortran 77.
Definition: entity.c:320
bool fortran_module_p(entity m)
Test if a module is in Fortran.
Definition: entity.c:2799
bool entity_pointer_p(entity e)
Definition: entity.c:745
entity entity_intrinsic(const char *name)
FI: I do not understand this function name (see next one!).
Definition: entity.c:1292
bool expression_integer_value(expression e, intptr_t *pval)
Definition: eval.c:792
expression add_integer_to_expression(expression exp, int val)
Definition: expression.c:2132
expression MakeSizeofType(type t)
Definition: expression.c:3904
bool expression_minmax_p(expression e)
Definition: expression.c:3882
expression entity_to_expression(entity e)
if v is a constant, returns a constant call.
Definition: expression.c:165
expression MakeBinaryCall(entity f, expression eg, expression ed)
Creates a call expression to a function with 2 arguments.
Definition: expression.c:354
void update_expression_syntax(expression e, syntax s)
frees expression syntax of e and replace it by the new syntax s
Definition: expression.c:3564
expression int_to_expression(_int i)
transform an int into an expression and generate the corresponding entity if necessary; it is not cle...
Definition: expression.c:1188
expression MakeSizeofExpression(expression e)
Definition: expression.c:3896
expression make_op_exp(char *op_name, expression exp1, expression exp2)
================================================================
Definition: expression.c:2012
expression MakeUnaryCall(entity f, expression a)
Creates a call expression to a function with one argument.
Definition: expression.c:342
bool expression_reference_p(expression e)
Test if an expression is a reference.
Definition: expression.c:528
reference expression_reference(expression e)
Short cut, meaningful only if expression_reference_p(e) holds.
Definition: expression.c:1832
entity expression_to_entity(expression e)
just returns the entity of an expression, or entity_undefined
Definition: expression.c:3140
expression syntax_to_expression(syntax s)
generates an expression from a syntax
Definition: expression.c:3581
type ultimate_type(type)
Definition: type.c:3466
expression SizeOfDimensions(list)
computes the product of all dimensions in dims
Definition: size.c:522
void AddLocalEntityToDeclarations(entity, entity, statement)
Add the variable entity e to the list of variables of the function module.
Definition: variable.c:233
bool entity_scalar_p(entity)
The concrete type of e is a scalar type.
Definition: variable.c:1113
type ultimate_array_type(type)
Definition: type.c:3471
type pointed_type(type)
returns the type pointed by the input type if it is a pointer or an array of pointers
Definition: type.c:3035
bool pointer_type_p(type)
Check for scalar pointers.
Definition: type.c:2993
bool formal_parameter_p(entity)
Definition: variable.c:1489
entity make_new_array_variable(entity, basic, list)
Definition: variable.c:793
expression SizeOfDimension(dimension)
Definition: size.c:503
bool type_struct_variable_p(type)
Definition: type.c:3867
bool type_pointer_on_struct_variable_p(type)
Definition: type.c:2960
basic basic_of_reference(reference)
Retrieves the basic of a reference in a newly allocated basic object.
Definition: type.c:1459
entity make_temporary_pointer_to_array_entity_with_prefix(char *, entity, entity, expression)
Definition: variable.c:801
#define value_undefined_p(x)
Definition: ri.h:3017
#define basic_pointer(x)
Definition: ri.h:637
#define normalized_undefined
Definition: ri.h:1745
#define expression_domain
newgen_execution_domain_defined
Definition: ri.h:154
#define normalized_linear_p(x)
Definition: ri.h:1779
#define call_function(x)
Definition: ri.h:709
#define callees_callees(x)
Definition: ri.h:675
#define reference_variable(x)
Definition: ri.h:2326
#define ENTITY(x)
ENTITY.
Definition: ri.h:2755
#define dimension_lower(x)
Definition: ri.h:980
#define type_variable(x)
Definition: ri.h:2949
#define basic_pointer_p(x)
Definition: ri.h:635
#define statement_domain
newgen_sizeofexpression_domain_defined
Definition: ri.h:362
#define call_domain
newgen_callees_domain_defined
Definition: ri.h:58
#define EXPRESSION(x)
EXPRESSION.
Definition: ri.h:1217
#define basic_undefined
Definition: ri.h:556
#define entity_undefined_p(x)
Definition: ri.h:2762
#define reference_domain
newgen_range_domain_defined
Definition: ri.h:338
#define expression_undefined
Definition: ri.h:1223
#define transformer_relation(x)
Definition: ri.h:2873
#define expression_normalized(x)
Definition: ri.h:1249
#define dimension_upper(x)
Definition: ri.h:982
#define reference_indices(x)
Definition: ri.h:2328
#define expression_undefined_p(x)
Definition: ri.h:1224
#define variable_dimensions(x)
Definition: ri.h:3122
#define statement_declarations(x)
Definition: ri.h:2460
#define syntax_undefined
Definition: ri.h:2676
#define statement_undefined_p(x)
Definition: ri.h:2420
#define entity_type(x)
Definition: ri.h:2792
#define expression_syntax(x)
Definition: ri.h:1247
#define type_variable_p(x)
Definition: ri.h:2947
#define predicate_system(x)
Definition: ri.h:2069
#define variable_basic(x)
Definition: ri.h:3120
#define statement_undefined
Definition: ri.h:2419
#define STATEMENT(x)
STATEMENT.
Definition: ri.h:2413
#define entity_initial(x)
Definition: ri.h:2796
void sc_rm(Psysteme ps)
void sc_rm(Psysteme ps): liberation de l'espace memoire occupe par le systeme de contraintes ps;
Definition: sc_alloc.c:277
Psysteme sc_new(void)
Psysteme sc_new(): alloue un systeme vide, initialise tous les champs avec des valeurs nulles,...
Definition: sc_alloc.c:55
Psysteme sc_dup(Psysteme ps)
Psysteme sc_dup(Psysteme ps): should becomes a link.
Definition: sc_alloc.c:176
Psysteme sc_intersection(Psysteme s1, Psysteme s2, Psysteme s3)
Psysteme sc_intersection(Psysteme s1, Psysteme s2, Psysteme s3): calcul d'un systeme de contraintes s...
Psysteme sc_free(Psysteme in_ps)
Psysteme sc_free( in_ps ) AL 30/05/94 Free of in_ps.
Definition: sc_list.c:112
int fprintf()
test sc_min : ce test s'appelle par : programme fichier1.data fichier2.data ...
char * strdup()
Psysteme sc_normalize2(volatile Psysteme ps)
Psysteme sc_normalize2(Psysteme ps): normalisation d'un systeme d'equation et d'inequations lineaires...
void sc_transform_eg_in_ineg(Psysteme sc)
Package sc.
bool precondition_minmax_of_expression(expression exp, transformer tr, intptr_t *pmin, intptr_t *pmax)
compute integer bounds pmax, pmin of expression exp under preconditions tr require value mappings set...
Definition: expression.c:5818
void simplify_minmax_expression(expression e, transformer tr)
tries hard to simplify expression e if it is a min or a max operator, by evaluating it under precondi...
Definition: expression.c:5849
void module_to_value_mappings(entity m)
void module_to_value_mappings(entity m): build hash tables between variables and values (old,...
Definition: mappings.c:624
transformer load_statement_precondition(statement)
void reset_precondition_map(void)
void set_precondition_map(statement_mapping)
#define ifdebug(n)
Definition: sg.c:47
#define intptr_t
Definition: stdint.in.h:294
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
isolate_statement
entity new_ent
enum region_to_dma_switch s
char * callee_module_name
list regions_to_extend
transformer transformer_range(transformer tf)
Return the range of relation tf in a newly allocated transformer.
Definition: transformer.c:714
void free_value_mappings(void)
Normal call to free the mappings.
Definition: value.c:1212
#define sc_equal_p(ps1, ps2)
Definition: union-local.h:83
#define exp
Avoid some warnings from "gcc -Wshadow".
Definition: vasnprintf.c:207
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
void AddEntityToModuleCompilationUnit(entity e, entity module)
Definition: module.c:301