PIPS
array_resizing_top_down.c
Go to the documentation of this file.
1 /*
2 
3  $Id: array_resizing_top_down.c 23065 2016-03-02 09:05:50Z 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 
25 // do not compile unless required
26 #include "phases.h"
27 #ifdef BUILDER_ARRAY_RESIZING_TOP_DOWN
28 
29 #ifdef HAVE_CONFIG_H
30  #include "pips_config.h"
31 #endif
32 /****************************************************************** *
33  *
34  * TOP DOWN ARRAY RESIZING
35  *
36  *
37 *******************************************************************/
38 /* Example :
39  PROGRAM MAIN
40  PARAMETER (N=10,M=20)
41  REAL A(N,M)
42  CALL FOO(A,N,M)
43  END
44  SUBROUTINE FOO(X,Y,Z)
45  REAL X(Y,*) // REAL X(Y,1)
46  DO I=1,10
47  X(I,I)=1.
48  ENDDO
49  END
50  In fact, the * or 1 could be replaced by its right value Z
51 
52  This phase is based on the association rules for dummy and actual arrays, in Fortran standard (ANSI)
53  * Section 15.9.3.3
54  *
55  * Association of dummy and actual argument : arrays as dummy argument
56  * 1. If actual argument is an array name : size(dummy_array) <= size(actual_array)
57  * 2. Actual argument is an array element name :
58  * size(dummy_array) <= size(actual_array)+ 1 - subscript_value(array element)
59  *
60  * So the new value is derived from the 2 equations :
61  * size(dummy_array) = size(actual_array) (1) or
62  * size(dummy_array) = size(actual_array)+ 1 - subscript_value(array element) (2)
63  *
64  * Our remarks to simplify these equations :
65  * 1. If the first k dimensions of the actual array and the dummy array are the same,
66  * we have (1) is equivalent with
67  *
68  * size_from_position(dummy_array,k+1) = size_from_position(actual_array,k+1)
69  *
70  * 2. If the first k dimensions of the actual array and the dummy array are the same,
71  * and the first k subscripts of the array element are equal with their
72  * correspond lower bounds (column-major order), we have (2) is equivalent with:
73  *
74  * size_from_position(dummy_array,k+1) = size_from_position(actual_array,k+1) +1
75  * - subscript_value_from_position(array_element,k+1)
76 
77  ATTENTION : FORTRAN standard (15.9.3) says that an association of dummy and actual
78  arguments is valid only if the type of the actual argument is the same as the type
79  of the corresponding dummy argument. But in practice, not much program respect this
80  rule , so we have to take into account the element size when computing the new value.
81  We have an option when computing the array size : multiply the array size with the
82  element size or not
83 
84  For example : SPEC95, benchmark 125.turb3d :
85  SUBROUTINE TURB3D
86  IMPLICIT REAL*8 (A-H,O-Z)
87  COMMMON /ALL/ U(IXPP,IY,IZ)
88 
89  CALL TGVEL(U,V,W)
90 
91  SUBROUTINE TGVEL(U,V,W)
92  COMPLEX*16 U(NXHP,NY,*)
93 
94  SUBROUTINE FOO(U,V,W)
95  REAL*8 U(2,NXHP,NY,*)
96 
97  If we take into account the different types, as we have NXHP=IXPP/2, IY=NY, NZ=IZ => *=NZ */
98 
99 #include <stdio.h>
100 #include <stdlib.h>
101 #include <string.h>
102 
103 #include "genC.h"
104 #include "linear.h"
105 
106 #include "misc.h"
107 #include "properties.h"
108 #include "pipsdbm.h"
109 
110 #include "ri.h"
111 #include "ri-util.h"
112 #include "prettyprint.h"
113 #include "effects.h"
114 #include "effects-util.h"
115 
116 #include "semantics.h"
117 #include "transformer.h"
118 #include "text-util.h" // words_to_string
119 #include "callgraph.h" // module_is_called_by_main_program_p
120 
121 // for efficient_sc_check_inequality_feasibility
122 #include "transformations.h"
123 
124 #define PREFIX1 "$ARRAY_DECLARATION"
125 #define PREFIX2 "$COMMON_DECLARATION"
126 #define PREFIX3 "$COMMON_DECLARATION_END"
127 #define NEW_DECLARATIONS ".new_declarations"
128 
129 /* Define a static stack and related functions to remember the current
130  statement and then get the current precondition for top_down_adn_flt(): */
132 
133 static list l_values_of_current_caller = NIL;
136 static entity current_dummy_array = entity_undefined;
137 static entity current_variable_caller = entity_undefined;
138 static FILE * instrument_file; /*To store new array declarations and assignments*/
139 static int number_of_unnormalized_arrays_without_caller = 0;
140 static int number_of_replaced_array_declarations = 0;
141 static int number_of_instrumented_array_declarations = 0;
142 static int number_of_array_size_assignments = 0;
143 static int number_of_processed_modules = 0;
144 static string file_name_caller= NULL;
145 
146 static int opt = 0; /* 0 <= opt <= 7*/
147 
148 static void display_array_resizing_top_down_statistics()
149 {
150  user_log("* Number of unnormalized arrays without caller: %d *\n",
151  number_of_unnormalized_arrays_without_caller);
152  user_log("* Number of right array declarations replaced: %d*\n",
153  number_of_replaced_array_declarations);
154  user_log("* Number of array declarations instrumented: %d *\n",
155  number_of_instrumented_array_declarations);
156  user_log("* Number of assignments added: %d *\n",
157  number_of_array_size_assignments);
158  user_log("\n Number of processed modules: %d \n"
160 }
161 
162 static bool scalar_argument_p(entity e)
163 {
164  type t = entity_type(e);
166 }
167 
168 
169 
170 
171 static list my_list_intersection(list l1, list l2)
172 {
173  /* if l1 = NIL then return l2
174  returns a list of expressions that are in both lists l1 and l2 */
175  if (l1 != NIL)
176  {
177  list l_tmp = NIL;
178  MAP(EXPRESSION,e1,
179  {
180  if (same_expression_in_list_p(e1,l2))
181  l_tmp = gen_nconc(l_tmp,CONS(EXPRESSION,e1,NIL));
182  },
183  l1);
184  return l_tmp;
185  }
186  return l2;
187 }
188 
189 /* Multiply each element of list l by e*/
190 static list my_list_multiplication(list l, expression e)
191 {
192  list l_tmp = NIL;
193  while (!ENDP(l))
194  {
195  expression e1= EXPRESSION(CAR(l));
197  l_tmp = gen_nconc(l_tmp,CONS(EXPRESSION,e1,NIL));
198  l = CDR(l);
199  }
200  return l_tmp;
201 }
202 
203 /* Divide each element of list l by e*/
204 static list my_list_division(list l, expression e)
205 {
206  list l_tmp = NIL;
207  while (!ENDP(l))
208  {
209  expression e1= EXPRESSION(CAR(l));
211  l_tmp = gen_nconc(l_tmp,CONS(EXPRESSION,e1,NIL));
212  l = CDR(l);
213  }
214  return l_tmp;
215 }
216 
217 /* Replace each element e of list l1 by "op e"*/
218 static list my_list_change(list l1, entity op)
219 {
220  list l = NIL;
221  while (!ENDP(l1))
222  {
223  expression e = MakeUnaryCall(op,EXPRESSION(CAR(l1)));
224  l = gen_nconc(l,CONS(EXPRESSION,e,NIL));
225  l1 = CDR(l1);
226  }
227  return l;
228 }
229 
230 /* Create new list of expressions "e1 op e2" where e1 is in l1, e2 is in l2*/
231 static list my_list_combination(list l1, list l2, entity op)
232 {
233  list l = NIL;
234  while (!ENDP(l1))
235  {
236  expression e1 = EXPRESSION(CAR(l1));
237  list l_tmp = gen_copy_seq(l2);
238  while (!ENDP(l_tmp))
239  {
240  expression e2 = EXPRESSION(CAR(l_tmp));
241  expression e = MakeBinaryCall(op,e1,e2);
242 
243  /* attention : add the expression_in_list_p test ??? */
244  l = gen_nconc(l,CONS(EXPRESSION,e,NIL));
245  l_tmp = CDR(l_tmp);
246  }
247  l1=CDR(l1);
248  }
249  return l;
250 }
251 
252 static list translate_reference_to_callee_frame(expression e, reference ref, transformer context)
253 {
254  /* There are 2 cases for a reference M
255  1. Common variable : CALLER::M = CALLEE::M or M'
256  2. Precondition + Association : M =10 or M = FOO::N -1 */
257  list l = NIL;
259  normalized ne;
260  if (variable_in_common_p(en))
261  {
262  /* Check if the COOMON/FOO/ N is also declared in the callee or not
263  * We can use ram_shared which contains a list of aliased variables with en
264  * but it does not work ????
265 
266  * Another way : looking for a variable in the declaration of the callee
267  * that has the same offset in the same common block */
269  bool in_callee = false;
270  /* search for equivalent variable in the list */
271  FOREACH(ENTITY, enti,l_callee_decl)
272  {
273  if (same_scalar_location_p(en, enti))
274  {
275  expression expr;
276  /* ATTENTION : enti may be an array, such as A(2):
277  COMMON C1,C2,C3,C4,C5
278  COMMON C1,A(2,2)
279  we must return A(1,1), not A */
280  if (array_entity_p(enti))
281  {
282  variable varenti = type_variable(entity_type(enti));
283  int len = gen_length(variable_dimensions(varenti));
284  list l_inds = make_list_of_constant(1,len);
285  reference refer = make_reference(enti,l_inds);
286  expr = reference_to_expression(refer);
287  }
288  else
289  expr = entity_to_expression(enti);
290  ifdebug(2)
291  {
292  fprintf(stderr, "\n Syntax reference: Common variable, add to list: \n");
293  print_expression(expr);
294  }
295  in_callee = true;
297  break;
298  }
299  }
300 
301  /* If en is a pips created common variable, we can add this common declaration
302  to the callee's declaration list => use this value.
303  If en is an initial program's common variable => do we have right to add ?
304  confusion between local and global varibales that have same name ??? */
305 
306  if (!in_callee && strstr(entity_local_name(en),"I_PIPS_") != NULL)
307  {
308  const char* callee_name = module_local_name(current_callee);
309  string user_file = db_get_memory_resource(DBR_USER_FILE,callee_name,true);
310  string base_name = pips_basename(user_file, NULL);
312  const char* pips_variable_name = entity_local_name(en);
313  string pips_common_name = strstr(entity_local_name(en),"PIPS_");
314  string new_decl = strdup(concatenate(" INTEGER*8 ",pips_variable_name,"\n",
315  " COMMON /",pips_common_name,"/ ",pips_variable_name,"\n",NULL));
316  /* Attention, miss a test if this declaration has already been added or not
317  => Solutions :
318  1. if add pips variable declaration for current module => add for all callees
319  where the array is passed ???
320  2. Filter when using script array_resizing_instrumentation => simpler ??? */
321  fprintf(instrument_file,"%s\t%s\t%s\t(%d,%d)\n",PREFIX2,file_name,callee_name,0,1);
322  fprintf(instrument_file,"%s", new_decl);
323  fprintf(instrument_file,"%s\n",PREFIX3);
324  free(file_name), file_name = NULL;
325  free(new_decl), new_decl = NULL;
326  l = gen_nconc(l,CONS(EXPRESSION,e,NIL));
327  }
328  }
329  /* Use the precondition + association of the call site:
330  Take only the equalities.
331  Project all variables belonging to the caller, except the current variable (from e)
332  there are 2 cases :
333  1. The projection is not exact , there are over flows
334  Return the SC_UNDEFINED => what to do, like before ?
335  2. The result is exact, three small cases:
336  2.1 The system is always false sc_empty => unreachable code ?
337  2.2 The system is always true sc_rn => we have nothing ?
338  2.3 The system is parametric =>
339 
340  Look for equality that contain e
341  Delete e from the vector
342  Check if the remaining of the vectors contains only constant (TCTS)
343  or formal variable of the callee,
344  Add to the list the expression (= remaining vertor)*/
346  ne = NORMALIZE_EXPRESSION(e);
347  if (normalized_linear_p(ne))
348  {
349  Pvecteur ve = normalized_linear(ne);
350  Variable vare = var_of(ve);
352  Pbase b_tmp = ps_tmp->base;
353  /* Attention : here the transformer current_con text is consistent
354  but not the system ps_tmp. I do not understand why ?
355  fprintf(stderr, "consistent psystem ps_tmp before");
356  pips_assert("consistent psystem ps_tmp", sc_consistent_p(ps_tmp));*/
357  if (base_contains_variable_p(b_tmp,vare))
358  {
359  Psysteme ps = sc_dup(ps_tmp);
360  Pbase b = ps->base;
361  Pvecteur pv_var = VECTEUR_NUL;
362  ifdebug(4)
363  {
364  fprintf(stderr, "\n Syntax reference : using precondition + association \n");
366  }
367  for(; !VECTEUR_NUL_P(b); b = b->succ)
368  {
369  Variable var = vecteur_var(b);
371  && (var!=vare))
372  vect_add_elem(&pv_var, var, VALUE_ONE);
373  }
375  ps->nb_ineq = 0;
376  ps = sc_system_projection_along_variables(ps, pv_var);
377  vect_rm(pv_var);
378  if (ps != SC_UNDEFINED)
379  {
380  // the projection is exact
381  Pcontrainte egal, egal1;
382  for (egal = ps->egalites; egal != NULL; egal = egal1)
383  {
384  /* Take only the equations of the system */
385  Pvecteur vec = egal->vecteur;
386  if (vect_contains_variable_p(vec,vare))
387  {
388  Value vale = vect_coeff(vare,vec);
389  Pvecteur newv = VECTEUR_UNDEFINED;
390  if (value_one_p(vale) || value_mone_p(vale))
391  newv = vect_del_var(vec,vare);
392  if (value_one_p(vale))
393  vect_chg_sgn(newv);
394  if (!VECTEUR_UNDEFINED_P(newv))
395  {
396  /*the coefficient of e is 1 or -1.
397  Check if the remaining vector contains only constant or formal argument of callee*/
398  Pvecteur v;
399  bool check = true;
400  for (v = newv; (v !=NULL) && (check); v = v->succ)
401  {
402  Variable var = v->var;
404  check = false;
405  }
406  if (check)
407  {
408  expression new_exp = Pvecteur_to_expression(newv);
409  ifdebug(2)
410  {
411  fprintf(stderr, "\n Add new expression/reference to list by using prec+ asso : \n");
412  print_expression(new_exp);
413  }
414  l = gen_nconc(l,CONS(EXPRESSION,new_exp,NIL));
415  }
416  vect_rm(newv);
417  }
418  }
419  egal1 = egal->succ;
420  }
421  }
422  sc_rm(ps);
423  }
424  }
425  return l;
426 }
427 
428 static list translate_to_callee_frame(expression e, transformer context);
429 
430 static list translate_call_to_callee_frame(call ca, transformer context)
431 {
432  list l = NIL;
433  entity fun = call_function(ca);
434  list l_args = call_arguments(ca);
435  if (l_args==NIL)
436  {
437  /* Numerical constant or symbolic value (PARAMETER (M=2000)) .
438  There are 2 cases:
439  1. Constant : 2000 => add to list
440  2. Precondition + Association : 2000 = M = FOO:N -1=> add N-1 to the list
441  => trade-off : we have more chances vs more computations */
442  value val = entity_initial(fun);
444  int i;
445  /* ifdebug(2)
446  {
447  fprintf(stderr, "\n Add symbolic value to list: \n");
448  print_expression(e);
449  } */
450  /* There is something changed in PIPS ?
451  PARAMETER M =10
452  add M, not 10 as before ??? */
453  // l = gen_nconc(l,CONS(EXPRESSION,e,NIL));
454 
455  if (value_symbolic_p(val))
456  {
457  /* Symbolic constant: PARAMETER (Fortran) or CONST (Pascal) */
458  symbolic sym = value_symbolic(val);
459  con = symbolic_constant(sym);
460  }
461  if (value_constant_p(val))
462  con = value_constant(val);
463  if (!constant_undefined_p(con))
464  {
465  if (constant_int_p(con))
466  {
467  /* Looking for a formal parameter of the callee that equals
468  to i in the Precondition + Association information
469  Add this formal parameter to the list
470  We have to project all variables of the caller
471  Attention : bug in PerfectClub/mdg :
472  looking for formal parameter equal to 1 in system: {==-1} */
474  Psysteme ps = sc_dup(ps_tmp);
475  Pbase b = ps->base;
476  Pvecteur pv_var = VECTEUR_NUL;
477  /* There is something changed in PIPS ?
478  PARAMETER M =10
479  add M, not 10 as before ??? */
480  int j = constant_int(con);
481  ifdebug(2)
482  {
483  fprintf(stderr, "\n Add numerical constant to list: \n");
485  }
487  for(; !VECTEUR_NUL_P(b); b = b->succ)
488  {
489  Variable var = vecteur_var(b);
491  vect_add_elem(&pv_var, var, VALUE_ONE);
492  }
494  ps->nb_ineq = 0;
495  ps = sc_system_projection_along_variables(ps, pv_var);
496  vect_rm(pv_var);
497  if (ps != SC_UNDEFINED)
498  {
499  // the projection is exact
500  Pcontrainte egal, egal1;
501  i = constant_int(con);
502  ifdebug(4)
503  {
504  fprintf(stderr, "\n Call : using Precondition + Association to find formal parameter equal to %d \n", i);
506  }
507  for (egal = ps->egalites; egal != NULL; egal = egal1)
508  {
509  /* Take the equations of the system */
510  Pvecteur vec = egal->vecteur,v;
511  for (v = vec; v !=NULL; v = v->succ)
512  {
513  if (term_cst(v))
514  {
515  Value valu = v->val;
516  if (value_eq(value_abs(valu),int_to_value(i)))
517  {
518  Pvecteur newv = vect_del_var(vec,TCST);
519  expression new_exp;
520  if (value_pos_p(valu))
521  vect_chg_sgn(newv);
522  new_exp = Pvecteur_to_expression(newv);
523  ifdebug(2)
524  {
525  fprintf(stderr, "\n Add new expression/constant to list by prec+asso: \n");
526  print_expression(new_exp);
527  }
528  l = gen_nconc(l,CONS(EXPRESSION,new_exp,NIL));
529  vect_rm(newv);
530  }
531  }
532  }
533  egal1 = egal->succ;
534  }
535  }
536  sc_rm(ps);
537  }
538  }
539  }
540  else
541  {
542  /* e is a call, not a constant
543  Recursive : with the arguments of the call
544  As our generated expression e is a call with operators : +,-,* only,
545  we treat only these cases */
546  if (gen_length(l_args)==1)
547  {
548  expression e1 = EXPRESSION(CAR(l_args));
549  list l1 = translate_to_callee_frame(e1, context);
550  l1 = my_list_change(l1,fun);
551  l = gen_nconc(l,l1);
552  }
553  if (gen_length(l_args)==2)
554  {
555  expression e1 = EXPRESSION(CAR(l_args));
556  expression e2 = EXPRESSION(CAR(CDR(l_args)));
557  list l1 = translate_to_callee_frame(e1, context);
558  list l2 = translate_to_callee_frame(e2, context);
559  list l3 = my_list_combination(l1,l2,fun);
560  l = gen_nconc(l,l3);
561  }
562  }
563  return l;
564 }
565 
566 static list translate_to_callee_frame(expression e, transformer context)
567 {
568  /* Check if the expression e can be translated to the frame of the callee or not.
569  Return list of all possible translated expressions.
570  Return list NIL if the expression can not be translated.
571 
572  BE CAREFUL when adding expressions to list => may have combination exploration
573 
574  If e is a reference:
575  1. Common variable => replace e by the corresponding variable
576  2. From the current context of the call site (precondition + association):
577  e = e1 where e1 is constant or e1 contains formal variables of the callee
578  => l = {e1}
579 
580  If e is a call :
581  1. Storage rom :
582  n1 = numerical constant or symbolic value (PARAMETER)
583  n2 = equivalent formal variable (if exist)
584  l = {n1,n2}
585  2. Recursive : e = e1 * e2
586  translate_to_callee_frame(e1) = l1 = (e11,e12,e13)
587  translate_to_callee_frame(e2) = l2 = (e21,e22)
588  translate_to_callee_frame(e) = (e11*e21, e11*e22, e12*e21,e12*....)
589 
590  If l1 or l2 = NIL => l = NIL
591 
592  If e is a range : error, size of array can not be a range */
593 
594  list l= NIL;
595  syntax syn = expression_syntax(e);
596  tag t = syntax_tag(syn);
597  switch(t){
598  case is_syntax_reference:
599  {
601  ifdebug(2)
602  {
603  fprintf(stderr, "\n Syntax reference \n");
604  print_expression(e);
605  }
606  return translate_reference_to_callee_frame(e,ref,context);
607  }
608  case is_syntax_call:
609  {
610  call ca = syntax_call(syn);
611  ifdebug(2)
612  {
613  fprintf(stderr, "\n Syntax call \n");
614  print_expression(e);
615  }
616  return translate_call_to_callee_frame(ca,context);
617  }
618  default:
619  pips_internal_error("Abnormal cases ");
620  break;
621  }
622  return l;
623 }
624 
625 /*****************************************************************************
626 
627  This function returns the size of an unnormalized array, from position i+1:
628  (D(i+1)*...*D(n-1))
629 
630 *****************************************************************************/
631 
632 static expression size_of_unnormalized_dummy_array(entity dummy_array,int i)
633 {
634  variable dummy_var = type_variable(entity_type(dummy_array));
635  list l_dummy_dims = variable_dimensions(dummy_var);
636  int num_dim = gen_length(l_dummy_dims),j;
638  for (j=i+1; j<= num_dim-1; j++)
639  {
640  dimension dim_j = find_ith_dimension(l_dummy_dims,j);
641  expression lower_j = dimension_lower(dim_j);
642  expression upper_j = dimension_upper(dim_j);
643  expression size_j;
644  if (expression_constant_p(lower_j) && (expression_to_int(lower_j)==1))
645  size_j = copy_expression(upper_j);
646  else
647  {
648  size_j = binary_intrinsic_expression(MINUS_OPERATOR_NAME,upper_j,lower_j);
651  }
652  if (expression_undefined_p(e))
653  e = copy_expression(size_j);
654  else
656  }
657  ifdebug(2)
658  {
659  fprintf(stderr, "\n Size of unnormalized dummy array: \n");
660  print_expression(e);
661  }
662  return e;
663 }
664 
665 /* This function computes a list of translated values corresponding to the current call site,
666  and then modify the list of values of the current caller*/
667 static bool top_down_adn_call_flt(call c)
668 {
669  if(call_function(c) == current_callee)
670  {
671  int off = formal_offset(storage_formal(entity_storage(current_dummy_array)));
672  list l_actual_args = call_arguments(c);
673  expression actual_arg = find_ith_argument(l_actual_args,off);
674  if (! expression_undefined_p(actual_arg))
675  {
676  entity actual_array = expression_to_entity(actual_arg);
677  int same_dim = 0;
678  statement stmt = current_statement_head();
679  expression actual_array_size = expression_undefined;
680  list l_values_of_current_call_site = NIL;
682  ifdebug(3)
683  {
684  fprintf(stderr, " \n Current statement : \n");
686  }
688  {
690  ifdebug(4)
691  {
692  fprintf(stderr, " \n The precondition before \n");
694  }
695  // context = formal_and_actual_parameters_association(c,prec);
697  ifdebug(4)
698  {
699  fprintf(stderr, " \n The precondition after \n");
701  }
702  }
703  else
705  if (array_argument_p(actual_arg))
706  {
707  /* Actual argument is an array */
708  if (!unnormalized_array_p(actual_array))
709  {
710  /* The actual array is not an assumed_sized array nor a pointer-type array
711  Attention : there may exist a declaration REAL A(1) which is good ? */
712  reference actual_ref = expression_reference(actual_arg);
713  list l_actual_ref = reference_indices(actual_ref);
714  while (same_dimension_p(actual_array,current_dummy_array,l_actual_ref,same_dim+1,context))
715  same_dim ++;
716  ifdebug(2)
717  fprintf(stderr, "\n Number of same dimensions : %d \n",same_dim);
718  actual_array_size = size_of_actual_array(actual_array,l_actual_ref,same_dim);
719  }
720  else
721  {
722  /* Actual argument is an unnormalized array =>
723  Pointer case => compute actual array size => try to translate
724  if not ok => code instrumentation*/
725  l_values_of_current_caller = NIL;
726  return false;
727  }
728  }
729  else
730  {
731  /* Actual argument is not an array*/
732  if (scalar_argument_p(actual_array))
733  {
734  /* Actual argument is a scalar variable like in PerfectClub/spc77
735  SUBROUTINE MSTADB
736  REAL T
737  CALL SATVAP(T,1)
738  SUBROUTINE SATVAP(T,JMAX)
739  REAL T(1)
740  T(1:JMAX)*/
741  ifdebug(2)
742  fprintf(stderr,"Actual argument is a scalar variable");
743  actual_array_size = int_to_expression(1);
744  }
745  else
746  {
747  if (value_constant_p(entity_initial(actual_array)) &&
749  {
750  /* Actual argument can be a string as in SPEC/wave5
751  CALL ABRT("BAD BY",6)
752  SUBROUTINE ABRT(MESS,NC)
753  CHARACTER MESS(1)
754  The argument's name is TOP-LEVEL:'name'*/
755  ifdebug(2)
756  fprintf(stderr,"Actual argument is a string");
757  actual_array_size = int_to_expression(strlen(entity_name(actual_array))-12);
758  }
759  else
760  {
761  /* Actual argument is not an array, not a scalar variable, not a string
762  => code instrumentation*/
763  l_values_of_current_caller = NIL;
764  return false;
765  }
766  }
767  }
768  ifdebug(2)
769  {
770  fprintf(stderr, "\n Size of actual array before translation : \n");
771  print_expression(actual_array_size);
772  }
773  l_values_of_current_call_site = translate_to_callee_frame(actual_array_size,context);
774  ifdebug(2)
775  {
776  fprintf(stderr, "\n Size of actual array after translation (list of possible values) : \n");
777  print_expressions(l_values_of_current_call_site);
778  }
779  if (l_values_of_current_call_site != NIL)
780  {
781  /* we have a list of translated actual array sizes (in the callee's frame)*/
782  expression dummy_array_size = size_of_unnormalized_dummy_array(current_dummy_array,same_dim);
783  if (value_constant_p(entity_initial(actual_array)))
784  {
785  /* String case : do not compare the element size*/
786  if (!expression_undefined_p(dummy_array_size))
787  l_values_of_current_call_site = my_list_division(l_values_of_current_call_site,
788  dummy_array_size);
789  }
790  else
791  {
792  /* Now, compare the element size of actual and dummy arrays*/
793  basic b_dummy = variable_basic(type_variable(entity_type(current_dummy_array)));
794  basic b_actual = variable_basic(type_variable(entity_type(actual_array)));
795  int i_dummy = SizeOfElements(b_dummy);
796  int i_actual = SizeOfElements(b_actual);
797  if (i_dummy == i_actual)
798  {
799  if (!expression_undefined_p(dummy_array_size))
800  l_values_of_current_call_site = my_list_division(l_values_of_current_call_site,
801  dummy_array_size);
802  }
803  else
804  {
805  l_values_of_current_call_site = my_list_multiplication(l_values_of_current_call_site,
806  int_to_expression(i_actual));
807  if (expression_undefined_p(dummy_array_size))
808  l_values_of_current_call_site = my_list_division(l_values_of_current_call_site,
809  int_to_expression(i_dummy));
810  else
811  {
812  dummy_array_size = binary_intrinsic_expression(MULTIPLY_OPERATOR_NAME,dummy_array_size,
813  int_to_expression(i_dummy));
814  l_values_of_current_call_site = my_list_division(l_values_of_current_call_site,
815  dummy_array_size);
816  }
817  }
818  }
819  l_values_of_current_caller = my_list_intersection(l_values_of_current_caller,
820  l_values_of_current_call_site);
821  ifdebug(2)
822  {
823  fprintf(stderr, "\n List of values of the current caller (after intersection): \n");
824  print_expressions(l_values_of_current_caller);
825  }
826  if (l_values_of_current_caller == NIL)
827  /* There is no same value for different call sites
828  => code instrumentation */
829  return false;
830  /* We have a list of same values for different call sites => continue
831  to find other calls to the callee*/
832  return true;
833  }
834  }
835  else
836  /* Actual argument is an undefined expression => code instrumentation*/
837  l_values_of_current_caller = NIL;
838  return false;
839  }
840  return true;
841 }
842 
843 /* Insert "I_PIPS_SUB_ARRAY = actual_array_size" before each call to the current callee*/
844 static void instrument_call_rwt(call c)
845 {
846  if(call_function(c) == current_callee)
847  {
848  int off = formal_offset(storage_formal(entity_storage(current_dummy_array)));
849  list l_actual_args = call_arguments(c);
850  expression actual_arg = find_ith_argument(l_actual_args,off);
851  if (! expression_undefined_p(actual_arg))
852  {
853  entity actual_array = expression_to_entity(actual_arg);
854  expression actual_array_size = expression_undefined;
855  if (array_argument_p(actual_arg))
856  {
857  if (!unnormalized_array_p(actual_array))
858  {
859  /* The actual array is not an assumed_sized array nor a pointer-type array
860  Attention : there may exist a declaration REAL A(1) which is good ? */
861  reference actual_ref = expression_reference(actual_arg);
862  list l_actual_ref = reference_indices(actual_ref);
863  actual_array_size = size_of_actual_array(actual_array,l_actual_ref,0);
864  }
865  else
866  pips_user_warning("Array %s in module %s has unnormalized declaration\n",
868  /* How to instrument code ??? Pointer cases ???
869  Caller is not called by the main program => already excluded*/
870  }
871  else
872  {
873  /* Actual argument is not an array*/
874  if (scalar_argument_p(actual_array))
875  {
876  ifdebug(2)
877  fprintf(stderr,"Actual argument is a scalar variable");
878  actual_array_size = int_to_expression(1);
879  }
880  else
881  {
882  if (value_constant_p(entity_initial(actual_array)) &&
884  {
885  /* Actual argument can be a string whose name is TOP-LEVEL:'name'*/
886  ifdebug(2)
887  fprintf(stderr,"Actual argument is a string");
888  actual_array_size = int_to_expression(strlen(entity_name(actual_array))-12);
889  }
890  else
891  /* Abnormal case*/
892  pips_user_warning("Actual argument %s is not an array, not a scalar variable, not a string.\n",entity_local_name(actual_array));
893  }
894  }
895  if (!expression_undefined_p(actual_array_size))
896  {
897  /* The actual array size is computable */
898  statement stmt = current_statement_head();
899  int order = statement_ordering(stmt);
900  expression left = entity_to_expression(current_variable_caller);
901  statement new_s;
902  if (!value_constant_p(entity_initial(actual_array)))
903  {
904  /* Compare the element size*/
905  basic b_dummy = variable_basic(type_variable(entity_type(current_dummy_array)));
906  basic b_actual = variable_basic(type_variable(entity_type(actual_array)));
907  int i_dummy = SizeOfElements(b_dummy);
908  int i_actual = SizeOfElements(b_actual);
909  if (i_dummy != i_actual)
910  {
911  actual_array_size = binary_intrinsic_expression(MULTIPLY_OPERATOR_NAME,actual_array_size,
912  int_to_expression(i_actual));
913  actual_array_size = binary_intrinsic_expression(DIVIDE_OPERATOR_NAME,actual_array_size,
914  int_to_expression(i_dummy));
915  }
916  }
917  new_s = make_assign_statement(left,actual_array_size);
918  ifdebug(2)
919  {
920  fprintf(stderr, "\n Size of actual array: \n");
921  print_expression(actual_array_size);
922  }
923  /* As we can not modify ALL.code, we cannot use a function like :
924  insert_statement(stmt,new_s,true).
925  Instead, we have to stock the assignment as weel as the ordering
926  of the call site in a special file, named TD_instrument.out, and
927  then use a script to insert the assignment before the call site.*/
928  ifdebug(2)
929  {
930  fprintf(stderr, "\n New statements: \n");
931  print_statement(new_s);
933  }
934  fprintf(instrument_file, "%s\t%s\t%s\t(%d,%d)\n",PREFIX2,file_name_caller,
936  fprint_statement(instrument_file, new_s);
937  fprintf(instrument_file,"%s\n",PREFIX3);
938  number_of_array_size_assignments++;
939  }
940  }
941  else
942  /* Abnormal case*/
943  pips_user_warning("Actual argument is an undefined expression\n");
944  }
945 }
946 
947 /* This function computes a list of translated values for the new size of the formal array*/
948 
949 static list top_down_adn_caller_array()
950 {
952  statement caller_statement = (statement) db_get_memory_resource(DBR_CODE,caller_name,true);
953  l_values_of_current_caller = NIL;
954  make_current_statement_stack();
956  db_get_memory_resource(DBR_PRECONDITIONS,caller_name,true));
957  gen_multi_recurse(caller_statement,
958  statement_domain, current_statement_filter,current_statement_rewrite,
959  call_domain, top_down_adn_call_flt, gen_null,
960  NULL);
962  free_current_statement_stack();
963  ifdebug(2)
964  {
965  fprintf(stderr, "\n List of values of the current caller is :\n ");
966  print_expressions(l_values_of_current_caller);
967  }
968  return l_values_of_current_caller;
969 }
970 
971 static void instrument_caller_array()
972 {
974  statement caller_statement = (statement) db_get_memory_resource(DBR_CODE,caller_name,true);
975  make_current_statement_stack();
977  db_get_memory_resource(DBR_PRECONDITIONS,caller_name,true));
978  gen_multi_recurse(caller_statement,
979  statement_domain, current_statement_filter,current_statement_rewrite,
980  call_domain,gen_true,instrument_call_rwt,NULL);
982  free_current_statement_stack();
983  return;
984 }
985 
986 static void top_down_adn_callers_arrays(list l_arrays,list l_callers)
987 {
988  /* For each unnormalized array:
989  For each call site in each caller, we compute a list of possible values
990  (these values have been translated to the frame of the callee).
991  If this list is NIL => code instrumentation
992  Else, from different lists of different call sites in different callers,
993  try to find a same value that becomes the new size of the unnormalized array.
994  If this value does not exist => code instrumentation */
995 
996  /* Find out the name of the printed file in Src directory: database/Src/file.f */
997  const char* callee_name = module_local_name(current_callee);
998  string user_file = db_get_memory_resource(DBR_USER_FILE,callee_name,true);
999  string base_name = pips_basename(user_file, NULL);
1001 
1002  while (!ENDP(l_arrays))
1003  {
1004  list l = gen_copy_seq(l_callers),l_values = NIL,l_dims;
1005  bool flag = true;
1006  variable v;
1007  int length;
1008  dimension last_dim;
1009  expression new_value;
1010  current_dummy_array = ENTITY(CAR(l_arrays));
1011  v = type_variable(entity_type(current_dummy_array));
1012  l_dims = variable_dimensions(v);
1013  length = gen_length(l_dims);
1014  last_dim = find_ith_dimension(l_dims,length);
1015  while (flag && !ENDP(l))
1016  {
1017  string caller_name = STRING(CAR(l));
1019  if ( (opt%8 >= 4) && (! module_is_called_by_main_program_p(current_caller)))
1020  /* If the current caller is never called by the main program =>
1021  no need to follow this caller*/
1022  pips_user_warning("Module %s is not called by the main program\n",caller_name);
1023  else
1024  {
1025  list l_values_of_one_caller = top_down_adn_caller_array();
1026  ifdebug(2)
1027  {
1028  fprintf(stderr, "\n List of values computed for caller %s is:\n ",caller_name);
1029  print_expressions(l_values_of_one_caller);
1030  }
1031  if (l_values_of_one_caller == NIL)
1032  flag = false;
1033  else
1034  {
1035  ifdebug(2)
1036  {
1037  fprintf(stderr, "\n List of values (before intersection):\n ");
1038  print_expressions(l_values);
1039  }
1040  l_values = my_list_intersection(l_values,l_values_of_one_caller);
1041  ifdebug(2)
1042  {
1043  fprintf(stderr, "\n List of values (after intersection):\n ");
1044  print_expressions(l_values);
1045  }
1046  if (l_values == NIL)
1047  flag = false;
1048  }
1049  }
1051  l = CDR(l);
1052  }
1053  if (flag && (l_values!=NIL))
1054  {
1055  /* We have l_values is the list of same values for different callers
1056  => replace the unnormalized upper bound by 1 value in this list */
1057  normalized n;
1058  new_value = EXPRESSION (CAR(l_values));
1059  clean_all_normalized(new_value);
1060  n = NORMALIZE_EXPRESSION(new_value);
1061  if (normalized_linear_p(n))
1062  {
1063  Pvecteur ve = normalized_linear(n);
1064  new_value = Pvecteur_to_expression(ve);
1065  }
1066  else
1067  {
1068  // Try to normalize the divide expression
1070  {
1071  call c = syntax_call(expression_syntax(new_value));
1072  list l = call_arguments(c);
1073  expression e1 = EXPRESSION(CAR(l));
1074  expression e2 = EXPRESSION(CAR(CDR(l)));
1075  normalized n1;
1077  n1 = NORMALIZE_EXPRESSION(e1);
1078  if (normalized_linear_p(n1))
1079  {
1080  Pvecteur v1 = normalized_linear(n1);
1083  }
1084  }
1085  }
1086  number_of_replaced_array_declarations++;
1087  }
1088  else
1089  {
1090  /* We have different values for different callers, or there are variables that
1091  can not be translated to the callee's frame => use code instrumentation:
1092  ......................
1093  Insert "INTERGER I_PIPS_SUB_ARRAY
1094  COMMON /PIPS_SUB_ARRAY/ I_PIPS_SUB_ARRAY"
1095  in the declaration of current callee and every caller that is called by the main program
1096  Modify array declaration ARRAY(,,I_PIPS_SUB_ARRAY/dummy_array_size)
1097  Insert "I_PIPS_SUB_ARRAY = actual_array_size" before each call site
1098  ......................*/
1099 
1100  /* Insert new declaration in the current callee*/
1101  string pips_common_name = strdup(concatenate("PIPS_",callee_name,"_",
1102  entity_local_name(current_dummy_array),NULL));
1103  string pips_variable_name = strdup(concatenate("I_",pips_common_name,NULL));
1104  entity pips_common = make_new_common(pips_common_name,current_callee);
1105  entity pips_variable = make_new_integer_scalar_common_variable(pips_variable_name,
1106  current_callee,pips_common);
1107  string new_decl = strdup(concatenate(" INTEGER*8 ",pips_variable_name,"\n",
1108  " COMMON /",pips_common_name,"/ ",pips_variable_name,"\n",NULL));
1109  // string old_decl = code_decls_text(entity_code(current_callee));
1110  expression dummy_array_size = size_of_unnormalized_dummy_array(current_dummy_array,0);
1111  new_value = entity_to_expression(pips_variable);
1112  if (!expression_undefined_p(dummy_array_size))
1113  new_value = binary_intrinsic_expression(DIVIDE_OPERATOR_NAME,new_value,dummy_array_size);
1114 
1115  /* We do not modify code_decls_text(entity_code(module)) because of
1116  repeated bugs with ENTRY */
1117 
1118  /* ifdebug(2)
1119  fprintf(stderr,"\n Old declaration of %s is %s\n",callee_name,
1120  code_decls_text(entity_code(current_callee)));
1121  code_decls_text(entity_code(current_callee)) = strdup(concatenate(old_decl,new_decl,NULL));
1122  ifdebug(2)
1123  fprintf(stderr,"\n New declaration of %s is %s\n",callee_name,
1124  code_decls_text(entity_code(current_callee)));
1125  free(old_decl), old_decl = NULL; */
1126 
1127  fprintf(instrument_file,"%s\t%s\t%s\t(%d,%d)\n",PREFIX2,file_name,callee_name,0,1);
1128  fprintf(instrument_file,"%s", new_decl);
1129  fprintf(instrument_file,"%s\n",PREFIX3);
1130 
1131  /* Insert new declaration and assignments in callers that are called by the main program*/
1132  l = gen_copy_seq(l_callers);
1133  while (!ENDP(l))
1134  {
1135  string caller_name = STRING(CAR(l));
1137  if ((opt%8 >= 4)&& (! module_is_called_by_main_program_p(current_caller)))
1138  /* If the current caller is never called by the main program =>
1139  no need to follow this caller*/
1140  pips_user_warning("Module %s is not called by the main program\n",caller_name);
1141  else
1142  {
1143  string user_file_caller = db_get_memory_resource(DBR_USER_FILE,caller_name,true);
1144  string base_name_caller = pips_basename(user_file_caller, NULL);
1146  "/",base_name_caller,NULL));
1147  current_variable_caller = make_new_integer_scalar_common_variable(pips_variable_name,current_caller,
1148  pips_common);
1149  fprintf(instrument_file, "%s\t%s\t%s\t(%d,%d)\n",PREFIX2,file_name_caller,caller_name,0,1);
1150  fprintf(instrument_file, "%s", new_decl);
1151  fprintf(instrument_file, "%s\n",PREFIX3);
1152 
1153  /* insert "I_PIPS_SUB_ARRAY = actual_array_size" before each call site*/
1154  instrument_caller_array();
1155  current_variable_caller = entity_undefined;
1156  free(file_name_caller), file_name_caller = NULL;
1157  }
1159  l = CDR(l);
1160  }
1161  number_of_instrumented_array_declarations++;
1162  free(new_decl), new_decl = NULL;
1163  }
1164  fprintf(instrument_file,"%s\t%s\t%s\t%s\t%d\t%s\t%s\n",PREFIX1,file_name,
1165  callee_name,entity_local_name(current_dummy_array),length,
1167  expression_to_string(new_value));
1168  dimension_upper(last_dim) = new_value;
1169  l_arrays = CDR(l_arrays);
1170  }
1171  free(file_name), file_name = NULL;
1172 }
1173 
1174 /* The rule in pipsmake permits a top-down analysis
1175 
1176 array_resizing_top_down > MODULE.new_declarations
1177  > PROGRAM.entities
1178  < PROGRAM.entities
1179  < CALLERS.code
1180  < CALLERS.new_declarations
1181 
1182 Algorithm : For each module that is called by the main program
1183 - Take the declaration list.
1184 - Take list of unnormalized array declarations
1185  - For each unnormalized array that is formal variable.
1186  - save the offset of this array in the formal arguments list
1187  - get the list of callers of the module
1188  - for each caller, get the list of call sites
1189  - for each call site, compute the new size for this array
1190  - base on the offset
1191  - base on the actual array size (if the actual array is assumed-size => return the * value,
1192  this case violates the standard norm but it exists in many case (SPEC95/applu,..)
1193  NN 26/10/2001: But now our goal is 100% resized arrays, by using code instrumentation
1194  as a complementary phase, so this case does not exist anymore)
1195  - base on the dummy array size
1196  - base on the subscript value of the array element
1197  - base on the binding information
1198  - base on the precondition of the call site
1199  - base on the translation from the caller's to the callee's name space
1200  - if success (the size can be translated to the callee's frame) => take this new value
1201  - if fail => using code instrumentation
1202  - For all call sites and all callers, if there exists a same value
1203  => take this value as the new size for the unnormalized array
1204  - Else, using code instrumentation
1205  - Modify the upper bound of the last dimension of the unnormalized declared array entity
1206  by the new value.
1207  - Put MODULE.new_declarations = "Okay, normalization has been done with right value"
1208 - If the list is nil => put MODULE.new_declarations, "Okay, there is nothing to normalize"*/
1209 
1210 bool array_resizing_top_down(const char* module_name)
1211 {
1212  /* instrument_file is used to store new array declarations and assignments which
1213  will be used by a script to insert these declarations in the source code in:
1214  xxx.database/Src/file_name.f
1215 
1216  declaration_file is only used to make the top-down mechanics of pipsmake possible*/
1217 
1218  FILE * declaration_file;
1219  string new_declarations = db_build_file_resource_name(DBR_NEW_DECLARATIONS,
1220  module_name,NEW_DECLARATIONS);
1221  string dir_name = db_get_current_workspace_directory();
1222  string declaration_file_name = strdup(concatenate(dir_name, "/", new_declarations, NULL));
1223  string instrument_file_name = strdup(concatenate(dir_name, "/TD_instrument.out", NULL));
1224  instrument_file = safe_fopen(instrument_file_name, "a");
1226 
1228  debug_on("ARRAY_RESIZING_TOP_DOWN_DEBUG_LEVEL");
1229  ifdebug(1)
1230  fprintf(stderr, " \n Begin top down array resizing for %s \n", module_name);
1232  {
1233  list l_callee_decl = NIL, l_formal_unnorm_arrays = NIL;
1235  l_callee_decl = code_declarations(entity_code(current_callee));
1236 
1237  opt = get_int_property("ARRAY_RESIZING_TOP_DOWN_OPTION");
1238  /* opt in {0,1,2,3} => Do not use MAIN program
1239  opt in {4,5,6,7} => Use MAIN program
1240  => (opt mod 8) <= 3 or not
1241 
1242  opt in {0,1,4,5} => Compute new declarations for assumed-size and one arrays only
1243  opt in {2,3,6,7} => Compute new declarations for all formal array arguments
1244  => (opt mod 4) <= 1 or not
1245 
1246  opt in {0,2,4,6} => Compute new declarations for assumed-size and one arrays
1247  opt in {1,3,5,7} => Compute new declarations for assumed-size arrays only
1248  => (opt mod 2) = 0 or not */
1249 
1250  /* Depending on the option, take the list of arrays to treat*/
1251 
1252  MAP(ENTITY, e,{
1253  if (opt%4 <= 1)
1254  {
1255  /* Compute new declarations for assumed-size and one arrays only */
1256  if (opt%2 == 0)
1257  {
1258  /* Compute new declarations for assumed-size and one arrays */
1260  l_formal_unnorm_arrays = gen_nconc(l_formal_unnorm_arrays,CONS(ENTITY,e,NIL));
1261  }
1262  else
1263  {
1264  /* Compute new declarations for assumed-size arrays only*/
1266  l_formal_unnorm_arrays = gen_nconc(l_formal_unnorm_arrays,CONS(ENTITY,e,NIL));
1267  }
1268  }
1269  else
1270  {
1271  /* Compute new declarations for all formal array arguments
1272  To be modified, the whole C code: instrumentation, assumed-size checks,...
1273  How about multi-dimensional array ? replace all upper bounds ?
1274  => different script, ...*/
1275 
1276  // if (array_entity_p(e) && formal_parameter_p(e))
1277  // l_formal_unnorm_arrays = gen_nconc(l_formal_unnorm_arrays,CONS(ENTITY,e,NIL));
1278  user_log("\n This option has not been implemented yet");
1279  }
1280  }, l_callee_decl);
1281 
1282  if (l_formal_unnorm_arrays != NIL)
1283  {
1284  if ((opt%8 >= 4) && (!module_is_called_by_main_program_p(current_callee)))
1285  {
1286  /* Use MAIN program */
1287  pips_user_warning("Module %s is not called by the main program\n",module_name);
1288  number_of_unnormalized_arrays_without_caller +=
1289  gen_length(l_formal_unnorm_arrays);
1290  }
1291  else
1292  {
1293  /* Do not use MAIN program or module_is_called_by_main_program.
1294  Take all callers of the current callee*/
1295  callees callers = (callees) db_get_memory_resource(DBR_CALLERS,module_name,true);
1296  list l_callers = callees_callees(callers);
1297  if (l_callers == NIL)
1298  {
1299  pips_user_warning("Module %s has no caller\n",module_name);
1300  number_of_unnormalized_arrays_without_caller +=
1301  gen_length(l_formal_unnorm_arrays);
1302  }
1303  ifdebug(2)
1304  {
1305  fprintf(stderr," \n The formal unnormalized array list :");
1306  print_entities(l_formal_unnorm_arrays);
1307  fprintf(stderr," \n The caller list : ");
1308  MAP(STRING, caller_name, {
1309  (void) fprintf(stderr, "%s, ", caller_name);
1310  }, l_callers);
1311  (void) fprintf(stderr, "\n");
1312  }
1313  top_down_adn_callers_arrays(l_formal_unnorm_arrays,l_callers);
1314  }
1315  }
1317  }
1318  display_array_resizing_top_down_statistics();
1319  declaration_file = safe_fopen(declaration_file_name, "w");
1320  fprintf(declaration_file, "/* Top down array resizing for module %s. */\n", module_name);
1321  safe_fclose(declaration_file, declaration_file_name);
1322  safe_fclose(instrument_file, instrument_file_name);
1323  free(dir_name), dir_name = NULL;
1324  free(declaration_file_name), declaration_file_name = NULL;
1325  free(instrument_file_name), instrument_file_name = NULL;
1327  DB_PUT_FILE_RESOURCE(DBR_NEW_DECLARATIONS, module_name, new_declarations);
1328  ifdebug(1)
1329  fprintf(stderr, " \n End top down array resizing for %s \n", module_name);
1330  debug_off();
1331  return true;
1332 }
1333 
1334 #endif // BUILDER_ARRAY_RESIZING_TOP_DOWN
int get_int_property(const string)
void user_log(const char *format,...)
Definition: message.c:234
expression copy_expression(expression p)
EXPRESSION.
Definition: ri.c:850
reference make_reference(entity a1, list a2)
Definition: ri.c:2083
static reference ref
Current stmt (an integer)
Definition: adg_read_paf.c:163
#define PREFIX1
TO AMELIORATE : for the moment, we only use trivial_expression_p to compare offsets + array sizes CAN...
Definition: alias_check.c:102
static entity current_caller
Definition: alias_check.c:121
static int number_of_processed_modules
Definition: alias_check.c:136
#define PREFIX2
Definition: alias_check.c:103
static const char * caller_name
Definition: alias_check.c:122
#define value_pos_p(val)
#define value_mone_p(val)
#define int_to_value(i)
end LINEAR_VALUE_IS_INT
#define value_one_p(val)
int Value
#define value_eq(v1, v2)
bool operators on values
#define VALUE_ONE
#define value_abs(val)
bool base_contains_variable_p(Pbase b, Variable v)
bool base_contains_variable_p(Pbase b, Variable v): returns true if variable v is one of b's elements...
Definition: base.c:136
transformer transformer_dup(transformer t_in)
transformer package - basic routines
Definition: basic.c:49
transformer transformer_identity()
Allocate an identity transformer.
Definition: basic.c:110
bool module_is_called_by_main_program_p(entity mod)
Definition: callgraph.c:103
struct _newgen_struct_statement_ * statement
Definition: cloning.h:21
Pcontrainte contraintes_free(Pcontrainte pc)
Pcontrainte contraintes_free(Pcontrainte pc): desallocation de toutes les contraintes de la liste pc.
Definition: alloc.c:226
static entity current_callee
const char * module_name(const char *s)
Return the module part of an entity name.
Definition: entity_names.c:296
FILE * safe_fopen(const char *filename, const char *what)
Definition: file.c:67
int safe_fclose(FILE *stream, const char *filename)
Definition: file.c:77
char * pips_basename(char *fullpath, char *suffix)
Definition: file.c:822
#define STRING(x)
Definition: genC.h:87
static FILE * user_file
These functions implements the writing of objects.
Definition: genClib.c:1485
if(!(yy_init))
Definition: genread_lex.c:1029
void free(void *)
void reset_current_module_entity(void)
Reset the current module entity.
Definition: static.c:97
entity set_current_module_entity(entity)
static.c
Definition: static.c:66
void gen_multi_recurse(void *o,...)
Multi recursion visitor function.
Definition: genClib.c:3428
void gen_null(__attribute__((unused)) void *unused)
Ignore the argument.
Definition: genClib.c:2752
bool gen_true(__attribute__((unused)) gen_chunk *unused)
Return true and ignore the argument.
Definition: genClib.c:2780
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
#define NIL
The empty list (nil in Lisp)
Definition: newgen_list.h:47
list gen_copy_seq(list l)
Copy a list structure.
Definition: list.c:501
size_t gen_length(const list l)
Definition: list.c:150
#define CONS(_t_, _i_, _l_)
List element cell constructor (insert an element at the beginning of a list)
Definition: newgen_list.h:150
list gen_nconc(list cp1, list cp2)
physically concatenates CP1 and CP2 but do not duplicates the elements
Definition: list.c:344
#define CAR(pcons)
Get the value of the first element of a list.
Definition: newgen_list.h:92
#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 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
string db_get_memory_resource(const char *rname, const char *oname, bool pure)
Return the pointer to the resource, whatever it is.
Definition: database.c:755
#define DB_PUT_FILE_RESOURCE
Put a file resource into the current workspace database.
Definition: pipsdbm-local.h:85
statement make_assign_statement(expression, expression)
Definition: statement.c:583
bool expression_constant_p(expression)
HPFC module by Fabien COELHO.
Definition: expression.c:2453
string db_build_file_resource_name(const char *rname, const char *oname, const char *suffix)
returns an allocated file name for a file resource.
Definition: lowlevel.c:169
string db_get_directory_name_for_module(const char *name)
returns the allocated and mkdir'ed directory for module name
Definition: lowlevel.c:150
#define debug_on(env)
Definition: misc-local.h:157
#define pips_user_warning
Definition: misc-local.h:146
#define pips_internal_error
Definition: misc-local.h:149
#define debug_off()
Definition: misc-local.h:160
string concatenate(const char *,...)
Return the concatenation of the given strings.
Definition: string.c:183
#define DEFINE_LOCAL_STACK(name, type)
int tag
TAG.
Definition: newgen_types.h:92
#define true
Definition: newgen_types.h:81
transformer fprint_transformer(FILE *fd, transformer tf, get_variable_name_t value_name)
Definition: io.c:69
#define WORKSPACE_SRC_SPACE
Definition: pipsdbm-local.h:32
string db_get_current_workspace_directory(void)
Definition: workspace.c:96
void print_expressions(list le)
Definition: expression.c:98
void print_expression(expression e)
no file descriptor is passed to make is easier to use in a debugging stage.
Definition: expression.c:58
string expression_to_string(expression e)
Definition: expression.c:77
void fprint_statement(FILE *, statement)
Print statement "s" on file descriptor "fd".
Definition: statement.c:68
void print_statement(statement)
Print a statement on stderr.
Definition: statement.c:98
#define MINUS_OPERATOR_NAME
#define PLUS_OPERATOR_NAME
#define ORDERING_NUMBER(o)
#define ORDERING_STATEMENT(o)
#define NORMALIZE_EXPRESSION(e)
#define binary_intrinsic_expression(name, e1, e2)
#define DIVIDE_OPERATOR_NAME
#define MULTIPLY_OPERATOR_NAME
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 assumed_size_array_p(entity e)
Definition: entity.c:807
bool array_entity_p(entity e)
Definition: entity.c:793
code entity_code(entity e)
Definition: entity.c:1098
entity module_name_to_entity(const char *mn)
This is an alias for local_name_to_top_level_entity.
Definition: entity.c:1479
bool entity_main_module_p(entity e)
Definition: entity.c:700
bool unnormalized_array_p(entity e)
Definition: entity.c:846
entity make_new_common(string name, entity mod)
This function creates a common for a given name in a given module.
Definition: entity.c:1806
const char * module_local_name(entity e)
Returns the module local user name.
Definition: entity.c:582
void print_entities(list l)
Definition: entity.c:167
entity make_new_integer_scalar_common_variable(string name, entity mod, entity com)
This function creates a common variable in a given common in a given module.
Definition: entity.c:1843
const char * entity_module_name(entity e)
See comments about module_name().
Definition: entity.c:1092
expression reference_to_expression(reference r)
Definition: expression.c:196
expression Pvecteur_to_expression(Pvecteur vect)
AP, sep 25th 95 : some usefull functions moved from static_controlize/utils.c.
Definition: expression.c:1825
void clean_all_normalized(expression e)
Definition: expression.c:4102
bool same_expression_in_list_p(expression e, list le)
This function returns true, if there exists a same expression in the list false, otherwise.
Definition: expression.c:557
int expression_to_int(expression exp)
================================================================
Definition: expression.c:2205
expression entity_to_expression(entity e)
if v is a constant, returns a constant call.
Definition: expression.c:165
expression MakeBinaryCall(entity f, expression eg, expression ed)
Creates a call expression to a function with 2 arguments.
Definition: expression.c:354
expression size_of_actual_array(entity actual_array, list l_actual_ref, int i)
Definition: expression.c:4197
expression int_to_expression(_int i)
transform an int into an expression and generate the corresponding entity if necessary; it is not cle...
Definition: expression.c:1188
expression find_ith_argument(list args, int n)
Definition: expression.c:1147
bool array_argument_p(expression e)
Definition: expression.c:513
list make_list_of_constant(int val, int number)
of expression
Definition: expression.c:3369
expression MakeUnaryCall(entity f, expression a)
Creates a call expression to a function with one argument.
Definition: expression.c:342
reference expression_reference(expression e)
Short cut, meaningful only if expression_reference_p(e) holds.
Definition: expression.c:1832
entity expression_to_entity(expression e)
just returns the entity of an expression, or entity_undefined
Definition: expression.c:3140
bool operator_expression_p(expression e, string op_name)
Definition: expression.c:1087
dimension find_ith_dimension(list, int)
This function returns the ith dimension of a list of dimensions.
Definition: type.c:5621
bool variable_is_a_module_formal_parameter_p(entity, entity)
Definition: variable.c:1547
bool variable_in_common_p(entity)
true if v is in a common.
Definition: variable.c:1570
bool same_scalar_location_p(entity, entity)
FI: transferred from semantics (should be used for effect translation as well)
Definition: variable.c:1992
bool formal_parameter_p(entity)
Definition: variable.c:1489
_int SizeOfElements(basic)
This function returns the length in bytes of the Fortran or C type represented by a basic,...
Definition: size.c:297
#define formal_offset(x)
Definition: ri.h:1408
struct _newgen_struct_callees_ * callees
Definition: ri.h:55
#define value_constant(x)
Definition: ri.h:3073
#define syntax_reference(x)
Definition: ri.h:2730
#define syntax_tag(x)
Definition: ri.h:2727
#define normalized_linear_p(x)
Definition: ri.h:1779
#define call_function(x)
Definition: ri.h:709
#define callees_callees(x)
Definition: ri.h:675
#define reference_variable(x)
Definition: ri.h:2326
#define ENTITY(x)
ENTITY.
Definition: ri.h:2755
#define symbolic_constant(x)
Definition: ri.h:2599
#define constant_int(x)
Definition: ri.h:850
#define statement_ordering(x)
Definition: ri.h:2454
#define dimension_lower(x)
Definition: ri.h:980
#define type_variable(x)
Definition: ri.h:2949
#define entity_storage(x)
Definition: ri.h:2794
#define statement_domain
newgen_sizeofexpression_domain_defined
Definition: ri.h:362
#define code_declarations(x)
Definition: ri.h:784
@ is_syntax_call
Definition: ri.h:2693
@ is_syntax_reference
Definition: ri.h:2691
#define value_constant_p(x)
Definition: ri.h:3071
#define call_domain
newgen_callees_domain_defined
Definition: ri.h:58
#define storage_formal(x)
Definition: ri.h:2524
#define value_symbolic(x)
Definition: ri.h:3070
#define EXPRESSION(x)
EXPRESSION.
Definition: ri.h:1217
#define entity_undefined
Definition: ri.h:2761
#define constant_int_p(x)
Definition: ri.h:848
#define expression_undefined
Definition: ri.h:1223
#define value_symbolic_p(x)
Definition: ri.h:3068
#define entity_name(x)
Definition: ri.h:2790
#define transformer_relation(x)
Definition: ri.h:2873
#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 syntax_call(x)
Definition: ri.h:2736
#define constant_undefined_p(x)
Definition: ri.h:803
#define expression_undefined_p(x)
Definition: ri.h:1224
#define variable_dimensions(x)
Definition: ri.h:3122
#define call_arguments(x)
Definition: ri.h:711
#define entity_type(x)
Definition: ri.h:2792
#define normalized_linear(x)
Definition: ri.h:1781
#define expression_syntax(x)
Definition: ri.h:1247
#define predicate_system(x)
Definition: ri.h:2069
#define constant_undefined
Definition: ri.h:802
#define variable_basic(x)
Definition: ri.h:3120
#define entity_initial(x)
Definition: ri.h:2796
void sc_rm(Psysteme ps)
void sc_rm(Psysteme ps): liberation de l'espace memoire occupe par le systeme de contraintes ps;
Definition: sc_alloc.c:277
Psysteme sc_dup(Psysteme ps)
Psysteme sc_dup(Psysteme ps): should becomes a link.
Definition: sc_alloc.c:176
int fprintf()
test sc_min : ce test s'appelle par : programme fichier1.data fichier2.data ...
char * strdup()
void vect_chg_sgn(Pvecteur v)
void vect_chg_sgn(Pvecteur v): multiplie v par -1
Definition: scalaires.c:151
bool statement_weakly_feasible_p(statement)
utils.c
Definition: utils.c:72
transformer load_statement_precondition(statement)
void reset_precondition_map(void)
void set_precondition_map(statement_mapping)
static statement current_statement
else
Definition: set.c:239
return(s1)
#define ifdebug(n)
Definition: sg.c:47
static entity array
Pvecteur vecteur
struct Scontrainte * succ
Pcontrainte inegalites
Definition: sc-local.h:71
Pcontrainte egalites
Definition: sc-local.h:70
Pbase base
Definition: sc-local.h:75
int nb_ineq
Definition: sc-local.h:73
le type des coefficients dans les vecteurs: Value est defini dans le package arithmetique
Definition: vecteur-local.h:89
Value val
Definition: vecteur-local.h:91
Variable var
Definition: vecteur-local.h:90
struct Svecteur * succ
Definition: vecteur-local.h:92
Polymorphic argument.
Definition: printf-args.h:92
The structure used to build lists in NewGen.
Definition: newgen_list.h:41
Definition: delay.c:253
Definition: statement.c:54
bool array_resizing_top_down(const char *)
array_resizing_top_down.c
transformer formal_and_actual_parameters_association(call c, transformer pre)
formal_and_actual_parameters_association(call c, transformer pre): Add equalities between actual and ...
Definition: transformer.c:2542
bool same_dimension_p(entity actual_array, entity dummy_array, list l_actual_ref, size_t i, transformer context)
This function returns true if the actual array and the dummy array have the same dimension number i,...
Definition: transformer.c:2665
static string file_name
#define TCST
VARIABLE REPRESENTANT LE TERME CONSTANT.
#define vecteur_var(v)
#define VECTEUR_NUL
DEFINITION DU VECTEUR NUL.
#define VECTEUR_UNDEFINED
char *(* get_variable_name_t)(Variable)
Definition: vecteur-local.h:62
#define VECTEUR_NUL_P(v)
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 var_of(varval)
#define term_cst(varval)
#define VECTEUR_UNDEFINED_P(v)
void vect_rm(Pvecteur v)
void vect_rm(Pvecteur v): desallocation des couples de v;
Definition: alloc.c:78
void vect_add_elem(Pvecteur *pvect, Variable var, Value val)
void vect_add_elem(Pvecteur * pvect, Variable var, Value val): addition d'un vecteur colineaire au ve...
Definition: unaires.c:72
Pvecteur vect_del_var(Pvecteur v_in, Variable var)
Pvecteur vect_del_var(Pvecteur v_in, Variable var): allocation d'un nouveau vecteur egal a la project...
Definition: unaires.c:206
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
bool vect_contains_variable_p(Pvecteur v, Variable var)
bool vect_contains_variable_p(Pvecteur v, Variable var) BA 19/05/94 input : a vector and a variable o...
Definition: unaires.c:415