PIPS
ri_to_preconditions.c
Go to the documentation of this file.
1 /*
2 
3  $Id: ri_to_preconditions.c 23646 2021-03-10 09:51:59Z coelho $
4 
5  Copyright 1989-2016 MINES ParisTech
6 
7  This file is part of PIPS.
8 
9  PIPS is free software: you can redistribute it and/or modify it
10  under the terms of the GNU General Public License as published by
11  the Free Software Foundation, either version 3 of the License, or
12  any later version.
13 
14  PIPS is distributed in the hope that it will be useful, but WITHOUT ANY
15  WARRANTY; without even the implied warranty of MERCHANTABILITY or
16  FITNESS FOR A PARTICULAR PURPOSE.
17 
18  See the GNU General Public License for more details.
19 
20  You should have received a copy of the GNU General Public License
21  along with PIPS. If not, see <http://www.gnu.org/licenses/>.
22 
23 */
24 #ifdef HAVE_CONFIG_H
25  #include "pips_config.h"
26 #endif
27  /* semantical analysis
28  *
29  * phasis 2: propagate preconditions from statement to sub-statement,
30  * starting from the module 1st statement
31  *
32  * For (simple) interprocedural analysis, this phasis should be performed
33  * top-down on the call tree.
34  *
35  * Most functions are called xxx_to_postcondition although the purpose is
36  * to compute preconditions. However transformer are applied to preconditions
37  * to produce postconditions. Thus these modules store the preconditions
38  * and then compute an independent (i.e. no sharing) postcondition which
39  * is returned to be used by the caller.
40  *
41  * Preconditions are *NEVER* shared. Sharing would introduce desastrous
42  * side effects when they are updated as for equivalenced variables and
43  * would make freeing them impossible. Thus on a recursive path from
44  * statement_to_postcondition() to itself the precondition must have been
45  * reallocated even when its value is not changed as between a block
46  * precondition and the first statement of the block precondition. In the
47  * same way statement_to_postcondition() should never returned a
48  * postcondition aliased with its precondition argument. Somewhere
49  * in the recursive call down the data structures towards
50  * call_to_postcondition() some allocation must take place even if the
51  * statement as no effect on preconditions.
52  *
53  * Preconditions can be used to evaluate sub-expressions because Fortran
54  * standard prohibit side effects within an expression. For instance, in:
55  * J = I + F(I)
56  * function F cannot modify I.
57  *
58  * Ambiguity: the type "transformer" is used to abstract statement effects
59  * as well as effects combined from the beginning of the module to just
60  * before the current statement (precondition) to just after the current
61  * statement (postcondition). This is because it was not realized that
62  * preconditions could advantageously be seen as transformers of the initial
63  * state when designing the ri.
64  */
65 
66 #include <stdio.h>
67 #include <string.h>
68 /* #include <stdlib.h> */
69 
70 #include "genC.h"
71 #include "linear.h"
72 #include "ri.h"
73 #include "effects.h"
74 #include "ri-util.h"
75 #include "workspace-util.h"
76 #include "effects-util.h"
77 #include "control.h"
78 #include "effects-generic.h"
79 #include "effects-simple.h"
80 
81 #include "misc.h"
82 
83 #include "properties.h"
84 
85 #include "ray_dte.h"
86 #include "sommet.h"
87 #include "sg.h"
88 #include "polyedre.h"
89 
90 #include "transformer.h"
91 
92 #include "semantics.h"
93 
94 /* another non recursive section used to filter out preconditions */
96 
97 list
99 {
101 }
102 
104 {
106 }
107 /* end of the non recursive section */
108 
110 
112  list b)
113 {
114  statement s;
115  transformer post;
117  list ls = b;
118 
119  debug(8,"block_to_postcondition","begin pre=%x\n", b_pre);
120 
121  /* The first statement of the block must receive a copy
122  * of the block precondition to avoid data sharing
123  */
124 
125  if(ENDP(ls))
126  /* to avoid accumulating equivalence equalities */
127  post = transformer_dup(b_pre);
128  else {
129  s = STATEMENT(CAR(ls));
130  s_pre = transformer_dup(b_pre);
131  post = statement_to_postcondition(s_pre, s);
132  for (POP(ls) ; !ENDP(ls); POP(ls)) {
133  s = STATEMENT(CAR(ls));
134  /* the precondition has been allocated as post */
135  s_pre = post;
136  post = statement_to_postcondition(s_pre, s);
137  // FI: within a long loop body, do not replicate the loop
138  // bound constraints
139  post = transformer_normalize(post, 2);
140  }
141  }
142 
143  pips_debug(8,"post=%p end\n", post);
144  return post;
145 }
146 ␌
148  test t,
149  transformer tf)
150 {
151 # define DEBUG_TEST_TO_POSTCONDITION 7
152  expression e = test_condition(t);
153  statement st = test_true(t);
154  statement sf = test_false(t);
155  transformer post;
156 
157  debug(DEBUG_TEST_TO_POSTCONDITION,"test_to_postcondition","begin\n");
158 
159  /* there are three levels of flow sensitivity and we have only a
160  bool flag! FI */
161 
162  /* test conditions are assumed to have no side effects; it might
163  be somewhere in the standard since functions called in an expression e
164  cannot (should not) modify any variable used in e */
165 
166  if(pips_flag_p(SEMANTICS_FLOW_SENSITIVE) /* && !transformer_identity_p(tf) */) {
167  /* convex hull might avoided if it is not required or if it is certainly useless
168  * but test information should always be propagated
169  */
170  /* True and false condition transformers. The nest three variables should be freed. */
171  transformer tct = condition_to_transformer(e, pre, true);
172  transformer fct = condition_to_transformer(e, pre, false);
173  /* To obtain the best results, transformer_normalize(x,7) should
174  be applied to subtransformers generated by
175  precondition_add_condition_information() in case of equality
176  condition and in case of string or float analysis. */
177  // transformer pret =
178  // precondition_add_condition_information(transformer_dup(pre),e, pre,
179  // true);
180  transformer pret = transformer_apply(tct, pre);
181 
183 
184  transformer postt;
185  transformer postf;
186 
187  /* "strong" transformer normalization to detect dead code generated by the
188  * test condition
189  */
190  /* A normalization of degree 3 is fine */
191  /* transformer_normalize(pret, 3); */
192  transformer_normalize(pret, 7);
193  /* Just to get a stronger normalization with
194  sc_safe_normalize()... which is sc_normalize(), a weak
195  normalization function. FI: I do not understand what's
196  going on. */
198 
199  /* FI, CA: the following "optimization" was added to avoid a call
200  * to Chernikova convex hull that core dumps:-(. 8 September 1993
201  *
202  * From a theoretical point of view, pref could always be computed.
203  *
204  * FI: removed because it is mathematically wrong in many cases;
205  * the negation of the test condition is lost! I keep the structure
206  * just in case another core dump occurs (25 April 1997).
207  */
208  if(!empty_statement_p(sf)||true) {
209  /* To obtain the best results, transformer_normalize(x,7) should
210  be applied to subtransformers generated by
211  precondition_add_condition_information() in case of equality
212  condition and in case of string or float analysis. */
213  /*
214  pref = precondition_add_condition_information(transformer_dup(pre),e,
215  pre, false);
216  */
217  pref = transformer_apply(fct, pre);
218  /* transformer_normalize(pref, 3); */
219  transformer_normalize(pref, 7);
220  /* Just to get a stronger normalization with sc_safe_normalize() */
222  }
223  else {
224  /* do not try to compute a refined precondition for an empty block
225  * keep the current precondition to store in the precondition statement mapping
226  */
227  pref = transformer_dup(pre);
228  }
229 
231  pips_debug(DEBUG_TEST_TO_POSTCONDITION, "pret=%p\n", pret);
232  (void) print_transformer(pret);
233  pips_debug(DEBUG_TEST_TO_POSTCONDITION, "pref=%p\n", pref);
234  (void) print_transformer(pref);
235  }
236 
237  postt = statement_to_postcondition(pret, st);
238  postf = statement_to_postcondition(pref, sf);
239  post = transformer_convex_hull(postt, postf);
240  free_transformer(postt);
241  free_transformer(postf);
242  }
243  else {
244  /* Be careful, pre is updated by statement_to_postcondition! */
245  (void) statement_to_postcondition(pre, st);
246  (void) statement_to_postcondition(pre, sf);
247  post = transformer_apply(tf, pre);
248  }
249 
251  debug(DEBUG_TEST_TO_POSTCONDITION,"test_to_postcondition",
252  "end post=\n");
253  (void) print_transformer(post);
254  }
255 
256  return post;
257 }
258 ␌
259 static transformer
261  transformer pre,
262  expression exp,
263  transformer tf)
264 {
266 
267  if(get_bool_property("SEMANTICS_RECOMPUTE_EXPRESSION_TRANSFORMERS")) {
268  /* Wild guess. See what should be done in call_to_postcondition() */
269  //list el = expression_to_proper_effects(exp);
271  transformer new_tf = expression_to_transformer(exp, pre, el);
272  post = transformer_apply(new_tf, pre);
273  free_transformer(new_tf);
274  }
275  else
276  post = transformer_apply(tf, pre);
277 
278  return post;
279 }
280 ␌
282  call c,
283  transformer tf)
284 {
286  entity e = call_function(c);
287  tag tt;
288 
289  pips_debug(8,"begin\n");
290 
291  switch (tt = value_tag(entity_initial(e))) {
292  case is_value_intrinsic:
293  /* there is room for improvement because assign is now the
294  only well handled intrinsic */
295  pips_debug(5, "intrinsic function %s\n",
296  entity_name(e));
297  if(get_bool_property("SEMANTICS_RECOMPUTE_EXPRESSION_TRANSFORMERS")
299  entity f = call_function(c);
300  list args = call_arguments(c);
301  /* impedance problem: build an expression from call c */
304  //list ef = expression_to_proper_effects(expr);
306  transformer pre_r = transformer_range(pre);
307  transformer new_tf = intrinsic_to_transformer(f, args, pre_r, ef);
308 
309  post = transformer_apply(new_tf, pre);
311  free_expression(expr);
312  free_transformer(new_tf);
313  free_transformer(pre_r);
314  }
315  else {
316  post = transformer_apply(tf, pre);
317  }
318  /* propagate precondition pre as summary precondition
319  of user functions */
320  /* FI: don't! Summary preconditions are computed independently*/
321  /*
322  if(get_bool_property(SEMANTICS_INTERPROCEDURAL)) {
323  list args = call_arguments(c);
324  expressions_to_summary_precondition(pre, args);
325  }
326  */
327  break;
328  case is_value_code:
329  pips_debug(5, "external function %s\n", entity_name(e));
331  /*
332  list args = call_arguments(c);
333 
334  transformer pre_callee = transformer_dup(pre);
335  pre_callee =
336  add_formal_to_actual_bindings(c, pre_callee);
337  add_module_call_site_precondition(e, pre_callee);
338  */
339  /*
340  expressions_to_summary_precondition(pre, args);
341  */
342  }
343  post = transformer_apply(tf, pre);
344  break;
345  case is_value_symbolic:
346  case is_value_constant: {
347  /* Declared in preprocessor.h */
348  /* This cannot occur in Fortran, but is possible in C. */
350  post = transformer_apply(tf, pre);
351  }
352  else {
353  pips_internal_error("call to symbolic or constant %s",
354  entity_name(e));
355  }
356  break;
357  }
358  case is_value_unknown:
359  pips_internal_error("unknown function %s", entity_name(e));
360  break;
361  default:
362  pips_internal_error("unknown tag %d", tt);
363  }
364 
365  pips_debug(8,"end\n");
366 
367  return post;
368 }
369 
370 /******************************************************** DATA PRECONDITIONS */
371 
372 /* a remake that works in all cases. FC. Isn'it a bit presumptuous? FI.
373  *
374  * This function works for C as well as Fortran. Its name should be
375  * initial_value_to_preconditions.
376  *
377  * FI: It remains to be enhanced to handle more cases for non-integer
378  * types. EvalExpression() should be extended to non-integer
379  * types. The new fields of data structure "constant" should be
380  * exploited.
381  *
382  */
384 {
386  transformer pre_r = transformer_undefined; // range of pre
387  linear_hashtable_pt b = linear_hashtable_make(); /* already seen */
388  //list ce = list_undefined;
389 
390  pips_debug(8, "begin for %s\n", module_local_name(m));
391 
392  /* look for entities with an initial value. */
393  FOREACH(ENTITY, e, le) {
394  value val = entity_initial(e);
395 
396  pips_debug(8, "begin for variable %s\n", entity_name(e));
397 
398  if (entity_has_values_p(e) && !linear_hashtable_isin(b, e)) {
399  if(value_constant_p(val)) {
400  constant c = value_constant(val);
401  if (constant_int_p(c)) {
402  int int_val = constant_int(value_constant(val));
403 
405  (Variable) e, VALUE_ONE,
406  TCST, int_to_value(-int_val));
407  pre = transformer_equality_add(pre, v);
408  linear_hashtable_put_once(b, e, e);
409  }
410  else if (constant_call_p(c)) {
411  entity f = constant_call(c);
414 
415  if((basic_float_p(bt) && float_analyzed_p())
416  || (basic_string_p(bt) && string_analyzed_p())
417  || (basic_logical_p(bt) && boolean_analyzed_p()) ) {
419  (Variable) e, VALUE_ONE,
421  TCST, VALUE_ZERO);
422  pre = transformer_equality_add(pre, v);
423  linear_hashtable_put_once(b, e, e);
424  }
425  }
426  }
427  else if(value_expression_p(val)) {
428  expression expr = value_expression(val);
429  transformer npre = safe_any_expression_to_transformer(e, expr, pre, false);
430 
431  pre = transformer_combine(pre, npre);
432  pre = transformer_safe_normalize(pre, 2);
433  free_transformer(npre);
434  }
435  }
436  }
437 
439  pre_r = transformer_range(pre);
440  free_transformer(pre);
441 
443  pips_assert("some transformer", pre_r != transformer_undefined);
444 
445  ifdebug(8) {
446  dump_transformer(pre_r);
447  pips_debug(8, "end for %s\n", module_local_name(m));
448  }
449 
450  return pre_r;
451 }
452 
454 {
456  transformer pre_r = transformer_undefined; // range of pre
457  //linear_hashtable_pt b = linear_hashtable_make(); /* already seen */
458  //list ce = list_undefined;
459 
460  pips_debug(8, "begin for %s\n", module_local_name(m));
461 
462  /* look for static entities with an initial value. */
463  FOREACH(ENTITY, e, le) {
465  /* e may not have values but its initialization expression may
466  refer other variables which have values, however they are not
467  likely to be static initializations. */
469  transformer pre_r = transformer_range(pre);
471  if( !expression_undefined_p(ie) )
472  npre = any_expression_to_transformer(e, ie, pre_r, false);
473  /* any_expression_to_transformer may end up with an undefined transformer ... */
474  if(transformer_undefined_p(npre))
475  npre=transformer_identity();
476 
477  pips_debug(8, "begin for variable %s\n", entity_name(e));
478 
479 
480  pre = transformer_combine(pre, npre);
481  pre = transformer_safe_normalize(pre, 2);
482  free_transformer(npre);
483  free_transformer(pre_r);
484  }
485  }
486 
488  pre_r = transformer_range(pre);
489  free_transformer(pre);
490 
491  ifdebug(8) {
492  dump_transformer(pre_r);
493  pips_debug(8, "end for %s\n", module_local_name(m));
494  }
495 
496  return pre_r;
497 }
498 
499 static transformer data_to_prec_for_variables(entity m, list /* of entity */le)
500 {
502 
503  if(c_language_module_p(m))
504  tf = c_data_to_prec_for_variables(m, le);
507  else
508  pips_internal_error("Unexpected language");
509 
510  return tf;
511 }
512 
513 /* returns an allocated list of entities that appear in lef.
514  * an entity may appear several times.
515  */
517 {
518  list le = NIL;
519  MAP(EFFECT, e,
521  lef);
522  return gen_nreverse(le);
523 }
524 
525 /* restricted to variables with effects. */
527 {
529  list le = effects_to_entity_list(lef);
531  gen_free_list(le);
532  return pre;
533 }
534 
535 /* any variable is included. */
537 {
538  /* FI: it would be nice, if only for debugging, to pass a more
539  restricted list...
540 
541  This assumes the all variables declared in a statement is also
542  declared at the module level. */
543  // transformer pre =
544  // data_to_prec_for_variables(m, code_declarations(entity_code(m)));
547 
548  gen_free_list(dl);
549 
550  return pre;
551 }
552 
553 static transformer
555  transformer pre,
556  instruction i,
557  transformer tf)
558 {
560  test t;
561  loop l;
562  whileloop wl;
563  forloop fl;
564  call c;
565  expression exp;
566 
567  pips_debug(9,"begin pre=%p tf=%p\n", pre, tf);
568 
569  switch(instruction_tag(i)) {
572  break;
573  case is_instruction_test:
574  t = instruction_test(i);
575  post = test_to_postcondition(pre, t, tf);
576  break;
577  case is_instruction_loop:
578  l = instruction_loop(i);
579  post = loop_to_postcondition(pre, l, tf);
580  break;
582  wl = instruction_whileloop(i);
584  post = whileloop_to_postcondition(pre, wl, tf);
585  else
586  post = repeatloop_to_postcondition(pre, wl, tf);
587  break;
588  }
589  case is_instruction_forloop: {
590  fl = instruction_forloop(i);
591  post = forloop_to_postcondition(pre, fl, tf);
592  break;
593  }
594  case is_instruction_goto:
595  pips_internal_error("unexpected goto in semantics analysis");
596  /* never reached: post = pre; */
597  break;
598  case is_instruction_call:
599  c = instruction_call(i);
600  post = call_to_postcondition(pre, c, tf);
601  break;
604  tf);
605  break ;
608  post = expression_to_postcondition(pre, exp, tf);
609  break ;
611  pips_internal_error("Should have been removed by the controlizer?");
612  break ;
613  default:
614  pips_internal_error("unexpected tag %d", instruction_tag(i));
615  }
616  pips_debug(9,"resultat post, %p:\n", post);
617  ifdebug(9) (void) print_transformer(post);
618  return post;
619 }
620 ␌
621 /* Assume that all references are legal. Assume that variables used in
622  array declarations are not modified in the module. */
624 {
626 
627  FOREACH(EFFECT, e, efs) {
629  list li = reference_indices(r);
630 
631  if(!ENDP(li)){
632  entity v = reference_variable(r);
634  basic b = variable_basic(tv);
635  list ld = NIL;
636 
637  pips_assert("Variable must be of type 'variable'",
639  if(!basic_pointer_p(b)) {
640  ld = variable_dimensions(tv);
641  /* This assert is too strong in argument lists in Fortran and
642  everywhere in C */
643  //pips_assert("Reference dimension = array dimension",
644  // gen_length(li)==gen_length(ld));
645  pips_assert("Reference dimension = array dimension",
646  gen_length(li)<=gen_length(ld));
647  FOREACH(EXPRESSION, i, li) {
649  if(normalized_linear_p(ni)) {
650  Pvecteur vi = normalized_linear(ni);
651  dimension d = DIMENSION(CAR(ld));
655  Pvecteur vl = normalized_linear(nl);
656  Pvecteur vu = normalized_linear(nu);
657 
660  Pvecteur cv = vect_substract(vl, vi);
661 
662  if(renaming)
663  upwards_vect_rename(cv, pre);
664  if(!vect_constant_p(cv) || vect_coeff(TCST, cv) > 0) {
666  }
667  else {
668  vect_rm(cv);
669  }
670  }
671 
673  Pvecteur cv = vect_substract(vi, vu);
674 
675  if(renaming)
676  upwards_vect_rename(cv, pre);
677  if(!vect_constant_p(cv) || vect_coeff(TCST, cv) > 0) {
679  }
680  else {
681  vect_rm(cv);
682  }
683  }
684  }
685 
686  }
687  }
688  POP(ld);
689  }
690  }
691  }
692  }
693 }
694 
696 {
697  add_reference_information(pre, s, false);
698 }
699 
701 {
702  add_reference_information(tf, s, true);
703 }
704 
706 {
708 }
709 
710 /* Refine the precondition pre of s using side effects and compute its
711  postcondition post. Postcondition post is returned. */
713  transformer pre, /* postcondition of predecessor */
714  statement s)
715 {
718  /* FI: if the statement s is a loop, the transformer tf is not the
719  statement transformer but the transformer T* which maps the
720  precondition pre onto the loop body precondition. The real
721  statement transformer is obtained by executing the loop till
722  it is exited. See complete_any_loop_transformer() */
724 
725  /* ACHTUNG! "pre" is likely to be misused! FI, Sept. 3, 1990 */
726 
727  pips_debug(1,"begin\n");
728 
729  pips_assert("The statement precondition is defined",
730  pre != transformer_undefined);
731 
732  ifdebug(1) {
733  int so = statement_ordering(s);
734  (void) fprintf(stderr, "statement %03td (%d,%d), precondition %p:\n",
736  ORDERING_STATEMENT(so), pre);
737  (void) print_transformer(pre) ;
738  }
739 
740  pips_assert("The statement transformer is defined",
741  tf != transformer_undefined);
742  ifdebug(1) {
743  int so = statement_ordering(s);
744  (void) fprintf(stderr, "statement %03td (%d,%d), transformer %p:\n",
746  ORDERING_STATEMENT(so), tf);
747  (void) print_transformer(tf) ;
748  }
749 
750  /* To provide information for warnings */
752 
753  if (!statement_reachable_p(s))
754  {
755  /* FC: if the code is not reachable (thanks to STOP or GOTO), which
756  * is a structural information, the precondition is just empty.
757  */
758  pre = empty_transformer(pre);
759  }
760 
762  /* keep only global initial scalar integer values;
763  else, you might end up giving the same xxx#old name to
764  two different local values */
765  list non_initial_values =
769 
770  /* FI: OK, to be fixed when the declaration representation is
771  frozen. */
773  && !declaration_statement_p(s)) {
774  // FI: Just to gain some time before dealing with controlizer and declarations updates
775  //pips_internal_error("Statement %p carries declarations");
776  pips_user_warning("Statement %p with instruction carries declarations\n",
778  }
779 
780  MAPL(cv,
781  {
782  entity v = ENTITY(CAR(cv));
783  ENTITY_(CAR(cv)) = entity_to_old_value(v);
784  },
785  non_initial_values);
786 
787  /* add array references information */
788  if(get_bool_property("SEMANTICS_TRUST_ARRAY_REFERENCES")) {
790  }
791 
792  /* add type information */
793  if(get_bool_property("SEMANTICS_USE_TYPE_INFORMATION")
794  || get_bool_property("SEMANTICS_USE_TYPE_INFORMATION_IN_PRECONDITIONS")) {
796  }
797 
798  /* Add information from declarations when useful */
799  if(declaration_statement_p(s) && !ENDP(dl)) {
800  /* FI: it might be better to have another function,
801  declarations_to_postconditions(), which might be
802  slightly more accurate? Note that
803  declarations_to_transformer() does compute the
804  postcondition, but free it before returning the transformer */
806  transformer dpre = transformer_apply(dt, pre);
807 
808  //post = instruction_to_postcondition(dpre, i, tf);
809  //free_transformer(dpre);
810  // FI: Let's assume that declaration statement do not
811  //require further analysis
812  post = dpre;
813  }
814  else {
815  post = instruction_to_postcondition(pre, i, tf);
816  }
817 
818  /* Remove information when leaving a block */
821 
822  if(!ENDP(vl))
823  post = safe_transformer_projection(post, vl);
824  }
825  else if(statement_loop_p(s)
826  && !get_bool_property("SEMANTICS_KEEP_DO_LOOP_EXIT_CONDITION")) {
827  loop l = statement_loop(s);
828  entity i = loop_index(l);
829  list vl = variable_to_values(i);
830  post = safe_transformer_projection(post, vl);
831  }
832 
833  /* add equivalence equalities */
835 
836  /* eliminate redundancy, rational redundancy but not integer redundancy. */
837 
838  /* FI: nice... but time consuming! */
839  /* Version 3 is OK. Equations are over-used and make
840  * inequalities uselessly conplex
841  */
842  /* pre = transformer_normalize(pre, 3); */
843 
844  /* pre = transformer_normalize(pre, 6); */
845  /* pre = transformer_normalize(pre, 7); */
846 
847  /* The double normalization could be avoided with a non-heuristics
848  approach. For ocean, its overhead is 34s out of 782.97 to give
849  816.62s: 5 %. The double normalization is also useful for some
850  exit conditions of WHILE loops (w05, w06, w07). It is not
851  powerful enough for preconditions containing equations with
852  three or more variables such as fraer01,...*/
853 
854  if(!transformer_consistency_p(pre)) {
855  ;
856  }
857  /* BC: pre = transformer_normalize(pre, 4); */
858  /* FI->BC: why keep a first normalization before the next
859  one? FI: Because a level 2 normalization does things that
860  a level 4 does not perform! Although level 2 is much
861  faster... */
862  pre = transformer_normalize(pre, 2);
863 
864  if(!transformer_consistency_p(pre)) {
865  ;
866  }
867  /* pre = transformer_normalize(pre, 2); */
868  if(get_int_property("SEMANTICS_NORMALIZATION_LEVEL_BEFORE_STORAGE")
869  == 4)
870  // FI HardwareAccelerator/freia_52: this level does not
871  // handle the signs properly for simple equations like -i==0
872  // and it does not sort constraints lexicographically!
873  pre = transformer_normalize(pre, 4);
874  else
875  pre = transformer_normalize(pre, 2);
876 
877  if(!transformer_consistency_p(pre)) {
878  int so = statement_ordering(s);
879  fprintf(stderr, "statement %03td (%d,%d), precondition %p end:\n",
881  ORDERING_STATEMENT(so), pre);
882  print_transformer(pre);
883  pips_internal_error("Non-consistent precondition after update");
884  }
885 
886  /* Do not keep too many initial variables in the
887  * preconditions: not so smart? invariance01.c: information is
888  * lost... Since C passes values, it is usually useless to
889  * keep track of the initial values of arguments because
890  * programmers usually do not modify them. However, when they
891  * do modify the formal parameter, information is lost.
892  *
893  * See character01.c, but other counter examples above about
894  * non_initial_values.
895  *
896  * FI: redundancy possibly added. See asopt02. Maybe this
897  * should be moved up before the normalization step.
898  */
899  if(get_bool_property("SEMANTICS_FILTER_INITIAL_VALUES")) {
900  pre = transformer_filter(pre, non_initial_values);
901  pre = transformer_normalize(pre, 2);
902  }
903 
904  /* store the precondition in the ri */
906 
907  gen_free_list(non_initial_values);
908  }
909  else {
910  pips_debug(8,"precondition already available\n");
911  /* pre = statement_precondition(s); */
912  (void) print_transformer(pre);
913  pips_internal_error("precondition already computed");
914  }
915 
916  /* post = instruction_to_postcondition(pre, i, tf); */
917 
918  ifdebug(1) {
919  int so = statement_ordering(s);
920  fprintf(stderr, "statement %03td (%d,%d), precondition %p end:\n",
924  }
925 
926  ifdebug(1) {
927  int so = statement_ordering(s);
928  fprintf(stderr, "statement %03td (%d,%d), postcondition %p:\n",
930  ORDERING_STATEMENT(so), post);
931  print_transformer(post) ;
932  }
933 
934  pips_assert("no sharing",post!=pre);
936 
937  pips_debug(1, "end\n");
938 
939  return post;
940 }
941 
942 /* This function is mostly copied from
943  declarations_to_transformer(). It is used to recompute
944  intermediate preconditions and to process the initialization
945  expressions with the proper precondition. For instance, in:
946 
947  int i = 10, j = i+1, a[i], k = foo(i);
948 
949  you need to collect information about i's value to initialize j,
950  dimension a and compute the summary precondition of function foo().
951 
952  We assume that the precondition does not change within the
953  expression as in:
954 
955  int k = i++ + foo(i);
956 
957  I do not remember if the standard prohibits this or not, but it may
958  well forbid such expressions or state that the result is undefined.
959 
960  But you can also have:
961 
962  int a[i++][foo(i)];
963 
964  or
965 
966  int a[i++][j=foo(i)];
967 
968  and the intermediate steps are overlooked by
969  declaration_to_transformer() but can be checked with a proper
970  process_dimensions() function.
971 
972  This function can be called from ri_to_preconditions.c to propagate
973  preconditions or from interprocedural.c to compute summary
974  preconditions. In the second case, the necessary side effects are
975  provided by the two functional parameters.
976 */
978 (list dl,
979  transformer pre,
980  void (*process_initial_expression)(expression, transformer)
981  // FI: ongoing implementation
982  //, transformer (*process_dimensions)(entity, transformer),
983 )
984 {
985  //entity v = entity_undefined;
986  //transformer btf = transformer_undefined;
987  //transformer stf = transformer_undefined;
989  list l = dl;
990 
991  pips_debug(8,"begin\n");
992 
993  if(ENDP(l))
994  post = copy_transformer(pre);
995  else {
996  entity v = ENTITY(CAR(l));
999  // FI: ongoing implementation
1000  //transformer stf = (*process_dimensions)(v, pre);
1003 
1004  if(!expression_undefined_p(ie)) {
1005  (*process_initial_expression)(ie, pre);
1006  free_expression(ie);
1007  }
1008 
1009  post = transformer_safe_apply(stf, pre);
1010 /* post = transformer_safe_normalize(post, 4); */
1011  post = transformer_safe_normalize(post, 2);
1012 
1013  for (POP(l) ; !ENDP(l); POP(l)) {
1014  v = ENTITY(CAR(l));
1016  if(!expression_undefined_p(ie)) {
1017  (*process_initial_expression)(ie, post);
1018  free_expression(ie);
1019  }
1020 
1021  if(!transformer_undefined_p(next_pre))
1022  free_transformer(next_pre);
1023  next_pre = post;
1024  stf = declaration_to_transformer(v, next_pre);
1025  post = transformer_safe_apply(stf, next_pre);
1026 /* post = transformer_safe_normalize(post, 4); */
1027  post = transformer_safe_normalize(post, 2);
1028  btf = transformer_combine(btf, stf);
1029 /* btf = transformer_normalize(btf, 4); */
1030  btf = transformer_normalize(btf, 2);
1031 
1032  ifdebug(1)
1033  pips_assert("btf is a consistent transformer", transformer_consistency_p(btf));
1034  pips_assert("post is a consistent transformer if pre is defined",
1036  }
1037  free_transformer(btf);
1038  }
1039 
1040  pips_debug(8, "end\n");
1041  return post;
1042 }
int get_int_property(const string)
void free_transformer(transformer p)
Definition: ri.c:2616
expression make_expression(syntax a1, normalized a2)
Definition: ri.c:886
void free_expression(expression p)
Definition: ri.c:853
syntax make_syntax(enum syntax_utype tag, void *val)
Definition: ri.c:2491
transformer copy_transformer(transformer p)
TRANSFORMER.
Definition: ri.c:2613
cons * arguments_difference(cons *a1, cons *a2)
set difference: a1 - a2 ; similar to set intersection
Definition: arguments.c:233
#define VALUE_ZERO
#define int_to_value(i)
end LINEAR_VALUE_IS_INT
#define VALUE_MONE
#define VALUE_ONE
transformer transformer_dup(transformer t_in)
transformer package - basic routines
Definition: basic.c:49
transformer transformer_inequality_add(transformer tf, Pvecteur i)
Definition: basic.c:375
transformer transformer_equality_add(transformer tf, Pvecteur i)
Definition: basic.c:383
transformer empty_transformer(transformer t)
Do not allocate an empty transformer, but transform an allocated transformer into an empty_transforme...
Definition: basic.c:144
transformer transformer_identity()
Allocate an identity transformer.
Definition: basic.c:110
bool transformer_consistency_p(transformer t)
FI: I do not know if this procedure should always return or fail when an inconsistency is found.
Definition: basic.c:612
bool vect_constant_p(Pvecteur)
bool vect_constant_p(Pvecteur v): v contains only a constant term, may be zero
Definition: predicats.c:211
bool statement_reachable_p(statement)
Test if the given statement is reachable from some statements given at init_reachable(start)
Definition: unreachable.c:234
list load_module_intraprocedural_effects(entity e)
list load_proper_rw_effects_list(statement)
list expression_to_proper_constant_path_effects(expression)
#define effect_any_reference(e)
FI: cannot be used as a left hand side.
#define EFFECT(x)
EFFECT.
Definition: effects.h:608
bool get_bool_property(const string)
FC 2015-07-20: yuk, moved out to prevent an include cycle dependency include "properties....
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
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
#define NIL
The empty list (nil in Lisp)
Definition: newgen_list.h:47
size_t gen_length(const list l)
Definition: list.c:150
#define CONS(_t_, _i_, _l_)
List element cell constructor (insert an element at the beginning of a list)
Definition: newgen_list.h:150
#define CAR(pcons)
Get the value of the first element of a list.
Definition: newgen_list.h:92
void gen_free_list(list l)
free the spine of the list
Definition: list.c:327
#define FOREACH(_fe_CASTER, _fe_item, _fe_list)
Apply/map an instruction block on all the elements of a list.
Definition: newgen_list.h:179
#define MAPL(_map_list_cp, _code, _l)
Apply some code on the addresses of all the elements of a list.
Definition: newgen_list.h:203
#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
loop statement_loop(statement)
Get the loop of a statement.
Definition: statement.c:1374
bool empty_statement_p(statement)
Test if a statement is empty.
Definition: statement.c:391
bool statement_loop_p(statement)
Definition: statement.c:349
bool declaration_statement_p(statement)
Had to be optimized according to Beatrice Creusillet.
Definition: statement.c:224
bool linear_hashtable_isin(linear_hashtable_pt h, void *k)
Definition: hashpointer.c:273
void linear_hashtable_put_once(linear_hashtable_pt h, void *k, void *v)
Definition: hashpointer.c:268
linear_hashtable_pt linear_hashtable_make(void)
constructor.
Definition: hashpointer.c:165
void linear_hashtable_free(linear_hashtable_pt h)
destructor
Definition: hashpointer.c:189
string instruction_identification(instruction i)
Return a constant string representing symbolically the instruction type.
Definition: instruction.c:284
#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
void debug(const int the_expected_debug_level, const char *calling_function_name, const char *a_message_format,...)
ARARGS0.
Definition: debug.c:189
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
#define print_transformer(t)
Definition: print.c:357
#define dump_transformer(t)
Definition: print.c:355
#define pips_flag_p(p)
for upwards compatibility with Francois's modified version
#define SEMANTICS_FLOW_SENSITIVE
#define SEMANTICS_INTERPROCEDURAL
#define ENTITY_ASSIGN_P(e)
#define ORDERING_NUMBER(o)
#define ORDERING_STATEMENT(o)
#define NORMALIZE_EXPRESSION(e)
#define statement_block_p(stat)
#define is_instruction_block
soft block->sequence transition
#define instruction_block(i)
bool c_module_p(entity m)
Test if a module "m" is written in C.
Definition: entity.c:2777
const char * module_local_name(entity e)
Returns the module local user name.
Definition: entity.c:582
bool c_language_module_p(entity m)
Definition: module.c:447
bool fortran95_language_module_p(entity m)
Definition: module.c:457
bool fortran_language_module_p(entity m)
Definition: module.c:452
type ultimate_type(type)
Definition: type.c:3466
statement pop_statement_global_stack(void)
Definition: static.c:352
expression variable_initial_expression(entity)
Returns a copy of the initial (i.e.
Definition: variable.c:1899
void push_statement_on_statement_global_stack(statement)
Definition: static.c:333
bool variable_static_p(entity)
true if v appears in a SAVE statement, or in a DATA statement, or is declared static i C.
Definition: variable.c:1579
#define value_tag(x)
Definition: ri.h:3064
#define normalized_undefined
Definition: ri.h:1745
#define transformer_undefined
Definition: ri.h:2847
#define functional_result(x)
Definition: ri.h:1444
#define transformer_undefined_p(x)
Definition: ri.h:2848
#define value_constant(x)
Definition: ri.h:3073
#define normalized_linear_p(x)
Definition: ri.h:1779
#define call_function(x)
Definition: ri.h:709
#define reference_variable(x)
Definition: ri.h:2326
#define ENTITY(x)
ENTITY.
Definition: ri.h:2755
#define constant_int(x)
Definition: ri.h:850
#define instruction_loop(x)
Definition: ri.h:1520
#define statement_ordering(x)
Definition: ri.h:2454
#define type_functional(x)
Definition: ri.h:2952
#define test_false(x)
Definition: ri.h:2837
#define dimension_lower(x)
Definition: ri.h:980
#define whileloop_evaluation(x)
Definition: ri.h:3166
#define type_variable(x)
Definition: ri.h:2949
#define basic_pointer_p(x)
Definition: ri.h:635
@ is_value_intrinsic
Definition: ri.h:3034
@ is_value_unknown
Definition: ri.h:3035
@ is_value_constant
Definition: ri.h:3033
@ is_value_code
Definition: ri.h:3031
@ is_value_symbolic
Definition: ri.h:3032
@ is_syntax_call
Definition: ri.h:2693
#define value_constant_p(x)
Definition: ri.h:3071
#define EXPRESSION(x)
EXPRESSION.
Definition: ri.h:1217
#define constant_int_p(x)
Definition: ri.h:848
@ is_instruction_goto
Definition: ri.h:1473
@ is_instruction_unstructured
Definition: ri.h:1475
@ is_instruction_whileloop
Definition: ri.h:1472
@ is_instruction_expression
Definition: ri.h:1478
@ is_instruction_test
Definition: ri.h:1470
@ is_instruction_multitest
Definition: ri.h:1476
@ is_instruction_call
Definition: ri.h:1474
@ is_instruction_forloop
Definition: ri.h:1477
@ is_instruction_loop
Definition: ri.h:1471
#define instruction_tag(x)
Definition: ri.h:1511
#define entity_name(x)
Definition: ri.h:2790
#define ENTITY_(x)
Definition: ri.h:2758
#define test_true(x)
Definition: ri.h:2835
#define transformer_arguments(x)
Definition: ri.h:2871
#define dimension_upper(x)
Definition: ri.h:982
#define reference_indices(x)
Definition: ri.h:2328
#define constant_call_p(x)
Definition: ri.h:860
#define instruction_forloop(x)
Definition: ri.h:1538
#define syntax_call(x)
Definition: ri.h:2736
#define instruction_expression(x)
Definition: ri.h:1541
#define expression_undefined_p(x)
Definition: ri.h:1224
#define test_condition(x)
Definition: ri.h:2833
#define instruction_whileloop(x)
Definition: ri.h:1523
#define variable_dimensions(x)
Definition: ri.h:3122
#define statement_declarations(x)
Definition: ri.h:2460
#define statement_instruction(x)
Definition: ri.h:2458
#define instruction_call(x)
Definition: ri.h:1529
#define call_arguments(x)
Definition: ri.h:711
#define instruction_test(x)
Definition: ri.h:1517
#define basic_string_p(x)
Definition: ri.h:629
#define entity_type(x)
Definition: ri.h:2792
#define constant_call(x)
Definition: ri.h:862
#define call_undefined
Definition: ri.h:685
#define statement_number(x)
Definition: ri.h:2452
#define value_expression_p(x)
Definition: ri.h:3080
#define normalized_linear(x)
Definition: ri.h:1781
#define expression_syntax(x)
Definition: ri.h:1247
#define evaluation_before_p(x)
Definition: ri.h:1159
#define type_variable_p(x)
Definition: ri.h:2947
#define value_expression(x)
Definition: ri.h:3082
#define instruction_unstructured(x)
Definition: ri.h:1532
#define loop_index(x)
Definition: ri.h:1640
#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
#define STATEMENT(x)
STATEMENT.
Definition: ri.h:2413
#define entity_initial(x)
Definition: ri.h:2796
static transformer block_to_postcondition(transformer b_pre, list b)
void precondition_add_reference_information(transformer pre, statement s)
static transformer expression_to_postcondition(transformer pre, expression exp, transformer tf)
static void add_reference_information(transformer pre, statement s, bool renaming)
Assume that all references are legal.
transformer data_to_precondition(entity m)
restricted to variables with effects.
static list module_global_arguments
semantical analysis
static transformer c_data_to_prec_for_variables(entity m, list le)
void precondition_add_type_information(transformer pre)
void transformer_add_reference_information(transformer tf, statement s)
list effects_to_entity_list(list lef)
returns an allocated list of entities that appear in lef.
void set_module_global_arguments(list args)
static transformer test_to_postcondition(transformer pre, test t, transformer tf)
static transformer call_to_postcondition(transformer pre, call c, transformer tf)
static transformer fortran_data_to_prec_for_variables(entity m, list le)
a remake that works in all cases.
static transformer data_to_prec_for_variables(entity m, list le)
transformer statement_to_postcondition(transformer, statement)
end of the non recursive section
transformer all_data_to_precondition(entity m)
any variable is included.
#define DEBUG_TEST_TO_POSTCONDITION
static transformer instruction_to_postcondition(transformer pre, instruction i, transformer tf)
list get_module_global_arguments()
ri_to_preconditions.c
transformer propagate_preconditions_in_declarations(list dl, transformer pre, void(*process_initial_expression)(expression, transformer))
This function is mostly copied from declarations_to_transformer().
transformer declaration_to_transformer(entity v, transformer pre)
Note: initializations of static variables are not used as transformers but to initialize the program ...
transformer intrinsic_to_transformer(entity e, list pc, transformer pre, list ef)
effects of intrinsic call
transformer declarations_to_transformer(list dl, transformer pre)
For C declarations.
int fprintf()
test sc_min : ce test s'appelle par : programme fichier1.data fichier2.data ...
transformer safe_any_expression_to_transformer(entity v, expression expr, transformer pre, bool is_internal)
Always return a usable transformer.
Definition: expression.c:5156
transformer any_expression_to_transformer(entity v, expression expr, transformer pre, bool is_internal)
A set of functions to compute the transformer associated to an expression evaluated in a given contex...
Definition: expression.c:4993
transformer expression_to_transformer(expression exp, transformer pre, list el)
Just to capture side effects as the returned value is ignored.
Definition: expression.c:5190
transformer condition_to_transformer(expression cond, transformer pre, bool veracity)
To capture side effects and to add C twist for numerical conditions.
Definition: expression.c:5348
transformer whileloop_to_postcondition(transformer pre, whileloop l, transformer tf)
Definition: loop.c:3141
transformer repeatloop_to_postcondition(transformer pre, whileloop wl, transformer t_body_star)
Definition: loop.c:2760
transformer forloop_to_postcondition(transformer pre, forloop fl, transformer t_body_star)
Definition: loop.c:2707
transformer loop_to_postcondition(transformer pre, loop l, transformer tf)
Definition: loop.c:2841
transformer tf_equivalence_equalities_add(transformer tf)
mappings.c
Definition: mappings.c:83
bool value_mappings_compatible_vector_p(Pvecteur iv)
transform a vector based on variable entities into a vector based on new value entities when possible...
Definition: mappings.c:924
list variables_to_values(list list_mod)
Definition: mappings.c:966
void upwards_vect_rename(Pvecteur v, transformer post)
Renaming of variables in v according to transformations occuring later.
Definition: mappings.c:1062
list variable_to_values(entity e)
Definition: mappings.c:982
void transformer_add_type_information(transformer)
type.c
Definition: type.c:162
transformer load_statement_precondition(statement)
transformer unstructured_to_postcondition(transformer, unstructured, transformer)
transformer load_statement_transformer(statement)
void store_statement_precondition(statement, transformer)
#define ifdebug(n)
Definition: sg.c:47
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
hidden structure to store the hashtable.
Definition: hashpointer.c:66
bool stf(const string)
standardize_structure.c
transformer transformer_convex_hull(transformer t1, transformer t2)
transformer transformer_convex_hull(t1, t2): compute convex hull for t1 and t2; t1 and t2 are slightl...
Definition: convex_hull.c:216
transformer transformer_safe_apply(transformer tf, transformer pre)
Definition: transformer.c:1627
transformer transformer_normalize(transformer t, int level)
Eliminate (some) rational or integer redundancy.
Definition: transformer.c:932
transformer transformer_safe_normalize(transformer t, int level)
Definition: transformer.c:1111
transformer transformer_filter(transformer t, list args)
transformer transformer_filter(transformer t, cons * args): projection of t along the hyperplane defi...
Definition: transformer.c:1716
transformer safe_transformer_projection(transformer t, list args)
t may be undefined, args may contain values unrelated to t
Definition: transformer.c:1187
transformer transformer_combine(volatile transformer t1, transformer t2)
transformer transformer_combine(transformer t1, transformer t2): compute the composition of transform...
Definition: transformer.c:238
transformer transformer_apply(transformer tf, transformer pre)
transformer transformer_apply(transformer tf, transformer pre): apply transformer tf on precondition ...
Definition: transformer.c:1559
transformer transformer_range(transformer tf)
Return the range of relation tf in a newly allocated transformer.
Definition: transformer.c:714
transformer transformer_temporary_value_projection(transformer tf)
Definition: transformer.c:1149
bool boolean_analyzed_p(void)
Definition: value.c:305
bool float_analyzed_p(void)
Definition: value.c:315
bool string_analyzed_p(void)
Definition: value.c:310
bool entity_has_values_p(entity)
This function could be made more robust by checking the storage of e.
Definition: value.c:911
entity entity_to_old_value(entity)
Definition: value.c:869
#define exp
Avoid some warnings from "gcc -Wshadow".
Definition: vasnprintf.c:207
#define TCST
VARIABLE REPRESENTANT LE TERME CONSTANT.
#define VECTEUR_NUL
DEFINITION DU VECTEUR NUL.
void * Variable
arithmetique is a requirement for vecteur, but I do not want to inforce it in all pips files....
Definition: vecteur-local.h:60
Pvecteur vect_make(Pvecteur v, Variable var, Value val,...)
Pvecteur vect_make(v, [var, val,]* 0, val) Pvecteur v; // may be NULL, use assigne anyway Variable va...
Definition: alloc.c:165
void vect_rm(Pvecteur v)
void vect_rm(Pvecteur v): desallocation des couples de v;
Definition: alloc.c:78
Pvecteur vect_substract(Pvecteur v1, Pvecteur v2)
Pvecteur vect_substract(Pvecteur v1, Pvecteur v2): allocation d'un vecteur v dont la valeur est la di...
Definition: binaires.c:75
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 module_to_all_declarations(entity m)
Definition: module.c:323