PIPS
utils.c
Go to the documentation of this file.
1 /*
2 
3  $Id: utils.c 23412 2017-08-09 15:07:09Z irigoin $
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 /* package generic effects : Be'atrice Creusillet 5/97
28  *
29  * File: utils.c
30  * ~~~~~~~~~~~~~~~~~
31  *
32  * This File contains various useful functions, some of which should be moved
33  * elsewhere.
34  *
35  */
36 
37 #include <stdio.h>
38 #include <string.h>
39 #include <stdlib.h>
40 
41 #include "genC.h"
42 #include "linear.h"
43 #include "ri.h"
44 #include "effects.h"
45 #include "ri-util.h"
46 #include "prettyprint.h"
47 #include "workspace-util.h"
48 #include "effects-util.h"
49 #include "misc.h"
50 #include "text-util.h"
51 #include "properties.h"
52 #include "preprocessor.h"
53 
54 #include "effects-generic.h"
55 
56 
57 /********************************************************************* MISC */
58 
59 
60 /* Statement stack to walk on control flow representation */
61 DEFINE_GLOBAL_STACK(effects_private_current_stmt, statement)
62 
63 /* Context stack to keep current context when walking on expressions */
64 DEFINE_GLOBAL_STACK(effects_private_current_context, transformer)
65 
67 {
68  return (effects_private_current_context_stack != stack_undefined);
69 }
71 {
72  return (effects_private_current_stmt_stack != stack_undefined);
73 }
74 
75 bool normalizable_and_linear_loop_p(entity index, range l_range)
76 {
77  Value incr = VALUE_ZERO;
78  normalized nub, nlb;
79  expression e_incr = range_increment(l_range);
80  normalized n;
81  bool result = true;
82 
83  /* Is the loop index an integer variable */
84  if (! entity_integer_scalar_p(index))
85  {
86  pips_user_warning("non integer scalar loop index %s.\n",
87  entity_local_name(index));
88  result = false;
89  }
90  else
91  {
92  /* Is the loop increment numerically known ? */
93  n = NORMALIZE_EXPRESSION(e_incr);
94  if(normalized_linear_p(n))
95  {
96  Pvecteur v_incr = normalized_linear(n);
97  if(vect_constant_p(v_incr))
98  incr = vect_coeff(TCST, v_incr);
99  }
100 
101  nub = NORMALIZE_EXPRESSION(range_upper(l_range));
102  nlb = NORMALIZE_EXPRESSION(range_lower(l_range));
103 
104  result = value_notzero_p(incr) && normalized_linear_p(nub)
105  && normalized_linear_p(nlb);
106  }
107 
108  return(result);
109 }
110 
113 {
115 
116  if (orig_trans != transformer_undefined)
117  {
118  res_trans = copy_transformer(orig_trans);
119  gen_remove(&transformer_arguments(res_trans), ent);
120  }
121  return(res_trans);
122 }
123 
124 
125 /**************************************** DESCRIPTORS (should not be there) */
126 
127 static bool descriptor_range_p = false;
128 
129 void
131 {
132  descriptor_range_p = b;
133 }
134 
135 bool
137 {
138  return(descriptor_range_p);
139 }
140 
143 {
144  if (!VECTEUR_UNDEFINED_P(v))
145  {
146  Psysteme sc = descriptor_convex(d);
147  Pcontrainte contrainte = contrainte_make(v);
148  sc_add_inegalite(sc, contrainte);
149  sc->base = BASE_NULLE;
150  sc_creer_base(sc);
152  }
153  return d;
154 }
155 
158 {
160  if (descriptor_none_p(d))
162  else
163  {
166  }
167  return(context);
168 }
169 
170 void
172 {
173  if (descriptor_convex_p(d))
174  {
176  (Variable) old_ent,
177  (Variable) new_ent);
178  }
179 }
180 
183 {
185  {
186  Psysteme
187  sc1 = descriptor_convex(d1),
188  sc2 = descriptor_convex(d2);
189 
190  sc1 = sc_safe_append(sc1, sc2);
192  }
193  else
195  return d1;
196 }
197 
198 /***********************************************************************/
199 /* */
200 /***********************************************************************/
201 
204 {
205  return transformer_undefined;
206 }
207 
210 {
211  return transformer_undefined;
212 }
213 
214 bool
216 {
217  return false;
218 }
219 
220 void
221 effects_computation_no_init(const char *module_name __attribute__ ((__unused__)) )
222 {
223  return;
224 }
225 
226 void
227 effects_computation_no_reset(const char *module_name __attribute__ ((__unused__)) )
228 {
229  return;
230 }
231 
232 
233 /***********************************************************************/
234 /* FORMER effects/utils.c */
235 /***********************************************************************/
236 
237 
238 string vect_debug_entity_name(e)
239 entity e;
240 {
241  return((e == (entity) TCST) ? "TCST" : entity_name(e));
242 }
243 
244 
245 /* check that *some* read or write effects are on integer variables
246  *
247  * FI: this is almost always true because of array subscript expressions
248  */
249 /*
250  This function might be dangerous in case of abstract locations and
251  with complex memory paths involving dereferencements, struct fields,
252  and array indices. BC.
253  */
255  bool r_or_w_p = false;
256  FOREACH(EFFECT, ef,fx) {
258  if( store_effect_p(ef) && integer_scalar_entity_p(e)) {
259  r_or_w_p = true;
260  break;
261  }
262  }
263  return r_or_w_p;
264 }
265 
266 
267 
268 
269 /* Return true if a statement has an I/O effect in the effects
270  list. */
272 {
273  bool io_effect_found = false;
274  list effects_list = load_proper_rw_effects_list(s);
275 
276  /* If there is an I/O effects, the following entity should
277  exist. If it does not exist, statement_io_effect_p() will return
278  false anyway. */
279  entity private_io_entity =
282 
283  MAP(EFFECT, an_effect,
284  {
285  reference a_reference = effect_any_reference(an_effect);
286  entity a_touched_variable =
287  reference_variable(a_reference);
288 
289  if (a_touched_variable == private_io_entity) {
290  io_effect_found = true;
291  break;
292  }
293  },
294  effects_list);
295 
296  return io_effect_found;
297 }
298 
299 /* Return true if the statement has a write effect on at least one of
300  the argument (formal parameter) of the module and if the argument
301  passing mode is by reference. Note that the return variable of a
302  function is also considered here as a formal parameter. */
304 {
305  bool write_effect_on_a_module_argument_found = false;
307  list effects_list = load_proper_rw_effects_list(s);
308  /* it might be better to check the parameter passing mode itself,
309  via the module type */
310  bool fortran_p = fortran_module_p(module);
311 
312  FOREACH(EFFECT, an_effect, effects_list) {
315  module);
316  bool return_variable_p = variable_return_p(a_variable);
317 
318  if (action_write_p(effect_action(an_effect))
319  && (return_variable_p
320  || (formal_p && fortran_p)
321  )
322  ) {
323  write_effect_on_a_module_argument_found = true;
324  break;
325  }
326  } ;
327 
328  return write_effect_on_a_module_argument_found;
329 
330 }
331 
332 
333 
334 list /* of effect */ make_effects_for_array_declarations(list refs)
335 {
336  list leff = NIL;
337  effect eff;
338  MAPL(l1,
339  {
340  reference ref = REFERENCE(CAR(l1));
341  /* FI: in this context, I assume that eff is never returned undefined */
342  // functions that can be pointed by reference_to_effect_func:
343  // reference_to_simple_effect
344  // reference_to_convex_region
345  // reference_to_reference_effect
346  eff = (*reference_to_effect_func)(ref, make_action_read_memory(), true);
347  if(effect_undefined_p(eff)) {
348  pips_debug(8, "Reference to \"%s\" ignored\n",
350  }
351  else
352  leff= CONS(EFFECT,eff,leff);
353  },refs);
354 
355  gen_free_list(refs);
356  return leff;
357 }
358 
359 
360 
361 
362 
364 {
365  list sel = NIL;
366  //entity mod = module_name_to_entity(module_name);
367  //list decls = code_declarations(value_code(entity_initial(mod)));
369  list refs = list_undefined;
370 
372 
373  ifdebug(8) {
374  pips_debug(8, "References from declarations:\n");
375  MAP(REFERENCE, r, {
376  pips_debug(8, "Reference for variable \"%s\"\n",
378  print_reference(r);
379  fprintf(stderr, "\n");
380  }, refs);
381  }
382 
384 
385  return sel;
386 }
387 ␌
388 /* Debugging functions (to be augmented for GAPs) */
389 void dump_cell(cell c)
390 {
391  fprintf(stderr, "Cell %p = (cell_tag=%u, reference=%p)\n", c, cell_tag(c),
393 }
394 
395 void dump_effect(effect e)
396 {
397  cell c = effect_cell(e);
398  action ac = effect_action(e);
399  action_kind ak = action_read_p(ac)? action_read(ac):
400  action_write(ac);
403 
405  fprintf(stderr, "Effect %p = (domain=%td, cell=%p, action=%p,"
406  " action_kind=%p, approximation=%p, descriptor=%p\n",
407  e, effect_domain_number(e), c, ac, ak, ap, d);
408  dump_cell(c);
409 }
410 
411 void dump_effects(list le)
412 {
413  int i = 1;
414  FOREACH(EFFECT, e, le) {
415  fprintf(stderr, "%d ", i++);
416  dump_effect(e);
417  }
418 }
419 ␌
420 /* Check if a reference appears more than once in the effect list. If
421  persistant_p is true, do not go thru persistant arcs. Else, use all
422  references. */
423 bool effects_reference_sharing_p(list el, bool persistant_p) {
424  bool sharing_p = false;
425  list srl = NIL; /* store reference list */
426  list erl = NIL; /* environment reference list */
427  list tdrl = NIL; /* type declaration reference list */
428 
429  //list ce = list_undefined; /* current effect */
430  //for (ce = el; !ENDP(ce); POP(ce)) {
431  //effect e = EFFECT(CAR(ce));
432  FOREACH(EFFECT,e,el) {
433  cell c = effect_cell(e);
435 
436  pips_assert("effect e is consistent", effect_consistent_p(e));
437 
438  if(persistant_p) {
439  if(cell_reference_p(c))
440  r = cell_reference(c);
441  } else
442  r = effect_any_reference(e);
443 
444  if(!reference_undefined_p(r)) {
445  /* FI: I though about parametrizing thru a list, but this
446  requires to conditional affectation, before and after each
447  loop body. Hence the cut-and-paste. */
448  if(store_effect_p(e)) {
449  if(gen_in_list_p((void *)r, srl)) {
450  fprintf(stderr, "this effect shares its reference with "
451  "another effect in list srl\n");
452  (*effect_prettyprint_func)(e);
453  sharing_p = true;
454  break;
455  } else {
456  srl = CONS(REFERENCE, r, srl);
457  }
458  } else if(environment_effect_p(e)) {
459  if(gen_in_list_p((void *)r, erl)) {
460  fprintf(stderr, "this effect shares its reference with "
461  "another effect in list srl\n");
462  (*effect_prettyprint_func)(e);
463  sharing_p = true;
464  break;
465  } else {
466  erl = CONS(REFERENCE, r, erl);
467  }
468  } else if(type_declaration_effect_p(e)) {
469  if(gen_in_list_p((void *)r, tdrl)) {
470  fprintf(stderr, "this effect shares its reference with "
471  "another effect in list srl\n");
472  (*effect_prettyprint_func)(e);
473  sharing_p = true;
474  break;
475  } else {
476  tdrl = CONS(REFERENCE, r, tdrl);
477  }
478  } else {
479  }
480  }
481  }
482  return sharing_p;
483 }
484 
485 /************************ anywhere effects ********************/
486 
487 /**
488  @return a new anywhere effect.
489  @param act is an action tag
490  act don't have to be use by another effects (make a copy)
491 
492  Allocate a new anywhere effect using generic function
493  reference_to_effect_func, and the anywhere entity on demand
494  which may not be best if we want to express it's aliasing with all
495  module areas. In the later case, the anywhere entity should be
496  generated by bootstrap and be updated each time new areas are
497  declared by the parsers. I do not use a persistant anywhere
498  reference to avoid trouble with convex-effect nypassing of the
499  persistant pointer. (re-used from original non-generic function
500  anywhere_effect.)
501 
502  Action a is integrated in the new effect (aliasing).
503 
504  FI: the type should always be passed and ignored according to
505  ALIAS_ACROSS_TYPES
506  */
508 {
509  // functions that can be pointed by reference_to_effect_func:
510  // reference_to_simple_effect
511  // reference_to_convex_region
512  // reference_to_reference_effect
513  effect anywhere_eff = (*reference_to_effect_func)(
514  make_reference(anywhere_ent, NIL),
515  act, false);
516  effect_to_may_effect(anywhere_eff);
517  return anywhere_eff;
518 }
519 
521 {
522  entity anywhere_ent = entity_all_locations();
523  effect anywhere_eff = make_some_anywhere_effect(act, anywhere_ent);
524 
525  return anywhere_eff;
526 }
527 
529 {
530  entity anywhere_ent = entity_undefined;
531  if(get_bool_property("ALIASING_ACROSS_TYPES")) {
532  anywhere_ent = entity_all_locations();
533  }
534  else {
536  // FI: if t is not a pointer type, returns t...
537  type pt = type_to_pointed_type(t);
538  anywhere_ent = entity_typed_anywhere_locations(pt);
539  }
540  effect anywhere_eff = make_some_anywhere_effect(act, anywhere_ent);
541 
542  return anywhere_eff;
543 }
544 
545 /* Make a typed anywhere effect if possible according to ALIASING_ACROSS_TYPES */
547 {
548  entity anywhere_ent = entity_undefined;
549  if(get_bool_property("ALIASING_ACROSS_TYPES")) {
550  anywhere_ent = entity_all_locations();
551  }
552  else {
553  anywhere_ent = entity_typed_anywhere_locations(t);
554  }
555  effect anywhere_eff = make_some_anywhere_effect(act, anywhere_ent);
556 
557  return anywhere_eff;
558 }
559 
561 {
562 
564 }
565 
567 {
568 
570 }
571 
573 {
574  list l = NIL;
577  return l;
578 }
579 
580 
581 /**
582  remove duplicate anywhere effects and keep anywhere effects and
583  effects not combinable with anywhere effects.
584 
585  @param l_eff is a list of effects
586  @return a new list with no sharing with the initial effect list.
587 
588  */
590 {
591  list l_tmp;
592  list l_res;
593  bool anywhere_w_p = false;
594  bool anywhere_r_p = false;
595 
596  l_tmp = l_eff;
597  while ((!anywhere_w_p || !anywhere_r_p) && !ENDP(l_tmp))
598  {
599  effect eff = EFFECT(CAR(l_tmp));
600  if (anywhere_effect_p(eff))
601  {
602  anywhere_w_p = anywhere_w_p || effect_write_p(eff);
603  anywhere_r_p = anywhere_r_p || effect_read_p(eff);
604  }
605 
606  POP(l_tmp);
607  }
608 
609  l_res = NIL;
610 
611  if (anywhere_r_p)
612  l_res = gen_nconc(l_res,
614  NIL));
615  if (anywhere_w_p)
616  l_res = gen_nconc(l_res,
618  NIL));
619 
620 
621  l_tmp = l_eff;
622  while (!ENDP(l_tmp))
623  {
624  effect eff = EFFECT(CAR(l_tmp));
625  pips_debug_effect(4, "considering effect:", eff);
626 
627  if (malloc_effect_p(eff) || io_effect_p(eff) ||
628  (!get_bool_property("USER_EFFECTS_ON_STD_FILES") && std_file_effect_p(eff)) ||
629  (effect_write_p(eff) && !anywhere_w_p) ||
630  (effect_read_p(eff) && !anywhere_r_p))
631  {
632  pips_debug(4, "added\n");
633  // functions that can be pointed by effect_dup_func:
634  // simple_effect_dup
635  // region_dup
636  // copy_effect
637  l_res = gen_nconc(l_res, CONS(EFFECT, (*effect_dup_func)(eff), NIL));
638  }
639  POP(l_tmp);
640  }
641 
642  return l_res;
643 }
644 
645 
646 /************************ effects on special pointer values ********************/
647 
648 /*
649  The semantics of the resulting effects is not well defined...
650  These effects should be used with care, as intermediaries.
651  */
652 
653 /**
654  @return a new effect on null_pointer_value.
655  @param act is an action tag
656  act don't have to be use by another effects (make a copy)
657 
658  Allocate a new anywhere effect using generic function
659  reference_to_effect_func, and the anywhere entity on demand
660  which may not be best if we want to express it's aliasing with all
661  module areas. In the later case, the anywhere entity should be
662  generated by bootstrap and be updated each time new areas are
663  declared by the parsers. I do not use a persistant anywhere
664  reference to avoid trouble with convex-effect nypassing of the
665  persistant pointer. (re-used from original non-generic function
666  anywhere_effect.)
667 
668  Action a is integrated in the new effect (aliasing).
669  */
671 {
672  entity null_ent = null_pointer_value_entity();
673  effect null_eff = effect_undefined;
674 
675  // functions that can be pointed by reference_to_effect_func:
676  // reference_to_simple_effect
677  // reference_to_convex_region
678  // reference_to_reference_effect
679  null_eff = (*reference_to_effect_func)(
680  make_reference(null_ent, NIL),
681  act, false);
682  return null_eff;
683 }
684 
686 {
688 }
689 
690 /**
691  @return a new effect on undefined_pointer_value.
692  @param act is an action tag
693  act don't have to be use by another effects (make a copy)
694 
695  Allocate a new effect on undefined pointer value using generic function
696  reference_to_effect_func, and the anywhere entity on demand
697  which may not be best if we want to express it's aliasing with all
698  module areas. In the later case, the anywhere entity should be
699  generated by bootstrap and be updated each time new areas are
700  declared by the parsers. I do not use a persistant anywhere
701  reference to avoid trouble with convex-effect nypassing of the
702  persistant pointer. (re-used from original non-generic function
703  anywhere_effect.)
704 
705  Action a is integrated in the new effect (aliasing).
706  */
708 {
709  entity undefined_ent = undefined_pointer_value_entity();
710  effect undefined_eff = effect_undefined;
711 
712  // functions that can be pointed by reference_to_effect_func:
713  // reference_to_simple_effect
714  // reference_to_convex_region
715  // reference_to_reference_effect
716  undefined_eff = (*reference_to_effect_func)(
717  make_reference(undefined_ent, NIL),
718  act, false);
719  return undefined_eff;
720 }
721 
723 {
725 }
726 
727 
728 /********************** Effects on all accessible paths ***************/
729 
730 /**
731  @param eff_write a write effect
732  @param is the action of the generated effects :
733  'r' for read, 'w' for write, and 'x' for read and write.
734  @return a list of effects. beware : eff_write is included in the list.
735 
736  */
738 {
739  list l_res = NIL;
740  effect eff_read = effect_undefined;
741  effect eff_write = effect_undefined;
742 
743  pips_assert("effect is defined \n", !effect_undefined_p(eff));
744 
745  if (act == 'x')
746  {
747  eff_write = eff;
748  effect_action_tag(eff_write) = is_action_write;
749  // functions that can be pointed by effect_dup_func:
750  // simple_effect_dup
751  // region_dup
752  // copy_effect
753  eff_read = (*effect_dup_func)(eff_write);
754  effect_action_tag(eff_read) = is_action_read;
755  }
756  else if (act == 'r')
757  {
758 
759  eff_read = eff;
760  effect_action_tag(eff_read) = is_action_read;
761  eff_write = effect_undefined;
762  }
763  else
764  {
765  eff_read = effect_undefined;
766  eff_write = eff;
767  effect_action_tag(eff_write) = is_action_write;
768  }
769 
770  ifdebug(8)
771  {
772  pips_debug(8, "adding effects to l_res : \n");
773  if(!effect_undefined_p(eff_write))
774  (*effect_prettyprint_func)(eff_write);
775  if(!effect_undefined_p(eff_read))
776  (*effect_prettyprint_func)(eff_read);
777  }
778 
779  if(!effect_undefined_p(eff_write))
780  l_res = gen_nconc(l_res, CONS(EFFECT, eff_write, NIL));
781  if(!effect_undefined_p(eff_read))
782  l_res = gen_nconc(l_res, CONS(EFFECT, eff_read, NIL));
783 
784  return l_res;
785 }
786 
787 /**
788  @param eff is an effect whose reference is the beginning access path.
789  it is not modified or re-used.
790  @param eff_type is the type of the object represented by the effect
791  access path. This avoids computing it at each step.
792  @param act is the action of the generated effects :
793  'r' for read, 'w' for write, and 'x' for read and write.
794  @param level represents the maximum number of dereferencing dimensions
795  in the resulting effects.
796  @param pointer_only must be set to true to only generate paths to pointers.
797  @return a list of effects on all the accessible paths from eff reference.
798  */
800  type eff_type,
801  tag act,
802  bool add_eff,
803  int level,
804  bool pointers_only)
805 {
806  list l_res = NIL;
807  pips_assert("the effect must be defined\n", !effect_undefined_p(eff));
808  pips_debug_effect(6, "input effect:", eff);
809  pips_debug(6, "input type: %s (%s)\n",
810  string_of_type(eff_type),
811  type_to_string(eff_type));
812  pips_debug(6, "add_eff is %s\n", add_eff? "true": "false");
813  if (type_with_const_qualifier_p(eff_type))
814  {
815  pips_debug(6, "const qualifier\n");
816  if (act == 'w')
817  return NIL;
818  else if (act == 'x')
819  act = 'r';
820  }
821 
822 
823  if (FILE_star_type_p(eff_type))
824  {
825  /* there is no other accessible path */
826  pips_debug(6, "FILE star path -> returning NIL or the path itself \n");
827  if (add_eff)
828  l_res = effect_to_list(eff);
829  }
832  {
833  /* there is no other accessible path */
834  pips_debug(6, "anywhere effect -> returning NIL \n");
835 
836  }
837  else
838  {
839  effect eff_write = effect_undefined;
840 
841  /* this may lead to memory leak if no different access path is
842  * reachable */
843  // functions that can be pointed by effect_dup_func:
844  // simple_effect_dup
845  // region_dup
846  // copy_effect
847  eff_write = (*effect_dup_func)(eff);
848 
849  pips_debug(6, "level is %d\n", level);
850  pips_debug_effect(6, "considering effect : \n", eff);
851 
852  switch (type_tag(eff_type))
853  {
854  case is_type_variable :
855  {
856  variable v = type_variable(eff_type);
857  basic b = variable_basic(v);
858  bool add_array_dims = false;
859 
860  pips_debug(8, "variable case, of dimension %d\n",
861  (int) gen_length(variable_dimensions(v)));
862 
863  /* we first add the array dimensions if any */
864  FOREACH(DIMENSION, c_t_dim,
866  {
867  // functions that can be pointed by effect_add_expression_dimension_func:
868  // simple_effect_add_expression_dimension
869  // convex_region_add_expression_dimension
870  (*effect_add_expression_dimension_func)
871  (eff_write, make_unbounded_expression());
872  add_array_dims = true;
873  }
874 
875  /* if the basic if an end basic, add the path if add_eff is true
876  or if there has been array dimensions added to the original input path */
877  if(basic_int_p(b) ||
878  basic_float_p(b) ||
879  basic_logical_p(b) ||
880  basic_overloaded_p(b) ||
881  basic_complex_p(b) || basic_bit_p(b) || basic_string_p(b)) /* should I had basic_string_p here or make a special case?*/
882  {
883  pips_debug(6, "end basic case\n");
884  if ((add_array_dims || add_eff) && !pointers_only)
885  l_res = gen_nconc
886  (l_res,
887  effect_to_effects_with_given_tag(eff_write,act));
888  }
889  /* If the basic is a pointer type, we must add an effect
890  with a supplementary dimension, and then recurse
891  on the pointed type.
892  */
893  else if(basic_pointer_p(b))
894  {
895  if (add_array_dims || add_eff)
896  l_res = gen_nconc
897  (l_res,
898  effect_to_effects_with_given_tag(eff_write,act));
899  if (level > 0)
900  {
901  pips_debug(8, "pointer case, \n");
902 
903  // functions that can be pointed by effect_dup_func:
904  // simple_effect_dup
905  // region_dup
906  // copy_effect
907  eff_write = (*effect_dup_func)(eff_write);
908  // functions that can be pointed by effect_add_expression_dimension_func:
909  // simple_effect_add_expression_dimension
910  // convex_region_add_expression_dimension
911  (*effect_add_expression_dimension_func)
912  (eff_write, make_unbounded_expression());
913 
914  /*l_res = gen_nconc
915  (l_res,
916  effect_to_effects_with_given_tag(eff_write,act));*/
917 
918  l_res = gen_nconc
919  (l_res,
921  (eff_write, basic_pointer(b), act, /*false*/ true, level - 1, pointers_only));
922  }
923  else
924  {
925  pips_debug(8, "pointer case with level == 0 -> no additional dimension\n");
926  }
927  }
928  else if (basic_derived_p(b))
929  {
931  {
932  pips_debug(8, "struct or union case\n");
933  list l_fields = type_fields(entity_type(basic_derived(b)));
934  FOREACH(ENTITY, f, l_fields)
935  {
936  type current_type = entity_basic_concrete_type(f);
937  // functions that can be pointed by effect_dup_func:
938  // simple_effect_dup
939  // region_dup
940  // copy_effect
941  effect current_eff = (*effect_dup_func)(eff_write);
942 
943  // we add the field index
944  effect_add_field_dimension(current_eff, f);
945 
946  // and call ourselves recursively
947  l_res = gen_nconc
948  (l_res,
950  (current_eff, current_type, act, true, level, pointers_only));
951  }
952  }
953  }
954  else if (!basic_typedef_p(b))
955  {
956 
957  if (!pointers_only && (add_array_dims || add_eff))
958  l_res = gen_nconc
959  (l_res,
960  effect_to_effects_with_given_tag(eff_write,act));
961  }
962  else
963  {
964  pips_internal_error("unexpected typedef basic");
965  }
966 
967  break;
968  }
969  case is_type_void:
970  {
971  pips_debug(8, "void case\n");
972  if (add_eff)
973  l_res = CONS(EFFECT, eff, NIL);
974  break;
975  }
976  case is_type_functional:
977  pips_debug(8, "functional case\n");
978  pips_user_warning("possible effect through indirect call (type is: %s(%s)) -> returning anywhere\n",
979  string_of_type(eff_type),
980  type_to_string(eff_type));
981  pips_debug_effect(0, "", eff);
983  break;
984  case is_type_struct:
985  case is_type_union:
986  case is_type_enum:
987  pips_debug(8, "agregate type case\n");
988  pips_internal_error("aggregate type not handeld yet\n");
989  break;
990 
991  case is_type_area:
992  case is_type_statement:
993  case is_type_varargs:
994  case is_type_unknown:
995  pips_internal_error("unexpected type in this context \n");
996  break;
997  default:
998  {
999  pips_internal_error("unknown type tag\n");
1000  }
1001  break;
1002  } /*switch */
1003  } /* else */
1004 
1005  pips_debug_effects(8, "output effects:\n", l_res);
1006 
1007  return(l_res);
1008 }
1009 
1010 /**
1011  @param eff is an effect whose reference is the beginning access path.
1012  it is not modified or re-used.
1013  @param eff_type is the type of the object represented by the effect
1014  access path. This avoids computing it at each step.
1015  @param act is the action of the generated effects :
1016  'r' for read, 'w' for write, and 'x' for read and write.
1017  @return a list of effects on all the accessible paths from eff reference.
1018  */
1020  type eff_type,
1021  tag act)
1022 {
1024  eff_type,
1025  act,
1026  false,
1027  10, /* to avoid too long paths until GAPS are handled */
1028  false);
1029 }
1030 
1031 /******************************************************************/
1032 
1033 
1034 /**
1035  NOT YET IMPLEMENTED FOR VARARGS AND FUNCTIONAL TYPES.
1036 
1037  @param eff is an effect
1038  @return true if the effect reference maybe an access path to a pointer
1039 */
1040 /* FI: this function is not used anymore, 13 July 2016 */
1041 bool r_effect_pointer_type_p(effect eff, list l_ind, type ct)
1042 {
1043  bool p = false, finished = false;
1044 
1045  pips_debug(7, "begin with type %s\n and number of indices : %d\n",
1046  string_of_type(ct),
1047  (int) gen_length(l_ind));
1048  while (!finished)
1049  {
1050  switch (type_tag(ct))
1051  {
1052  case is_type_variable :
1053  {
1054  variable v = type_variable(ct);
1055  basic b = variable_basic(v);
1056  list l_dim = variable_dimensions(v);
1057 
1058  pips_debug(8, "variable case, of basic %s, of dimension %d\n",
1059  basic_to_string(b),
1060  (int) gen_length(variable_dimensions(v)));
1061 
1062  while (!ENDP(l_dim) && !ENDP(l_ind))
1063  {
1064  POP(l_dim);
1065  POP(l_ind);
1066  }
1067 
1068  if(ENDP(l_ind) && ENDP(l_dim))
1069  {
1070  if(basic_pointer_p(b))
1071  {
1072  p = true;
1073  finished = true;
1074  }
1075  else
1076  finished = true;
1077  }
1078  else if (ENDP(l_dim)) /* && !ENDP(l_ind) by construction */
1079  {
1080  pips_assert("the current basic should be a pointer or a derived\n",
1081  basic_pointer_p(b) || basic_derived_p(b));
1082 
1083  if (basic_pointer_p(b))
1084  {
1085  ct = basic_pointer(b);
1086  POP(l_ind);
1087  }
1088  else /* b is a derived */
1089  {
1090  ct = entity_type(basic_derived(b));
1091  p = r_effect_pointer_type_p(eff, l_ind, ct);
1092  finished = true;
1093  }
1094 
1095  }
1096  else /* ENDP(l_ind) but !ENDP(l_dim) */
1097  {
1098  finished = true;
1099  }
1100 
1101  break;
1102  }
1103  case is_type_struct:
1104  case is_type_union:
1105  case is_type_enum:
1106  {
1107  list l_ent = type_fields(ct);
1108  expression field_exp = EXPRESSION(CAR(l_ind));
1109  entity field = entity_undefined;
1110 
1111  pips_debug(7, "field case, with field expression : %s \n",
1112  expression_to_string(field_exp));
1113 
1114  /* If the field is known, we only look at the corresponding type.
1115  If not, we have to recursively look at each field
1116  */
1117  if (!unbounded_expression_p(field_exp))
1118  {
1119  pips_assert("the field expression must be a reference\n",
1120  expression_reference_p(field_exp));
1121  field = expression_variable(field_exp);
1122  if (variable_phi_p(field))
1123  field = entity_undefined;
1124  }
1125 
1126  if (!entity_undefined_p(field))
1127  {
1128  /* the current type is the type of the field */
1129  ct = entity_basic_concrete_type(field);
1130  p = r_effect_pointer_type_p(eff, CDR(l_ind), ct);
1131  /* free_type(ct); */
1132  ct = type_undefined;
1133  finished = true;
1134  }
1135  else
1136  /* look at each field until a pointer is found*/
1137  {
1138  while (!ENDP(l_ent) && p)
1139  {
1140  type new_ct = entity_basic_concrete_type(ENTITY(CAR(l_ent)));
1141  p = r_effect_pointer_type_p(eff, CDR(l_ind),
1142  new_ct);
1143  POP(l_ent);
1144  }
1145  finished = true;
1146  }
1147  break;
1148  }
1149  default:
1150  {
1151  pips_internal_error("case not handled yet");
1152  }
1153  } /*switch */
1154 
1155  }/*while */
1156  pips_debug(8, "end with p = %s\n", p== false ? "false" : "true");
1157  return p;
1158 
1159 }
1160 
1161 
1162 /**
1163  NOT YET IMPLEMENTED FOR VARARGS AND FUNCTIONAL TYPES.
1164 
1165  FI: NOT FULLY IMPLEMENTED FOR ALL POSSIBLE ABSTRACT LOCATIONS
1166 
1167  @param eff is an effect
1168  @return true if the effect reference maybe an access path to a pointer
1169 */
1170 bool effect_pointer_type_p(effect eff)
1171 {
1172  bool p = false;
1174  // list l_ind = reference_indices(ref);
1175  entity ent = reference_variable(ref);
1176  // type t = entity_basic_concrete_type(ent);
1177 
1178  pips_debug(8, "begin with effect reference %s\n",
1180  if (entity_abstract_location_p(ent)) {
1181  // FI: potentially, we have other abstract locations that are not typed
1182  p = true;
1183  }
1184  else {
1185  // p = r_effect_pointer_type_p(eff, l_ind, t);
1187  p = pointer_type_p(et);
1188  }
1189 
1190  pips_debug(8, "end with p = %s\n", p== false ? "false" : "true");
1191  return p;
1192 
1193 }
1194 
1195 
1196 
1198 {
1200  type ct; /* current_type */
1201 
1202  list l_inds = reference_indices(ref);
1203 
1204  type t = type_undefined; /* result */
1205  bool finished = false;
1206 
1207  pips_debug(8, "beginning with reference : %s\n", reference_to_string(ref));
1208 
1209  ct = bct;
1210  while (! finished)
1211  {
1212  basic cb = variable_basic(type_variable(ct)); /* current basic */
1213  list cd = variable_dimensions(type_variable(ct)); /* current type dimensions */
1214 
1215  while(!ENDP(cd) && !ENDP(l_inds))
1216  {
1217  pips_debug(8, "poping one array dimension \n");
1218  POP(cd);
1219  POP(l_inds);
1220  }
1221 
1222  if(ENDP(l_inds))
1223  {
1224  pips_debug(8, "end of reference indices, generating type\n");
1227  gen_full_copy_list(cd),
1228  NIL));
1229  finished = true;
1230  }
1231  else /* ENDP (cd) && ! ENDP(l_inds) */
1232  {
1233  switch (basic_tag(cb))
1234  {
1235  case is_basic_pointer:
1236  /* in an effect reference there is always an index for a pointer */
1237  pips_debug(8, "poping pointer dimension\n");
1238  POP(l_inds);
1239  ct = basic_pointer(cb);
1240  break;
1241  case is_basic_derived:
1242  {
1243  /* we must know which field it is, else return an undefined type */
1244  expression field_exp = EXPRESSION(CAR(l_inds));
1245  entity field = entity_undefined;
1246  pips_debug(8, "field dimension : %s\n",
1247  expression_to_string(field_exp));
1248 
1249  if (!unbounded_expression_p(field_exp))
1250  {
1251  pips_assert("the field expression must be a reference\n",
1252  expression_reference_p(field_exp));
1253  field = expression_variable(field_exp);
1254  if (variable_phi_p(field))
1255  field = entity_undefined;
1256  }
1257 
1258  if (!entity_undefined_p(field))
1259  {
1260  pips_debug(8, "known field, poping field dimension\n");
1261  bct = entity_basic_concrete_type(field);
1262  ct = bct;
1263  POP(l_inds);
1264  }
1265  else
1266  {
1267  pips_debug(8, "unknown field, returning type_undefined\n");
1268  t = type_undefined;
1269  finished = true;
1270  }
1271  }
1272  break;
1273  case is_basic_int:
1274  case is_basic_float:
1275  case is_basic_logical:
1276  case is_basic_complex:
1277  case is_basic_string:
1278  case is_basic_bit:
1279  case is_basic_overloaded:
1280  pips_internal_error("fundamental basic not expected here ");
1281  break;
1282  case is_basic_typedef:
1283  pips_internal_error("typedef not expected here ");
1284  } /* switch (basic_tag(cb)) */
1285  }
1286 
1287  } /* while (!finished) */
1288 
1289 
1290  pips_debug(6, "returns with %s\n", string_of_type(t));
1291  return t;
1292 
1293 }
1294 
1295 
1296 ␌
1298 {
1299  FOREACH(EFFECT, r, rl) {
1300  descriptor rd = effect_descriptor(r);
1301 
1302  if(descriptor_convex_p(rd)) {
1303  Psysteme rsc = descriptor_convex(rd);
1304 
1305  pips_assert("rsc is weakly consistent", sc_weak_consistent_p(rsc));
1306  }
1307  }
1308  return true;
1309 }
1310 
1312 {
1313  descriptor rd = effect_descriptor(r);
1314 
1315  if(descriptor_convex_p(rd)) {
1316  Psysteme rsc = descriptor_convex(rd);
1317 
1318  pips_assert("rsc is weakly consistent", sc_weak_consistent_p(rsc));
1319  }
1320 
1321  return true;
1322 }
1323 
1324 /**
1325  * Effects are not copied but a new list is built.
1326  *
1327  * Filter out the memory/store write effects on pointers
1328  *
1329  * The list is/should be simplified when abstract locations are used.
1330  *
1331  * By definition, the untyped anywhere abstract location includes pointers.
1332  *
1333  * FI: this function is to be completed for abstract locations that
1334  * are not the all locations abstract location, and particularly for
1335  * those that are typed.
1336  */
1338 {
1339  list l_cumu_eff = load_rw_effects_list(s);
1340  list l_res = NIL;
1341  bool anywhere_p = false;
1342 
1343  ifdebug(6){
1344  pips_debug(6, " effects before selection: \n");
1345  (*effects_prettyprint_func)(l_cumu_eff);
1346  }
1347 
1348  FOREACH(EFFECT, eff, l_cumu_eff)
1349  {
1350  if (!anywhere_p && effect_write_p(eff))
1351  {
1352  if (anywhere_effect_p(eff))
1353  anywhere_p = true; // FI: why not break here?
1354  else if (store_effect_p(eff) && effect_pointer_type_p(eff))
1355  l_res = gen_nconc(l_res, CONS(EFFECT, eff, NIL));
1356  }
1357  }
1358  if (anywhere_p)
1359  {
1360  gen_free_list(l_res);
1362  }
1363 
1364  ifdebug(6){
1365  pips_debug(6, " effects after selection: \n");
1366  (*effects_prettyprint_func)(l_res);
1367  }
1368 
1369  return l_res;
1370 }
1371 
1372 /******************************************************************/
1373 
1374 
1375 static bool effects_reference_indices_may_equal_p(expression ind1, expression ind2)
1376 {
1378  return true;
1379  else
1380  return same_expression_p(ind1, ind2);
1381 }
1382 
1383 /**
1384  This function should be instanciated differently for simple and convex
1385  effects : much more work should be done for convex effects.
1386 
1387  @return true if the effects have comparable access paths
1388  in which case result is set to
1389  0 if the effects paths may be equal
1390  1 if eff1 access path may lead to eff2 access path
1391  -1 if eff2 access path may lead to eff1 access path
1392  false otherwise.
1393 */
1394 static bool effects_access_paths_comparable_p(effect eff1, effect eff2,
1395  int *result)
1396 {
1397  bool comparable_p = true; /* assume they are comparable */
1398  reference ref1 = effect_any_reference(eff1);
1399  reference ref2 = effect_any_reference(eff2);
1400  list linds1 = reference_indices(ref1);
1401  list linds2 = reference_indices(ref2);
1402 
1403  pips_debug_effect(8, "begin\neff1 = \n", eff1);
1404  pips_debug_effect(8, "begin\neff2 = \n", eff2);
1405 
1406  /* to be comparable, they must have the same entity */
1407  comparable_p = same_entity_p(reference_variable(ref1),
1408  reference_variable(ref2));
1409 
1410  while( comparable_p && !ENDP(linds1) && !ENDP(linds2))
1411  {
1412  if (!effects_reference_indices_may_equal_p(EXPRESSION(CAR(linds1)),
1413  EXPRESSION(CAR(linds2))))
1414  comparable_p = false;
1415 
1416  POP(linds1);
1417  POP(linds2);
1418  }
1419 
1420  if (comparable_p)
1421  {
1422  *result = (int) (gen_length(linds2) - gen_length(linds1)) ;
1423  if (*result != 0) *result = *result / abs(*result);
1424  }
1425 
1426  pips_debug(8, "end with comparable_p = %s and *result = %d",
1427  comparable_p ? "true" : "false", *result);
1428 
1429  return comparable_p;
1430 }
1431 
1432 /* See if list el contain an abstract effect with action ea and type
1433  * et
1434  */
1436 {
1437  bool found_p = false;
1438  FOREACH(EFFECT, e, el) {
1439  if(action_equal_p(effect_action(e), ea)) {
1441  if(ENDP(reference_indices(er))) {
1442  entity ee = reference_variable(er);
1443  // FI: we are only interested in *ANY_MODULE*:*ANYWHERE*_bxx entities */
1444  if(entity_abstract_location_p(ee)) {
1445  type eet = entity_type(ee); // FI: named type should not be used for abstract locations
1446  if(type_equal_p(et, eet)) {
1447  found_p = true;
1448  break;
1449  }
1450  }
1451  }
1452  }
1453  }
1454  return found_p;
1455 }
1456 
1457 /* do not reuse l_eff after calling this function
1458  *
1459  *
1460  */
1461 list generic_effects_store_update(list l_eff, statement s, bool backward_p)
1462 {
1463  transformer t; /* transformer of statement s */
1464  list l_eff_pointers;
1465  list l_res = NIL;
1466  bool anywhere_w_p = false;
1467  bool anywhere_r_p = false;
1468 
1469  pips_debug(5, "begin\n");
1470 
1471  debug_on("SEMANTICS_DEBUG_LEVEL");
1472  t = (*load_completed_transformer_func)(s);
1473  debug_off();
1474 
1475  if (l_eff !=NIL)
1476  {
1477  /* first change the store of the descriptor */
1478  if (backward_p) {
1479  // functions that can be pointed by effects_transformer_composition_op:
1480  // effects_composition_with_transformer_nop
1481  // effects_undefined_composition_with_transformer
1482  // convex_regions_transformer_compose
1483  // simple_effects_composition_with_effect_transformer
1484  l_eff = (*effects_transformer_composition_op)(l_eff, t);
1485  }
1486  else {
1487  // functions that can be pointed by effects_transformer_inverse_composition_op:
1488  // effects_composition_with_transformer_nop
1489  // effects_undefined_composition_with_transformer
1490  // convex_regions_inverse_transformer_compose
1491  l_eff = (*effects_transformer_inverse_composition_op)(l_eff, t);
1492  }
1493 
1494  ifdebug(5){
1495  pips_debug(5, " effects after composition with transformer: \n");
1496  (*effects_prettyprint_func)(l_eff);
1497  }
1498 
1499  if (get_bool_property("EFFECTS_POINTER_MODIFICATION_CHECKING"))
1500  {
1501  /* then change the effects references if some pointer is modified */
1502  /* backward_p is not used here because we lack points_to information
1503  * and we thus generate anywhere effects
1504  */
1505  l_eff_pointers = statement_modified_pointers_effects_list(s);
1506 
1507  while( !ENDP(l_eff) &&
1508  ! (anywhere_w_p && anywhere_r_p))
1509  {
1510  list l_eff_p_tmp = l_eff_pointers;
1511  effect eff = EFFECT(CAR(l_eff));
1512  bool eff_w_p = effect_write_p(eff);
1513  bool found = false;
1514 
1515 
1516  while( !ENDP(l_eff_p_tmp) &&
1517  !((eff_w_p && anywhere_w_p) || (!eff_w_p && anywhere_r_p)))
1518  {
1519  effect eff_p = EFFECT(CAR(l_eff_p_tmp));
1520  effect new_eff = effect_undefined;
1521  int comp_res = 0;
1522 
1523  if(store_effect_p(eff)
1524  && effects_access_paths_comparable_p(eff, eff_p, &comp_res)
1525  // FI: I want a write effect by eff_p on a prefix of eff
1526  // && comp_res <=0 )
1527  && comp_res <0 )
1528  {
1529  if(!get_bool_property("EFFECTS_IGNORE_DEREFERENCING")) {
1530  found = true;
1531  if(get_bool_property("ALIASING_ACROSS_TYPES")) {
1533  if (eff_w_p)
1534  anywhere_w_p = true;
1535  else
1536  anywhere_r_p = true;
1537  }
1538  else {
1539  action ea = copy_action(effect_action(eff));
1540  reference er = effect_any_reference(eff);
1542  if(abstract_effect_in_effect_list_p(ea, et, l_res))
1543  new_eff = effect_undefined;
1544  else
1545  new_eff = make_generic_anywhere_effect(ea, er);
1546  }
1547  if(!effect_undefined_p(new_eff))
1548  l_res = gen_nconc(l_res, CONS(EFFECT, new_eff, NIL));
1549  }
1550  } /* if(effects_access_paths_comparable_p) */
1551 
1552  POP(l_eff_p_tmp);
1553  } /* while( !ENDP(l_eff_p_tmp))*/
1554 
1555  /* if we have found no modifiying pointer, we keep the effect */
1556  if (!found)
1557  {
1558  /* is the copy necessary ?
1559  * sg: yes, to be consistent with other branches of the test */
1560  // functions that can be pointed by effect_dup_func:
1561  // simple_effect_dup
1562  // region_dup
1563  // copy_effect
1564  l_res = gen_nconc(l_res, CONS(EFFECT,(*effect_dup_func)(eff) , NIL));
1565  }
1566 
1567  POP(l_eff);
1568  } /* while( !ENDP(l_eff)) */
1569 
1570  ifdebug(5){
1571  pips_debug(5, " effects after composition with pointer effects: \n");
1572  (*effects_prettyprint_func)(l_res);
1573  }
1574  } /* if (get_bool_property("EFFECTS_POINTER_MODIFICATION_CHECKING"))*/
1575  else
1576  l_res = l_eff;
1577  } /* if (l_eff !=NIL) */
1578 
1579  free_transformer(t);
1580 
1581  return l_res;
1582 }
1583 
1584 /************ CONVERSION TO CONSTANT PATH EFFECTS ***********/
1585 
1586 
1587 
1588 
1589 /**
1590  @param l_pointer_eff is a list of effects that may involve access
1591  paths dereferencing pointers.
1592 
1593  @return a list of effects with no access paths dereferencing pointers.
1594 
1595  Two algorithms are currently used, depending on the value returned
1596  by get_use_points_to.
1597 
1598  If true, when there is an effect reference with a dereferencing
1599  dimension, eval_cell_with_points_to is called to find an equivalent
1600  constant path using points-to.
1601 
1602  If false, effect references with a dereferencing dimension are
1603  systematically replaced by anywhere effects.
1604  */
1606 {
1607  list le = NIL;
1608 
1609  pips_debug_effects(8, "input effects : \n", l_pointer_eff);
1610 
1611  FOREACH(EFFECT, eff, l_pointer_eff)
1612  {
1613  pips_debug_effect(8, "current effect : \n", eff);
1614 
1615  if(store_effect_p(eff))
1616  {
1617  //bool exact_p;
1618  //reference ref = effect_any_reference(eff);
1619 
1620  pips_debug(8, "store effect\n");
1621 
1622  // FI: should use package_effect_p() ?
1623  if (io_effect_p(eff)
1624  || malloc_effect_p(eff)
1625  || (!get_bool_property("USER_EFFECTS_ON_STD_FILES")
1626  && std_file_effect_p(eff)))
1627  {
1628  pips_debug(8, "special effect \n");
1629  // functions that can be pointed by effect_dup_func:
1630  // simple_effect_dup
1631  // region_dup
1632  // copy_effect
1633  le = CONS(EFFECT, (*effect_dup_func)(eff), le);
1634  }
1635  else
1636  {
1637  // functions that can be pointed by effect_to_constant_path_effects_func:
1638  // effect_to_constant_path_effects_with_no_pointer_information
1639  // simple_effect_to_constant_path_effects_with_points_to
1640  // simple_effect_to_constant_path_effects_with_pointer_values
1641  // convex_effect_to_constant_path_effects_with_points_to
1642  // convex_effect_to_constant_path_effects_with_pointer_values
1643  list l_const = (*effect_to_constant_path_effects_func)(eff);
1644  pips_debug(8,"computing the union\n");
1645  pips_debug_effects(8, "l_const before union: \n", le);
1646  pips_debug_effects(8, "le before union: \n", le);
1647  // functions that can be pointed by effects_union_op:
1648  // ProperEffectsMustUnion
1649  // RegionsMustUnion
1650  // ReferenceUnion
1651  // EffectsMustUnion
1652  le = (*effects_union_op)(l_const, le, effects_scalars_and_same_action_p);
1653  pips_debug_effects(8, "effects after union: \n", le);
1654  }
1655  }
1656  else
1657  {
1658  pips_debug(8, "non store effect\n");
1659  // functions that can be pointed by effect_dup_func:
1660  // simple_effect_dup
1661  // region_dup
1662  // copy_effect
1663  le = CONS(EFFECT, (*effect_dup_func)(eff), le);
1664  }
1665  }
1666 
1667  pips_debug_effects(8, "ouput effects : \n", le);
1668 
1669  return le;
1670 }
1671 
1672 
1674 {
1675  list le = NIL;
1676  bool exact_p;
1678 
1679  if (effect_reference_dereferencing_p(ref, &exact_p)) {
1680  if(!get_bool_property("EFFECTS_IGNORE_DEREFERENCING")) {
1682  if(!get_bool_property("USER_EFFECTS_ON_STD_FILES")
1683  && std_file_entity_p(e)) {
1684  // Preserve the effect as such because it cannot create
1685  // conflicts with user variables
1686  le = CONS(EFFECT, (*effect_dup_func)(eff), le);
1687  }
1688  else {
1689  pips_debug(8, "dereferencing case \n");
1690  effect neff =
1692  le = CONS(EFFECT, neff, le);
1693  }
1694  }
1695  }
1696  else {
1697  // functions that can be pointed by effect_dup_func:
1698  // simple_effect_dup
1699  // region_dup
1700  // copy_effect
1701  le = CONS(EFFECT, (*effect_dup_func)(eff), le);
1702  }
1703 
1704  return le;
1705 }
1706 
1708 {
1709  list cel = NIL;
1710  FOREACH(EFFECT, ef, el) {
1712  }
1713  return cel;
1714 }
1715 
1716 // moved here from accel-util
1717 
1718 /* find effects on entity `e' in statement `s'
1719  * cumulated effects for these statements must have been loaded
1720  */
1722 {
1723  list cummulated_effects = load_cumulated_rw_effects_list( s );
1724  FOREACH(EFFECT, eff, cummulated_effects)
1725  {
1727  entity re = reference_variable(r);
1729  {
1730  if( !entity_pointer_p(e) && (entity_scalar_p(e) || derived_entity_p(e)) ) {
1731  ifdebug(6) {
1732  pips_debug(6,"Found conflict on %s with effect : ",entity_name(e));
1733  void print_effect(effect e);
1734  print_effect(eff);
1735  }
1736  return true;
1737  }
1738  }
1739  }
1740  return false;
1741 }
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
action copy_action(action p)
ACTION.
Definition: effects.c:77
bool effect_consistent_p(effect p)
Definition: effects.c:457
void free_transformer(transformer p)
Definition: ri.c:2616
transformer make_transformer(list a1, predicate a2)
Definition: ri.c:2649
predicate make_predicate(Psysteme a1)
Definition: ri.c:1820
basic copy_basic(basic p)
BASIC.
Definition: ri.c:104
reference make_reference(entity a1, list a2)
Definition: ri.c:2083
variable make_variable(basic a1, list a2, list a3)
Definition: ri.c:2895
type make_type(enum type_utype tag, void *val)
Definition: ri.c:2706
transformer copy_transformer(transformer p)
TRANSFORMER.
Definition: ri.c:2613
static reference ref
Current stmt (an integer)
Definition: adg_read_paf.c:163
bool entity_null_locations_p(entity e)
test if an entity is the NULL POINTER
bool entity_abstract_location_p(entity al)
entity entity_typed_anywhere_locations(type t)
entity entity_all_locations()
eturn ANY_MODULE:ANYWHERE (the top of the lattice)
#define VALUE_ZERO
#define value_notzero_p(val)
void const char const char const int
int Value
Pcontrainte contrainte_make(Pvecteur pv)
Pcontrainte contrainte_make(Pvecteur pv): allocation et initialisation d'une contrainte avec un vecte...
Definition: alloc.c:73
bool vect_constant_p(Pvecteur)
bool vect_constant_p(Pvecteur v): v contains only a constant term, may be zero
Definition: predicats.c:211
#define pips_debug_effects(level, message, l_eff)
#define pips_debug_effect(level, message, eff)
for debug
list make_anywhere_read_write_memory_effects(void)
transformer load_undefined_transformer(statement)
bool effect_pointer_type_p(effect)
effect make_undefined_pointer_value_effect(action)
effect make_anywhere_effect(action)
void dump_cell(cell)
void dump_effect(effect)
list make_effects_for_array_declarations(list)
string vect_debug_entity_name(entity)
list statement_modified_pointers_effects_list(statement)
bool null_pointer_value_effect_p(effect)
void descriptor_variable_rename(descriptor, entity, entity)
effect make_some_anywhere_effect(action, entity)
bool abstract_effect_in_effect_list_p(action, type, list)
list effect_to_constant_path_effects_with_no_pointer_information(effect)
list load_proper_rw_effects_list(statement)
transformer descriptor_to_context(descriptor)
transformer transformer_remove_variable_and_dup(transformer, entity)
bool region_weakly_consistent_p(effect)
bool regions_weakly_consistent_p(list)
bool get_descriptor_range_p(void)
effect make_anywhere_write_memory_effect(void)
void effects_computation_no_init(const char *)
void set_descriptor_range_p(bool)
list clean_anywhere_effects(list)
list generic_effects_store_update(list, statement, bool)
bool undefined_pointer_value_effect_p(effect)
bool normalizable_and_linear_loop_p(entity, range)
descriptor descriptor_inequality_add(descriptor, Pvecteur)
bool effects_private_current_context_stack_initialized_p(void)
bool effects_scalars_and_same_action_p(effect, effect)
bool statement_has_a_formal_argument_write_effect_p(statement)
list effect_to_effects_with_given_tag(effect, tag)
list effects_to_constant_path_effects_with_no_pointer_information(list)
descriptor descriptor_append(descriptor, descriptor)
void effect_to_may_effect(effect)
effect make_anywhere_read_memory_effect(void)
list load_rw_effects_list(statement)
void(* effect_prettyprint_func)(effect)
list load_cumulated_rw_effects_list(statement)
effect make_typed_anywhere_effect(action, type)
bool find_write_effect_on_entity(statement, entity)
type simple_effect_reference_type(reference)
effect make_null_pointer_value_effect(action)
bool effects_reference_sharing_p(list, bool)
bool some_integer_scalar_read_or_write_effects_p(cons *)
bool empty_context_test_false(transformer)
effect(* effect_dup_func)(effect eff)
transformer load_undefined_context(statement)
effect make_generic_anywhere_effect(action, reference)
void dump_effects(list)
void effects_computation_no_reset(const char *)
list pointer_effects_to_constant_path_effects(list)
list generic_effect_generate_all_accessible_paths_effects_with_level(effect, type, tag, bool, int, bool)
list effect_to_list(effect)
void effect_add_field_dimension(effect, entity)
bool statement_io_effect_p(statement)
list generic_effect_generate_all_accessible_paths_effects(effect, type, tag)
bool effects_private_current_stmt_stack_initialized_p(void)
list summary_effects_from_declaration(const char *)
bool r_effect_pointer_type_p(effect, list, type)
#define effect_any_reference(e)
FI: cannot be used as a left hand side.
#define effect_write_p(eff)
#define effect_read_p(eff)
#define effect_scalar_p(eff) entity_scalar_p(effect_entity(eff))
#define effect_action_tag(eff)
#define variable_phi_p(e)
true if e is a phi variable PHI entities have a name like: REGIONS:PHI#, where # is a number.
bool type_declaration_effect_p(effect)
Definition: effects.c:1080
type points_to_reference_to_concrete_type(reference)
Definition: type.c:685
entity null_pointer_value_entity(void)
bool effect_reference_dereferencing_p(reference, bool *)
Definition: type.c:233
entity effect_entity(effect)
cproto-generated files
Definition: effects.c:52
action make_action_write_memory(void)
To ease the extension of action with action_kind.
Definition: effects.c:1011
bool abstract_pointer_value_cell_p(cell)
bool undefined_pointer_value_entity_p(entity)
bool store_effect_p(effect)
Definition: effects.c:1062
bool environment_effect_p(effect)
Definition: effects.c:1071
bool malloc_effect_p(effect)
Definition: effects.c:478
bool action_equal_p(action, action)
Definition: effects.c:1023
bool anywhere_effect_p(effect)
Is it an anywhere effect? ANYMMODULE:ANYWHERE
Definition: effects.c:346
bool std_file_effect_p(effect)
Definition: effects.c:519
action make_action_read_memory(void)
Definition: effects.c:1017
bool null_pointer_value_entity_p(entity)
entity undefined_pointer_value_entity(void)
pointer_values.c
bool io_effect_p(effect)
Definition: effects.c:501
#define cell_reference(x)
Definition: effects.h:469
#define effect_undefined_p(x)
Definition: effects.h:615
#define cell_preference(x)
Definition: effects.h:472
#define action_write(x)
Definition: effects.h:316
#define cell_reference_p(x)
Definition: effects.h:467
#define descriptor_convex_(x)
Definition: effects.h:600
#define effect_domain_number(x)
Definition: effects.h:638
#define effect_action(x)
Definition: effects.h:642
#define effect_undefined
Definition: effects.h:614
#define action_read(x)
Definition: effects.h:313
#define action_write_p(x)
Definition: effects.h:314
#define action_read_p(x)
Definition: effects.h:311
#define cell_tag(x)
Definition: effects.h:466
#define descriptor_convex_p(x)
Definition: effects.h:599
#define effect_descriptor(x)
Definition: effects.h:646
#define descriptor_undefined
Definition: effects.h:559
#define descriptor_convex(x)
Definition: effects.h:601
@ is_action_write
Definition: effects.h:293
@ is_action_read
Definition: effects.h:292
#define cell_preference_p(x)
Definition: effects.h:470
#define descriptor_none_p(x)
Definition: effects.h:602
#define effect_approximation(x)
Definition: effects.h:644
#define newgen_Psysteme(p)
Definition: effects.h:47
#define EFFECT(x)
EFFECT.
Definition: effects.h:608
#define effect_cell(x)
Definition: effects.h:640
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....
static entity a_variable
bool entities_may_conflict_p(entity e1, entity e2)
Check if two entities may conflict.
Definition: conflicts.c:984
entity get_current_module_entity(void)
Get the entity of the current module.
Definition: static.c:85
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
void gen_remove(list *cpp, const void *o)
remove all occurences of item o from list *cpp, which is thus modified.
Definition: list.c:685
#define POP(l)
Modify a list pointer to point on the next element of the list.
Definition: newgen_list.h:59
#define NIL
The empty list (nil in Lisp)
Definition: newgen_list.h:47
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
bool gen_in_list_p(const void *vo, const list lx)
tell whether vo belongs to lx
Definition: list.c:734
#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
#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
#define list_undefined
Undefined list definition :-)
Definition: newgen_list.h:69
#define MAP(_map_CASTER, _map_item, _map_code, _map_list)
Apply/map an instruction block on all the elements of a list (old fashioned)
Definition: newgen_list.h:226
list gen_full_copy_list(list l)
Copy a list structure with element copy.
Definition: list.c:535
#define debug_on(env)
Definition: misc-local.h:157
#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 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 DEFINE_GLOBAL_STACK(name, type)
#define stack_undefined
Definition: newgen_stack.h:55
int tag
TAG.
Definition: newgen_types.h:92
int f(int off1, int off2, int n, float r[n], float a[n], float b[n])
Definition: offsets.c:15
static char * module
Definition: pips.c:74
string reference_to_string(reference r)
Definition: expression.c:87
string expression_to_string(expression e)
Definition: expression.c:77
void print_reference(reference r)
Definition: expression.c:142
#define print_effect(e)
Definition: print.c:336
string string_of_type(const type)
Definition: type.c:56
string basic_to_string(basic)
Definition: type.c:87
#define IO_EFFECTS_PACKAGE_NAME
Implicit variables to handle IO effetcs.
#define NORMALIZE_EXPRESSION(e)
#define IO_EFFECTS_ARRAY_NAME
array of Logical UNits; it is more or less handled as the current file pointer; in C,...
entity FindEntity(const char *package, const char *name)
Retrieve an entity from its package/module name and its local name.
Definition: entity.c:1503
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 same_entity_p(entity e1, entity e2)
predicates on entities
Definition: entity.c:1321
bool std_file_entity_p(entity e)
Definition: entity.c:1232
bool fortran_module_p(entity m)
Test if a module is in Fortran.
Definition: entity.c:2799
bool derived_entity_p(entity e)
Definition: entity.c:1048
bool entity_pointer_p(entity e)
Definition: entity.c:745
list extract_references_from_declarations(list decls)
FI: this function has not yet been extended for C types!!!
Definition: entity.c:2834
expression make_unbounded_expression()
Definition: expression.c:4339
bool expression_reference_p(expression e)
Test if an expression is a reference.
Definition: expression.c:528
bool unbounded_expression_p(expression e)
Definition: expression.c:4329
entity expression_variable(expression e)
Definition: expression.c:532
bool same_expression_p(expression e1, expression e2)
this is slightly different from expression_equal_p, as it will return true for a+b vs b+a
Definition: expression.c:1426
bool variable_is_a_module_formal_parameter_p(entity, entity)
Definition: variable.c:1547
bool entity_scalar_p(entity)
The concrete type of e is a scalar type.
Definition: variable.c:1113
bool variable_return_p(entity)
True if a variable is the pseudo-variable used to store value returned by a function:
Definition: variable.c:1522
list type_fields(type)
Definition: type.c:3073
bool type_equal_p(type, type)
Definition: type.c:547
bool integer_scalar_entity_p(entity)
integer_scalar_entity_p() is obsolete; use entity_integer_scalar_p()
Definition: variable.c:1137
type type_to_pointed_type(type)
returns t if t is not a pointer type, and the pointed type if t is a pointer type.
Definition: type.c:5265
type entity_basic_concrete_type(entity)
retrieves or computes and then returns the basic concrete type of an entity
Definition: type.c:3677
bool FILE_star_type_p(type)
Definition: type.c:3046
bool pointer_type_p(type)
Check for scalar pointers.
Definition: type.c:2993
bool type_with_const_qualifier_p(type)
Is there a const qualifier associated to type t.
Definition: type.c:5483
bool entity_integer_scalar_p(entity)
for variables (like I), not constants (like 1)! use integer_constant_p() for constants
Definition: variable.c:1130
string type_to_string(const type)
type.c
Definition: type.c:51
#define type_enum_p(x)
Definition: ri.h:2968
@ is_basic_derived
Definition: ri.h:579
@ is_basic_string
Definition: ri.h:576
@ is_basic_float
Definition: ri.h:572
@ is_basic_bit
Definition: ri.h:577
@ is_basic_pointer
Definition: ri.h:578
@ is_basic_overloaded
Definition: ri.h:574
@ is_basic_int
Definition: ri.h:571
@ is_basic_logical
Definition: ri.h:573
@ is_basic_typedef
Definition: ri.h:580
@ is_basic_complex
Definition: ri.h:575
#define basic_pointer(x)
Definition: ri.h:637
#define transformer_undefined
Definition: ri.h:2847
#define REFERENCE(x)
REFERENCE.
Definition: ri.h:2296
#define basic_complex_p(x)
Definition: ri.h:626
#define basic_int_p(x)
Definition: ri.h:614
#define reference_undefined
Definition: ri.h:2302
#define normalized_linear_p(x)
Definition: ri.h:1779
#define reference_variable(x)
Definition: ri.h:2326
#define basic_derived(x)
Definition: ri.h:640
#define basic_typedef_p(x)
Definition: ri.h:641
#define range_upper(x)
Definition: ri.h:2290
#define type_tag(x)
Definition: ri.h:2940
#define reference_undefined_p(x)
Definition: ri.h:2303
#define ENTITY(x)
ENTITY.
Definition: ri.h:2755
#define basic_tag(x)
Definition: ri.h:613
#define type_variable(x)
Definition: ri.h:2949
#define basic_pointer_p(x)
Definition: ri.h:635
#define basic_derived_p(x)
Definition: ri.h:638
#define range_increment(x)
Definition: ri.h:2292
#define basic_overloaded_p(x)
Definition: ri.h:623
#define EXPRESSION(x)
EXPRESSION.
Definition: ri.h:1217
#define entity_undefined_p(x)
Definition: ri.h:2762
#define entity_undefined
Definition: ri.h:2761
#define entity_name(x)
Definition: ri.h:2790
#define transformer_arguments(x)
Definition: ri.h:2871
#define reference_indices(x)
Definition: ri.h:2328
#define preference_reference(x)
Definition: ri.h:2102
#define range_lower(x)
Definition: ri.h:2288
#define variable_dimensions(x)
Definition: ri.h:3122
#define type_undefined
Definition: ri.h:2883
@ is_type_varargs
Definition: ri.h:2902
@ is_type_void
Definition: ri.h:2904
@ is_type_enum
Definition: ri.h:2907
@ is_type_statement
Definition: ri.h:2898
@ is_type_functional
Definition: ri.h:2901
@ is_type_variable
Definition: ri.h:2900
@ is_type_union
Definition: ri.h:2906
@ is_type_area
Definition: ri.h:2899
@ is_type_unknown
Definition: ri.h:2903
@ is_type_struct
Definition: ri.h:2905
#define basic_string_p(x)
Definition: ri.h:629
#define entity_type(x)
Definition: ri.h:2792
#define normalized_linear(x)
Definition: ri.h:1781
#define basic_bit_p(x)
Definition: ri.h:632
#define variable_basic(x)
Definition: ri.h:3120
#define basic_logical_p(x)
Definition: ri.h:620
#define basic_float_p(x)
Definition: ri.h:617
Psysteme sc_variable_rename(Psysteme s, Variable v_old, Variable v_new)
Psysteme sc_variable_rename(Psysteme s, Variable v_old, Variable v_new): reecriture du systeme s remp...
Definition: sc.c:157
bool sc_weak_consistent_p(Psysteme sc)
check that sc is well defined, that the numbers of equalities and inequalities are consistent with th...
Definition: sc.c:362
void sc_creer_base(Psysteme ps)
void sc_creer_base(Psysteme ps): initialisation des parametres dimension et base d'un systeme lineair...
Definition: sc_alloc.c:129
void sc_add_inegalite(Psysteme p, Pcontrainte i)
void sc_add_inegalite(Psysteme p, Pcontrainte i): macro ajoutant une inegalite i a un systeme p; la b...
Definition: sc_alloc.c:406
Psysteme sc_dup(Psysteme ps)
Psysteme sc_dup(Psysteme ps): should becomes a link.
Definition: sc_alloc.c:176
#define level
Psysteme sc_safe_append(Psysteme s1, Psysteme s2)
Psysteme sc_safe_append(Psysteme s1, Psysteme s2) input : output : calcul de l'intersection des polye...
int fprintf()
test sc_min : ce test s'appelle par : programme fichier1.data fichier2.data ...
#define ifdebug(n)
Definition: sg.c:47
Pbase base
Definition: sc-local.h:75
le type des coefficients dans les vecteurs: Value est defini dans le package arithmetique
Definition: vecteur-local.h:89
The structure used to build lists in NewGen.
Definition: newgen_list.h:41
Definition: delay.c:253
#define abs(v)
Definition: syntax-local.h:48
#define TCST
VARIABLE REPRESENTANT LE TERME CONSTANT.
void * Variable
arithmetique is a requirement for vecteur, but I do not want to inforce it in all pips files....
Definition: vecteur-local.h:60
#define BASE_NULLE
MACROS SUR LES BASES.
#define VECTEUR_UNDEFINED_P(v)
Value vect_coeff(Variable var, Pvecteur vect)
Variable vect_coeff(Variable var, Pvecteur vect): coefficient de coordonnee var du vecteur vect —> So...
Definition: unaires.c:228
list current_module_declarations()
Definition: module.c:78